{-# OPTIONS_GHC -w #-} {-# OPTIONS -XMagicHash -XBangPatterns -XTypeSynonymInstances -XFlexibleInstances -cpp #-} #if __GLASGOW_HASKELL__ >= 710 {-# OPTIONS_GHC -XPartialTypeSignatures #-} #endif {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveAnyClass #-} module Language.Wasm.Parser ( parseModule, parseModuleFields, parseScript, desugarize, ModuleField(..), DataSegment(..), ElemSegment(..), StartFunction(..), Export(..), ExportDesc(..), Table(..), Memory(..), Global(..), Function(..), LocalType(..), Import(..), ImportDesc(..), Instruction(..), TypeUse(..), TypeDef(..), PlainInstr(..), Index(..), Ident(..), ParamType(..), FuncType(..), -- script Script, ModuleDef(..), Command(..), Action(..), Assertion(..), Meta(..) ) where import Language.Wasm.Structure ( MemArg(..), IUnOp(..), IBinOp(..), IRelOp(..), FUnOp(..), FBinOp(..), FRelOp(..), BitSize(..), TableType(..), ElemType(..), Limit(..), GlobalType(..), ValueType(..) ) import qualified Language.Wasm.Structure as S import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Encoding as TLEncoding import qualified Data.Text.Lazy.Read as TLRead import qualified Data.ByteString.Lazy as LBS import qualified Data.ByteString.Lazy.Char8 as LBSChar8 import Data.Maybe (fromMaybe, fromJust, isNothing) import Data.List (foldl', findIndex, find) import Control.Monad (guard, foldM) import Numeric.Natural (Natural) import Data.Word (Word32, Word64) import Data.Bits ((.|.)) import Numeric.IEEE (infinity, nan, maxFinite) import Language.Wasm.FloatUtils (doubleToFloat) import Control.DeepSeq (NFData) import GHC.Generics (Generic) import Language.Wasm.Lexer ( Token ( TKeyword, TIntLit, TFloatLit, TStringLit, TId, TOpenBracket, TCloseBracket, TReserved, EOF ), Lexeme(..), AlexPosn(..), asFloat, asDouble ) import qualified Data.Array as Happy_Data_Array import qualified Data.Bits as Bits import qualified GHC.Exts as Happy_GHC_Exts import Control.Applicative(Applicative(..)) import Control.Monad (ap) -- parser produced by Happy Version 1.19.8 newtype HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131 = HappyAbsSyn HappyAny #if __GLASGOW_HASKELL__ >= 607 type HappyAny = Happy_GHC_Exts.Any #else type HappyAny = forall a . a #endif happyIn6 :: (TL.Text) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn6 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn6 #-} happyOut6 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (TL.Text) happyOut6 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut6 #-} happyIn7 :: (TL.Text) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn7 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn7 #-} happyOut7 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (TL.Text) happyOut7 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut7 #-} happyIn8 :: (Ident) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn8 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn8 #-} happyOut8 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Ident) happyOut8 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut8 #-} happyIn9 :: (ValueType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn9 #-} happyOut9 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ValueType) happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut9 #-} happyIn10 :: (Index) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn10 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn10 #-} happyOut10 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Index) happyOut10 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut10 #-} happyIn11 :: (Integer) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn11 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn11 #-} happyOut11 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Integer) happyOut11 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut11 #-} happyIn12 :: (Natural) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn12 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn12 #-} happyOut12 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Natural) happyOut12 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut12 #-} happyIn13 :: (Integer) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn13 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn13 #-} happyOut13 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Integer) happyOut13 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut13 #-} happyIn14 :: (Float) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn14 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn14 #-} happyOut14 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Float) happyOut14 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut14 #-} happyIn15 :: (Double) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn15 #-} happyOut15 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Double) happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut15 #-} happyIn16 :: (PlainInstr) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn16 #-} happyOut16 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (PlainInstr) happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut16 #-} happyIn17 :: (TypeUse) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn17 #-} happyOut17 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (TypeUse) happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut17 #-} happyIn18 :: (TypeUse) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn18 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn18 #-} happyOut18 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (TypeUse) happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut18 #-} happyIn19 :: (Maybe FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn19 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn19 #-} happyOut19 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe FuncType) happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut19 #-} happyIn20 :: (TypeDef) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn20 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn20 #-} happyOut20 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (TypeDef) happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut20 #-} happyIn21 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn21 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn21 #-} happyOut21 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut21 #-} happyIn22 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn22 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn22 #-} happyOut22 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut22 #-} happyIn23 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn23 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn23 #-} happyOut23 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut23 #-} happyIn24 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn24 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn24 #-} happyOut24 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut24 #-} happyIn25 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn25 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn25 #-} happyOut25 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut25 #-} happyIn26 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn26 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn26 #-} happyOut26 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut26 #-} happyIn27 :: (FuncType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn27 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn27 #-} happyOut27 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (FuncType) happyOut27 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut27 #-} happyIn28 :: (MemArg) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn28 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn28 #-} happyOut28 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (MemArg) happyOut28 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut28 #-} happyIn29 :: (MemArg) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn29 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn29 #-} happyOut29 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (MemArg) happyOut29 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut29 #-} happyIn30 :: (MemArg) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn30 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn30 #-} happyOut30 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (MemArg) happyOut30 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut30 #-} happyIn31 :: (MemArg) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn31 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn31 #-} happyOut31 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (MemArg) happyOut31 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut31 #-} happyIn32 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn32 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn32 #-} happyOut32 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut32 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut32 #-} happyIn33 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn33 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn33 #-} happyOut33 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut33 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut33 #-} happyIn34 :: (Maybe Ident -> Either String Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn34 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn34 #-} happyOut34 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Either String Instruction) happyOut34 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut34 #-} happyIn35 :: (Maybe Ident -> Either String Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn35 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn35 #-} happyOut35 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Either String Instruction) happyOut35 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut35 #-} happyIn36 :: (Maybe Ident -> Either String Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn36 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn36 #-} happyOut36 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Either String Instruction) happyOut36 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut36 #-} happyIn37 :: (Maybe Ident -> Either String Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn37 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn37 #-} happyOut37 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Either String Instruction) happyOut37 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut37 #-} happyIn38 :: (Maybe Ident -> Either String [Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn38 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn38 #-} happyOut38 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Either String [Instruction]) happyOut38 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut38 #-} happyIn39 :: (Maybe Ident -> Either String [Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn39 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn39 #-} happyOut39 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Either String [Instruction]) happyOut39 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut39 #-} happyIn40 :: (([Instruction], Maybe Ident)) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn40 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn40 #-} happyOut40 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (([Instruction], Maybe Ident)) happyOut40 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut40 #-} happyIn41 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn41 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn41 #-} happyOut41 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut41 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut41 #-} happyIn42 :: ((TypeUse, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn42 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn42 #-} happyOut42 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((TypeUse, [Instruction])) happyOut42 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut42 #-} happyIn43 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn43 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn43 #-} happyOut43 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut43 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut43 #-} happyIn44 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn44 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn44 #-} happyOut44 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut44 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut44 #-} happyIn45 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn45 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn45 #-} happyOut45 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut45 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut45 #-} happyIn46 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn46 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn46 #-} happyOut46 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut46 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut46 #-} happyIn47 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn47 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn47 #-} happyOut47 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut47 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut47 #-} happyIn48 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn48 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn48 #-} happyOut48 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut48 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut48 #-} happyIn49 :: (Maybe Ident -> Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn49 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn49 #-} happyOut49 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Instruction) happyOut49 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut49 #-} happyIn50 :: (Maybe Ident -> Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn50 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn50 #-} happyOut50 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Instruction) happyOut50 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut50 #-} happyIn51 :: (Maybe Ident -> Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn51 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn51 #-} happyOut51 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Instruction) happyOut51 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut51 #-} happyIn52 :: (Maybe Ident -> Instruction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn52 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn52 #-} happyOut52 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Instruction) happyOut52 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut52 #-} happyIn53 :: (Maybe Ident -> [Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn53 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn53 #-} happyOut53 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> [Instruction]) happyOut53 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut53 #-} happyIn54 :: (([Instruction], ([Instruction], [Instruction]))) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn54 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn54 #-} happyOut54 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (([Instruction], ([Instruction], [Instruction]))) happyOut54 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut54 #-} happyIn55 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn55 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn55 #-} happyOut55 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut55 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut55 #-} happyIn56 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn56 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn56 #-} happyOut56 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut56 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut56 #-} happyIn57 :: ((TypeUse, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn57 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn57 #-} happyOut57 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((TypeUse, [Instruction])) happyOut57 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut57 #-} happyIn58 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn58 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn58 #-} happyOut58 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut58 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut58 #-} happyIn59 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn59 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn59 #-} happyOut59 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut59 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut59 #-} happyIn60 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn60 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn60 #-} happyOut60 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut60 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut60 #-} happyIn61 :: ((Maybe FuncType, [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn61 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn61 #-} happyOut61 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ((Maybe FuncType, [Instruction])) happyOut61 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut61 #-} happyIn62 :: (ImportDesc) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn62 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn62 #-} happyOut62 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ImportDesc) happyOut62 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut62 #-} happyIn63 :: (Import) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn63 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn63 #-} happyOut63 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Import) happyOut63 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut63 #-} happyIn64 :: (ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn64 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn64 #-} happyOut64 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ModuleField) happyOut64 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut64 #-} happyIn65 :: (Maybe Ident -> ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn65 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn65 #-} happyOut65 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> ModuleField) happyOut65 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut65 #-} happyIn66 :: (Maybe Ident -> ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn66 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn66 #-} happyOut66 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> ModuleField) happyOut66 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut66 #-} happyIn67 :: (Maybe Ident -> ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn67 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn67 #-} happyOut67 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> ModuleField) happyOut67 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut67 #-} happyIn68 :: (Maybe Ident -> Function) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn68 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn68 #-} happyOut68 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> Function) happyOut68 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut68 #-} happyIn69 :: (Function) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn69 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn69 #-} happyOut69 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Function) happyOut69 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut69 #-} happyIn70 :: (Function) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn70 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn70 #-} happyOut70 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Function) happyOut70 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut70 #-} happyIn71 :: (Function) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn71 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn71 #-} happyOut71 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Function) happyOut71 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut71 #-} happyIn72 :: (Function) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn72 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn72 #-} happyOut72 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Function) happyOut72 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut72 #-} happyIn73 :: (([LocalType], [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn73 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn73 #-} happyOut73 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (([LocalType], [Instruction])) happyOut73 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut73 #-} happyIn74 :: (([LocalType], [Instruction])) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn74 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn74 #-} happyOut74 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (([LocalType], [Instruction])) happyOut74 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut74 #-} happyIn75 :: (ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn75 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn75 #-} happyOut75 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ModuleField) happyOut75 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut75 #-} happyIn76 :: (GlobalType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn76 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn76 #-} happyOut76 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (GlobalType) happyOut76 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut76 #-} happyIn77 :: (Maybe Ident -> ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn77 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn77 #-} happyOut77 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> ModuleField) happyOut77 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut77 #-} happyIn78 :: (Maybe Ident -> ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn78 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn78 #-} happyOut78 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> ModuleField) happyOut78 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut78 #-} happyIn79 :: ([ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn79 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn79 #-} happyOut79 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([ModuleField]) happyOut79 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut79 #-} happyIn80 :: (Maybe Ident -> [ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn80 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn80 #-} happyOut80 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> [ModuleField]) happyOut80 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut80 #-} happyIn81 :: (LBS.ByteString) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn81 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn81 #-} happyOut81 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (LBS.ByteString) happyOut81 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut81 #-} happyIn82 :: (Maybe Ident -> [ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn82 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn82 #-} happyOut82 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> [ModuleField]) happyOut82 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut82 #-} happyIn83 :: (Maybe Ident -> [ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn83 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn83 #-} happyOut83 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> [ModuleField]) happyOut83 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut83 #-} happyIn84 :: (Limit) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn84 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn84 #-} happyOut84 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Limit) happyOut84 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut84 #-} happyIn85 :: (ElemType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn85 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn85 #-} happyOut85 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ElemType) happyOut85 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut85 #-} happyIn86 :: (TableType) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn86 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn86 #-} happyOut86 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (TableType) happyOut86 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut86 #-} happyIn87 :: ([ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn87 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn87 #-} happyOut87 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([ModuleField]) happyOut87 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut87 #-} happyIn88 :: (Maybe Ident -> [ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn88 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn88 #-} happyOut88 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> [ModuleField]) happyOut88 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut88 #-} happyIn89 :: (Maybe Ident -> [ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn89 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn89 #-} happyOut89 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Maybe Ident -> [ModuleField]) happyOut89 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut89 #-} happyIn90 :: (ExportDesc) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn90 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn90 #-} happyOut90 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ExportDesc) happyOut90 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut90 #-} happyIn91 :: (Export) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn91 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn91 #-} happyOut91 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Export) happyOut91 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut91 #-} happyIn92 :: (StartFunction) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn92 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn92 #-} happyOut92 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (StartFunction) happyOut92 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut92 #-} happyIn93 :: ([Instruction]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn93 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn93 #-} happyOut93 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([Instruction]) happyOut93 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut93 #-} happyIn94 :: (ElemSegment) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn94 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn94 #-} happyOut94 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ElemSegment) happyOut94 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut94 #-} happyIn95 :: (DataSegment) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn95 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn95 #-} happyOut95 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (DataSegment) happyOut95 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut95 #-} happyIn96 :: (ModuleField) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn96 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn96 #-} happyOut96 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ModuleField) happyOut96 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut96 #-} happyIn97 :: ([ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn97 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn97 #-} happyOut97 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([ModuleField]) happyOut97 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut97 #-} happyIn98 :: ([ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn98 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn98 #-} happyOut98 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([ModuleField]) happyOut98 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut98 #-} happyIn99 :: ([ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn99 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn99 #-} happyOut99 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([ModuleField]) happyOut99 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut99 #-} happyIn100 :: ([ModuleField]) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn100 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn100 #-} happyOut100 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> ([ModuleField]) happyOut100 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut100 #-} happyIn101 :: (S.Module) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn101 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn101 #-} happyOut101 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (S.Module) happyOut101 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut101 #-} happyIn102 :: (Script) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn102 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn102 #-} happyOut102 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Script) happyOut102 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut102 #-} happyIn103 :: (Command) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn103 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn103 #-} happyOut103 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Command) happyOut103 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut103 #-} happyIn104 :: (Command) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn104 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn104 #-} happyOut104 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Command) happyOut104 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut104 #-} happyIn105 :: (ModuleDef) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn105 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn105 #-} happyOut105 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (ModuleDef) happyOut105 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut105 #-} happyIn106 :: (Action) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn106 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn106 #-} happyOut106 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Action) happyOut106 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut106 #-} happyIn107 :: (Assertion) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn107 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn107 #-} happyOut107 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Assertion) happyOut107 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut107 #-} happyIn108 :: (Either Action ModuleDef) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn108 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn108 #-} happyOut108 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Either Action ModuleDef) happyOut108 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut108 #-} happyIn109 :: (Meta) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn109 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn109 #-} happyOut109 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Meta) happyOut109 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut109 #-} happyIn110 :: t110 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn110 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn110 #-} happyOut110 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t110 happyOut110 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut110 #-} happyIn111 :: t111 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn111 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn111 #-} happyOut111 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t111 happyOut111 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut111 #-} happyIn112 :: t112 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn112 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn112 #-} happyOut112 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t112 happyOut112 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut112 #-} happyIn113 :: t113 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn113 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn113 #-} happyOut113 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t113 happyOut113 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut113 #-} happyIn114 :: t114 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn114 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn114 #-} happyOut114 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t114 happyOut114 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut114 #-} happyIn115 :: t115 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn115 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn115 #-} happyOut115 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t115 happyOut115 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut115 #-} happyIn116 :: t116 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn116 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn116 #-} happyOut116 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t116 happyOut116 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut116 #-} happyIn117 :: t117 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn117 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn117 #-} happyOut117 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t117 happyOut117 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut117 #-} happyIn118 :: t118 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn118 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn118 #-} happyOut118 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t118 happyOut118 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut118 #-} happyIn119 :: t119 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn119 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn119 #-} happyOut119 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t119 happyOut119 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut119 #-} happyIn120 :: t120 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn120 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn120 #-} happyOut120 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t120 happyOut120 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut120 #-} happyIn121 :: t121 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn121 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn121 #-} happyOut121 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t121 happyOut121 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut121 #-} happyIn122 :: t122 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn122 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn122 #-} happyOut122 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t122 happyOut122 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut122 #-} happyIn123 :: t123 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn123 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn123 #-} happyOut123 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t123 happyOut123 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut123 #-} happyIn124 :: t124 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn124 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn124 #-} happyOut124 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t124 happyOut124 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut124 #-} happyIn125 :: t125 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn125 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn125 #-} happyOut125 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t125 happyOut125 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut125 #-} happyIn126 :: t126 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn126 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn126 #-} happyOut126 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t126 happyOut126 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut126 #-} happyIn127 :: t127 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn127 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn127 #-} happyOut127 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t127 happyOut127 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut127 #-} happyIn128 :: t128 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn128 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn128 #-} happyOut128 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t128 happyOut128 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut128 #-} happyIn129 :: t129 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn129 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn129 #-} happyOut129 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t129 happyOut129 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut129 #-} happyIn130 :: t130 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn130 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn130 #-} happyOut130 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t130 happyOut130 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut130 #-} happyIn131 :: t131 -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyIn131 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyIn131 #-} happyOut131 :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> t131 happyOut131 x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOut131 #-} happyInTok :: (Lexeme) -> (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) happyInTok x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyInTok #-} happyOutTok :: (HappyAbsSyn t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131) -> (Lexeme) happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x {-# INLINE happyOutTok #-} happyExpList :: HappyAddr happyExpList = HappyA# "\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x6f\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf8\x36\xff\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\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\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x06\xe0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\xfc\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7f\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x80\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x07\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7c\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x0d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7c\x1b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf8\x36\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\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\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xc0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xc0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xe0\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xf8\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x80\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\xfe\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xfc\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\xf8\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xf8\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\xe0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xc2\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x01\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x1e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\xf8\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\xe0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3f\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xc0\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x07\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xf8\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7f\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\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\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xc0\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\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\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\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\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\xfc\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x80\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\xfc\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\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\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# {-# NOINLINE happyExpListPerState #-} happyExpListPerState st = token_strs_expected where token_strs = ["error","%dummy","%start_parseModule","%start_parseModuleFields","%start_parseScript","string","name","ident","valtype","index","int32","u32","int64","float32","float64","plaininstr","typeuse","typeuse1","typedtypeuse","typedef","functype","params_results","params_results1","results","results1","paramsresultstypeuse","paramsresulttypeuse","memarg1","memarg2","memarg4","memarg8","instruction","raw_instr","raw_block","raw_block1","raw_loop","raw_loop1","raw_if_result","raw_if_result1","raw_else","raw_call_indirect","raw_call_indirect_typeuse","raw_call_indirect_functype","raw_call_indirect_functype1","raw_call_indirect_return_functype","raw_call_indirect_return_functype1","folded_instr","folded_instr1","folded_block","folded_block1","folded_loop","folded_loop1","folded_if_result","folded_then_else","folded_else","folded_call_indirect","folded_call_indirect_typeuse","folded_call_indirect_functype","folded_call_indirect_functype1","folded_call_indirect_return_functype","folded_call_indirect_return_functype1","importdesc","import","function","export_import_typeuse_locals_body","export_import_typeuse_locals_body1","import_typeuse_locals_body1","typeuse_locals_body1","signature_locals_body","signature_locals_body1","result_locals_body","result_locals_body1","locals_body","locals_body1","global","globaltype","global_type_export_import","global_mut_export_import","memory","memory_limits_export_import","datastring","memory_limits_export_import1","memory_limits","limits","elemtype","tabletype","table","limits_elemtype_elem","import_export_table","exportdesc","export","start","offsetexpr","elemsegment","datasegment","modulefield1_single","modulefield1_multi","modulefield1","modulefield","modAsFields","mod","script","command","command1","module1","action1","assertion1","assertion_trap","meta1","list__command__","list__folded_instr__","list__index__","list__instruction__","list__modulefield__","list__str__","list__string__","list__valtype__","opt__align__","opt__ident__","opt__index__","opt__offset__","opt__u32__","rev_list1__index__","rev_list__command__","rev_list__folded_instr__","rev_list__index__","rev_list__instruction__","rev_list__modulefield__","rev_list__str__","rev_list__string__","rev_list__valtype__","'('","')'","'func'","'param'","'result'","'i32'","'i64'","'f32'","'f64'","'mut'","'anyfunc'","'type'","'unreachable'","'nop'","'br'","'br_if'","'br_table'","'return'","'call'","'call_indirect'","'drop'","'select'","'get_local'","'set_local'","'tee_local'","'get_global'","'set_global'","'i32.load'","'i64.load'","'f32.load'","'f64.load'","'i32.load8_s'","'i32.load8_u'","'i32.load16_s'","'i32.load16_u'","'i64.load8_s'","'i64.load8_u'","'i64.load16_s'","'i64.load16_u'","'i64.load32_s'","'i64.load32_u'","'i32.store'","'i64.store'","'f32.store'","'f64.store'","'i32.store8'","'i32.store16'","'i64.store8'","'i64.store16'","'i64.store32'","'current_memory'","'grow_memory'","'memory.size'","'memory.grow'","'i32.const'","'i64.const'","'f32.const'","'f64.const'","'i32.clz'","'i32.ctz'","'i32.popcnt'","'i32.add'","'i32.sub'","'i32.mul'","'i32.div_s'","'i32.div_u'","'i32.rem_s'","'i32.rem_u'","'i32.and'","'i32.or'","'i32.xor'","'i32.shl'","'i32.shr_s'","'i32.shr_u'","'i32.rotl'","'i32.rotr'","'i64.clz'","'i64.ctz'","'i64.popcnt'","'i64.add'","'i64.sub'","'i64.mul'","'i64.div_s'","'i64.div_u'","'i64.rem_s'","'i64.rem_u'","'i64.and'","'i64.or'","'i64.xor'","'i64.shl'","'i64.shr_s'","'i64.shr_u'","'i64.rotl'","'i64.rotr'","'f32.abs'","'f32.neg'","'f32.ceil'","'f32.floor'","'f32.trunc'","'f32.nearest'","'f32.sqrt'","'f32.add'","'f32.sub'","'f32.mul'","'f32.div'","'f32.min'","'f32.max'","'f32.copysign'","'f64.abs'","'f64.neg'","'f64.ceil'","'f64.floor'","'f64.trunc'","'f64.nearest'","'f64.sqrt'","'f64.add'","'f64.sub'","'f64.mul'","'f64.div'","'f64.min'","'f64.max'","'f64.copysign'","'i32.eqz'","'i32.eq'","'i32.ne'","'i32.lt_s'","'i32.lt_u'","'i32.gt_s'","'i32.gt_u'","'i32.le_s'","'i32.le_u'","'i32.ge_s'","'i32.ge_u'","'i64.eqz'","'i64.eq'","'i64.ne'","'i64.lt_s'","'i64.lt_u'","'i64.gt_s'","'i64.gt_u'","'i64.le_s'","'i64.le_u'","'i64.ge_s'","'i64.ge_u'","'f32.eq'","'f32.ne'","'f32.lt'","'f32.gt'","'f32.le'","'f32.ge'","'f64.eq'","'f64.ne'","'f64.lt'","'f64.gt'","'f64.le'","'f64.ge'","'i32.wrap/i64'","'i32.trunc_s/f32'","'i32.trunc_u/f32'","'i32.trunc_s/f64'","'i32.trunc_u/f64'","'i64.extend_s/i32'","'i64.extend_u/i32'","'i64.trunc_s/f32'","'i64.trunc_u/f32'","'i64.trunc_s/f64'","'i64.trunc_u/f64'","'f32.convert_s/i32'","'f32.convert_u/i32'","'f32.convert_s/i64'","'f32.convert_u/i64'","'f32.demote/f64'","'f64.convert_s/i32'","'f64.convert_u/i32'","'f64.convert_s/i64'","'f64.convert_u/i64'","'f64.promote/f32'","'i32.reinterpret/f32'","'i64.reinterpret/f64'","'f32.reinterpret/i32'","'f64.reinterpret/i64'","'block'","'loop'","'if'","'else'","'end'","'then'","'table'","'memory'","'global'","'import'","'export'","'local'","'elem'","'data'","'offset'","'start'","'module'","'binary'","'quote'","'register'","'invoke'","'get'","'assert_return'","'assert_return_canonical_nan'","'assert_return_arithmetic_nan'","'assert_trap'","'assert_malformed'","'assert_invalid'","'assert_unlinkable'","'assert_exhaustion'","'script'","'input'","'output'","id","int","f64","offset","align","str","EOF","%eof"] bit_start = st * 353 bit_end = (st + 1) * 353 read_bit = readArrayBit happyExpList bits = map read_bit [bit_start..bit_end - 1] bits_indexed = zip bits [0..352] token_strs_expected = concatMap f bits_indexed f (False, _) = [] f (True, nr) = [token_strs !! nr] happyActOffsets :: HappyAddr happyActOffsets = HappyA# "\x1a\x00\x1a\x00\x00\x00\x60\xff\x00\x00\x69\xff\x6c\xff\x51\x00\x72\xff\x2f\x00\x00\x00\x72\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\x8b\xff\x8b\xff\x8b\xff\x8b\xff\x8b\xff\x95\xff\x95\xff\xeb\x00\xeb\x00\xeb\x00\x00\x00\x00\x00\xfe\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x01\x59\x02\x18\x03\x18\x03\xf2\x00\x08\x01\x0d\x01\xa6\x04\x60\x05\x15\x06\x18\x06\x5b\x0a\x7c\x09\x7c\x09\x7c\x09\x0f\x0b\xc1\x0b\x00\x00\xc2\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x2f\x0d\xe4\x0d\x00\x00\x3d\x0f\x1e\x0f\x00\x00\xe4\x03\x02\x00\x01\x00\xad\x10\x55\x05\x85\x10\x00\x00\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x00\x00\x00\x00\xeb\x00\xeb\x00\xeb\x00\x00\x00\xeb\x00\x15\x12\x00\x00\x00\x00\xeb\x00\xeb\x00\xeb\x00\xeb\x00\xeb\x00\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\xf0\x11\x00\x00\x00\x00\x00\x00\x00\x00\xa6\x12\xff\x13\xec\x00\x10\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x14\x01\x14\x01\x14\x9a\x15\x9c\x15\xb4\x14\xa1\x15\xad\x15\xaf\x15\x00\x00\x58\x05\x00\x00\x00\x00\x00\x00\xd4\x15\xa8\xff\x00\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x15\x19\x00\x99\x09\x99\x09\x00\x00\x00\x00\x45\x00\xfc\x14\x0c\x15\x0c\x15\x00\x00\x04\x06\x3a\x00\x3a\x00\x3a\x00\x1f\x00\x04\x06\x04\x06\x04\x06\x0c\x15\x0c\x15\x1e\x15\x09\x06\x00\x00\xf8\x15\x00\x00\x00\x00\x0d\x16\x00\x00\x1c\x16\x00\x00\x28\x16\x29\x16\x00\x00\x00\x00\x4a\x15\x4a\x15\x4a\x15\x4a\x15\x4a\x15\x38\x16\x4e\x16\x53\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x07\x74\x15\x74\x15\x74\x15\x00\x00\x00\x00\x56\x16\xb1\x06\xb1\x06\xb1\x06\xb1\x06\x2a\x00\x00\x00\x99\x04\x94\x15\x94\x15\x65\x16\x51\x0a\x00\x00\x95\x15\x95\x15\x00\x00\x00\x00\x00\x00\x95\x15\x95\x15\x00\x00\xa3\x15\x00\x00\x00\x00\x00\x00\x3d\x08\x00\x00\x29\x03\xe3\x03\x9b\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x15\x00\x00\x00\x00\x71\x15\x00\x00\x71\x15\x00\x00\x00\x00\x00\x00\x71\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x0b\x00\x00\x00\x00\x69\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x15\x00\x00\x69\x07\xd1\x15\xd1\x15\xd7\x15\x6a\x16\x00\x00\x99\x04\xde\x16\x99\x04\xdf\x16\x06\x16\xe1\x16\xe2\x16\x99\x04\xe5\x16\xe8\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x69\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x0f\x14\x16\x00\x00\x00\x00\xee\x0f\x14\x16\x00\x00\x00\x00\x00\x00\xa2\x10\x14\x16\x14\x16\x00\x00\xf2\x08\x00\x00\x00\x00\xea\x16\x11\x16\xec\x16\x00\x00\x13\x16\xee\x16\x15\x16\x00\x00\x00\x00\x00\x00\xcd\x14\x00\x00\xf0\x16\x17\x16\xf2\x16\xf3\x16\x1f\x16\x1f\x16\x1f\x16\x1f\x16\xf5\x16\xf6\x16\xf7\x16\xf8\x16\x00\x00\xf9\x16\x21\x08\xfa\x16\xfc\x16\xfd\x16\x0d\x06\xc5\x06\x00\x00\x6f\x0c\x00\x00\xfe\x16\xff\x16\x00\x00\x00\x00\x00\x00\x00\x17\x01\x17\x02\x17\x03\x17\x04\x17\x00\x00\x00\x00\x05\x17\x00\x00\x06\x17\x00\x00\x07\x17\x23\x16\x08\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x21\x08\x00\x00\x00\x00\x56\x11\x00\x00\x00\x00\x00\x00\x0a\x12\x00\x00\x05\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x04\x33\x16\x33\x16\x0b\x17\x00\x00\x00\x00\x0c\x17\x53\x05\x00\x00\x0d\x17\x02\x00\x00\x00\x0e\x17\x0f\x17\x01\x00\x10\x17\x00\x00\x00\x00\x36\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x04\xa1\x09\x00\x00\x00\x00\x00\x00\x99\x04\x5e\x16\x00\x00\x00\x00\x00\x00\x99\x04\x62\x16\x11\x17\x12\x17\x13\x17\x00\x00\x74\x0c\x14\x17\x7d\x07\x74\x0c\x15\x17\x35\x08\x00\x00\xed\x08\x17\x17\xed\x08\x00\x00\x00\x00\x85\x0e\x00\x00\x00\x00\x19\x17\x00\x00\xbc\x01\x00\x00\x00\x00\x00\x00\x71\x02\x00\x00\x74\x0c\x00\x00\x1a\x17\x1c\x17\x1d\x17\x4b\x16\x1e\x17\x67\x16\x50\x16\x21\x17\x6b\x16\x00\x00\x22\x17\xbe\x0b\x6e\x16\x24\x17\x99\x04\x27\x17\x28\x17\x00\x00\x47\x16\x00\x00\x00\x00\x47\x16\x00\x00\x57\x05\x29\x17\x2a\x17\xe2\x03\x2b\x17\x2c\x17\x00\x00\x2d\x17\x26\x17\x30\x17\x00\x00\x00\x00\x99\x04\x00\x00\x00\x00\x00\x00\x99\x04\x31\x17\x00\x00\x00\x00\x99\x04\x32\x17\x33\x17\x34\x17\x35\x17\x36\x17\x00\x00\x78\x0c\x29\x0d\x2b\x0d\x00\x00\x37\x17\x38\x17\x00\x00\x39\x17\x3a\x17\x3b\x17\x3c\x17\x1e\x14\x99\x04\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x17\x00\x00\x69\x16\x00\x00\x57\x0c\x00\x00\x00\x00\x3f\x17\x40\x17\x41\x17\x00\x00\xde\x0d\x42\x17\xe0\x0d\x71\x16\x00\x00\x00\x00\x71\x16\x00\x00\x00\x00\x71\x16\x00\x00\x00\x00\x00\x00\x24\x0d\x00\x00\xbe\x12\x00\x00\x00\x00\x00\x00\x43\x17\x00\x00\x44\x17\x00\x00\x45\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x16\x00\x00\x8f\x16\x00\x00\x2a\x0d\x00\x00\x00\x00\x46\x17\x00\x00\x3f\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x48\x17\x4a\x17\x99\x04\x4b\x17\x3e\x0f\x4c\x17\x00\x00\x4e\x17\x43\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x0d\x00\x00\x00\x00\x72\x13\x00\x00\x00\x00\x00\x00\x00\x00\x4f\x17\x50\x17\x00\x00\x97\x16\x00\x00\x1e\x14\x00\x00\x00\x00\x00\x00\x51\x17\x00\x00\x53\x17\x00\x00\x00\x00\x00\x00\x7e\x16\x7e\x16\x00\x00\x00\x00\x00\x00\xf0\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x17\x56\x17\x57\x17\x00\x00\x00\x00"# happyGotoOffsets :: HappyAddr happyGotoOffsets = HappyA# "\x98\x0f\x09\x17\xf8\xff\x00\x00\x00\x00\x00\x00\x00\x00\xfb\x16\x00\x00\x21\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\xff\x0c\x00\x17\x00\x1b\x00\x1c\x00\x1d\x00\xf8\x0f\xa8\x10\x11\x00\x14\x00\x73\x02\xe2\xff\x00\x00\x82\x15\x00\x00\xea\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1e\x00\x58\x17\x21\x00\x22\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x24\x00\x25\x00\x00\x00\x16\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x10\x00\x00\x49\x00\xb9\x15\x9e\x15\x52\x17\x6f\x00\x00\x00\x00\x00\x00\x00\xf0\xff\x00\x00\x44\x16\x00\x00\x00\x00\x00\x00\x76\x02\x2a\x03\x09\x00\x00\x00\x2b\x03\x3d\x17\x00\x00\x00\x00\x0e\x06\x0f\x06\xc6\x06\xc7\x06\x7e\x07\x6d\x00\x08\x00\x88\x00\x18\x00\xee\xff\xf2\xff\xfd\xff\x46\x00\xfc\xff\x16\x00\x4c\x00\x4f\x00\x93\x00\x9d\x00\x9e\x00\x9f\x00\x6e\x15\x70\x15\x39\x00\x65\x00\x44\x00\x70\x00\x6f\x15\x00\x00\x00\x00\x00\x00\x00\x00\x55\x17\x5b\x17\x5c\x17\x5a\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x27\x00\x28\x00\x00\x00\x00\x00\x0b\x00\x1b\x17\x00\x00\x00\x00\x00\x00\x0a\x17\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x17\xf4\xff\x00\x00\x20\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x17\x7e\x15\x93\x15\x00\x00\x00\x00\x3a\x16\x00\x00\x5e\x17\x5f\x17\xc1\x15\x23\x17\xbf\x15\xe3\x15\x08\x16\xa6\x15\x25\x17\x2e\x17\x2f\x17\x65\x17\x66\x17\x2c\x00\x84\x00\x00\x00\x00\x00\xff\xff\x2b\x15\x00\x00\x32\x15\x00\x00\xdc\x15\x00\x00\x00\x00\x00\x00\x00\x00\x69\x17\x6d\x17\x6e\x17\x6f\x17\x70\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf6\x15\x00\x00\x43\x15\x47\x17\x2d\x00\x2e\x00\x31\x00\x24\x16\x2d\x16\x00\x00\x7f\x07\x36\x08\x37\x08\xee\x08\x49\x17\x00\x00\x71\x17\xac\x10\x5c\x11\x00\x00\x87\x16\x00\x00\x5e\x11\x60\x11\xb2\x15\x00\x00\x00\x00\x10\x12\x12\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x17\x00\x00\x84\x16\x82\x16\x8a\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xeb\x16\x00\x00\x00\x00\x4d\x17\x00\x00\x59\x17\x00\x00\x00\x00\x00\x00\x5d\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x74\x16\x00\x00\x00\x00\xef\x08\x00\x00\x00\x00\x2e\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x00\xfb\xff\x52\x0a\x14\x12\xc4\x12\x04\x00\x00\x00\x00\x00\x72\x17\x00\x00\x73\x17\x00\x00\xc6\x12\x00\x00\x00\x00\x74\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x16\x39\x16\x53\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x16\x00\x00\x90\x15\x32\x00\x3f\x16\x00\x00\x16\x16\x33\x00\x40\x16\x00\x00\x00\x00\x8e\x15\x34\x00\x35\x00\x00\x00\xfc\x00\x00\x00\x42\x16\x00\x00\xc8\x12\x00\x00\x00\x00\x00\x00\x00\x00\x78\x13\x00\x00\x00\x00\x00\x00\x19\x16\x00\x00\x00\x00\x7a\x13\x00\x00\x00\x00\x36\x00\x37\x00\x38\x00\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x0b\x00\x00\x62\x17\x00\x00\x97\x15\x4d\x16\x00\x00\xfb\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x16\x00\x00\x00\x00\x00\x00\x43\x16\x4c\x16\x0a\x0b\x48\x16\x00\x00\x4b\x00\x00\x00\x49\x16\x00\x00\x8b\x15\x00\x00\x1a\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x4d\x00\x84\x15\x67\x17\x00\x00\x4a\x16\x00\x00\x4a\x00\x00\x00\x00\x00\xc4\x15\x00\x00\x00\x00\x00\x00\xa4\x15\x00\x00\x00\x00\x00\x00\x05\x00\x4f\x16\x00\x00\x51\x16\x00\x00\x54\x16\x77\x17\x60\x17\x00\x00\x00\x00\x59\x16\x79\x17\x00\x00\x00\x00\x00\x00\x5a\x16\x7a\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x63\x17\x00\x00\x88\x15\x64\x17\x00\x00\x87\x15\x00\x00\x83\x15\x00\x00\x85\x15\x5b\x16\x00\x00\x81\x15\x00\x00\x00\x00\x75\x17\x00\x00\x8c\x15\x00\x00\x5c\x16\x00\x00\x8d\x15\x00\x00\x68\x17\x00\x00\x6a\x17\x76\x17\x6b\x17\x3d\x00\x00\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6c\x17\x00\x00\x00\x00\x7b\x17\x00\x00\x00\x00\x00\x00\xbd\x15\x00\x00\x00\x00\x4e\x00\x00\x00\x5b\x00\x00\x00\x00\x00\x1f\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7c\x17\x5d\x16\x60\x16\x00\x00\x80\x17\x00\x00\x63\x16\x00\x00\x81\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7d\x17\x7e\x17\x7f\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x16\x82\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x07\x00\x61\x16\xbf\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x17\x00\x00\x83\x17\x3f\x00\x00\x00\x64\x16\x40\x00\x66\x16\x00\x00\x41\x00\x6c\x16\x00\x00\x00\x00\x5f\x16\x00\x00\x09\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x17\x00\x00\x00\x00\x85\x17\x00\x00\x87\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x17\x00\x00\x8a\x17\x00\x00\x00\x00\x00\x00\x88\x17\x00\x00\x6d\x16\x00\x00\x6f\x16\x00\x00\x1d\x16\x00\x00\x00\x00\x89\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x45\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8c\x17\x00\x00\x00\x00\x00\x00\x42\x00\x43\x00\x00\x00\x00\x00\x00\x00\x68\x13\x00\x00\x00\x00\x70\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# happyAdjustOffset :: Happy_GHC_Exts.Int# -> Happy_GHC_Exts.Int# happyAdjustOffset off = off happyDefActions :: HappyAddr happyDefActions = HappyA# "\x00\x00\x00\x00\x64\xfe\x00\x00\xfc\xff\x00\x00\x00\x00\x79\xfe\x00\x00\x00\x00\x94\xfe\x00\x00\xa3\xfe\xa2\xfe\x9d\xfe\x9c\xfe\x9a\xfe\x9b\xfe\xa1\xfe\xa0\xfe\x9f\xfe\x9e\xfe\x99\xfe\x98\xfe\x5c\xfe\x6e\xfe\x6e\xfe\x6e\xfe\x6e\xfe\x6e\xfe\x00\x00\x00\x00\x6c\xfe\x6c\xfe\x00\x00\x5c\xfe\x65\xfe\x00\x00\x93\xfe\x5c\xfe\x92\xfe\x91\xfe\x8f\xfe\x8e\xfe\x8d\xfe\x6e\xfe\x00\x00\x6e\xfe\x6e\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6e\xfe\x6e\xfe\x6e\xfe\x00\x00\x75\xfe\xf4\xff\x00\x00\xf5\xff\xfa\xff\xf2\xff\x6d\xfe\x00\x00\x00\x00\xfb\xff\x00\x00\x00\x00\x6f\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x95\xfe\x29\xff\x5e\xfe\xe0\xfe\x00\x00\xdf\xfe\xec\xff\xeb\xff\x00\x00\x00\x00\x00\x00\xe7\xff\x00\x00\x12\xff\xe5\xff\xe4\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\x6a\xfe\xc7\xff\xc6\xff\xc5\xff\xc4\xff\x00\x00\x00\x00\x00\x00\x00\x00\xbf\xff\xbe\xff\xbd\xff\xbc\xff\xbb\xff\xba\xff\xb9\xff\xb8\xff\xb7\xff\xb6\xff\xb5\xff\xb4\xff\xb3\xff\xb2\xff\xb1\xff\xb0\xff\xaf\xff\xae\xff\xad\xff\xac\xff\xab\xff\xaa\xff\xa9\xff\xa8\xff\xa7\xff\xa6\xff\xa5\xff\xa4\xff\xa3\xff\xa2\xff\xa1\xff\xa0\xff\x9f\xff\x9e\xff\x9d\xff\x9c\xff\x9b\xff\x9a\xff\x99\xff\x98\xff\x97\xff\x96\xff\x95\xff\x94\xff\x93\xff\x92\xff\x91\xff\x90\xff\x8f\xff\x8e\xff\x8d\xff\x8c\xff\x8b\xff\x8a\xff\x89\xff\x88\xff\x87\xff\x86\xff\x85\xff\x84\xff\x83\xff\x82\xff\x81\xff\x80\xff\x7f\xff\x7e\xff\x7d\xff\x7c\xff\x7b\xff\x7a\xff\x79\xff\x78\xff\x77\xff\x76\xff\x75\xff\x74\xff\x73\xff\x72\xff\x71\xff\x70\xff\x6f\xff\x6e\xff\x6d\xff\x6c\xff\x6b\xff\x6a\xff\x69\xff\x68\xff\x67\xff\x66\xff\x65\xff\x64\xff\x63\xff\x62\xff\x61\xff\x60\xff\x5f\xff\x5e\xff\x5d\xff\x5c\xff\x5b\xff\x5a\xff\x59\xff\x58\xff\x57\xff\x56\xff\x55\xff\x54\xff\x53\xff\x52\xff\x51\xff\x50\xff\x4f\xff\x4e\xff\x4d\xff\x4c\xff\x4b\xff\x4a\xff\x49\xff\x48\xff\x47\xff\x46\xff\x45\xff\x6e\xfe\x6e\xfe\x6e\xfe\x00\x00\x00\x00\x68\xfe\x00\x00\x00\x00\x00\x00\xb3\xfe\x00\x00\xb5\xfe\xbe\xfe\xbd\xfe\x00\x00\x00\x00\x5e\xfe\xc6\xfe\x00\x00\xf9\xff\xf8\xff\xf7\xff\xf6\xff\x00\x00\x00\x00\x00\x00\x00\x00\xa8\xfe\x5d\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x64\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6e\xfe\x5c\xfe\x89\xfe\x00\x00\x5a\xfe\x58\xfe\x00\x00\x62\xfe\x00\x00\x62\xfe\x00\x00\x00\x00\x7d\xfe\x7e\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x96\xfe\x97\xfe\x62\xfe\xa6\xfe\x5a\xfe\x00\x00\x6e\xfe\x6e\xfe\x6e\xfe\x62\xfe\x60\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x76\xfe\xbc\xfe\x00\x00\x00\x00\x5a\xfe\xb7\xfe\xb0\xfe\x00\x00\x00\x00\xb2\xfe\x00\x00\xb4\xfe\x69\xfe\xb6\xfe\x00\x00\x3e\xff\x00\x00\x00\x00\x00\x00\xc0\xff\xee\xff\xed\xff\xc1\xff\xf0\xff\xef\xff\xc2\xff\xf1\xff\xc3\xff\xf3\xff\xc8\xff\x70\xfe\x6b\xfe\xc9\xff\x70\xfe\xca\xff\x70\xfe\xcb\xff\xcc\xff\xcd\xff\x70\xfe\xce\xff\xcf\xff\xd0\xff\xd1\xff\xd2\xff\xd3\xff\xd4\xff\xd5\xff\xd6\xff\xd7\xff\xd8\xff\xd9\xff\xda\xff\xdb\xff\xdc\xff\xdd\xff\xde\xff\xdf\xff\xe0\xff\xe1\xff\xe2\xff\xe3\xff\x28\xff\x00\x00\xe6\xff\x66\xfe\xe8\xff\xe9\xff\xea\xff\x5e\xfe\xdd\xfe\xdb\xfe\xd9\xfe\xd7\xfe\xd2\xfe\xcd\xfe\x56\xfe\x56\xfe\x00\x00\x00\x00\x00\x00\x56\xfe\x00\x00\xde\xfe\x00\x00\x00\x00\x72\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x67\xfe\x13\xff\x10\xff\x0c\xff\x08\xff\x56\xfe\x56\xfe\x00\x00\x2c\xff\x71\xfe\x2f\xff\x2e\xff\x2d\xff\x5e\xfe\x27\xff\x00\x00\x6e\xfe\x5e\xfe\x26\xff\x00\x00\x6e\xfe\x5e\xfe\x25\xff\x1a\xff\x00\x00\x6e\xfe\x6e\xfe\x3d\xff\x00\x00\x3c\xff\x60\xfe\x00\x00\x00\x00\x00\x00\xbb\xfe\x74\xfe\x00\x00\x00\x00\x5f\xfe\x2b\xff\x2a\xff\x00\x00\xc3\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x6e\xfe\x6e\xfe\x6e\xfe\x6e\xfe\x00\x00\x00\x00\x00\x00\x00\x00\xa9\xfe\x00\x00\x77\xfe\x00\x00\x78\xfe\x00\x00\x00\x00\x00\x00\x05\xff\x00\x00\xf1\xfe\x00\x00\x00\x00\x7a\xfe\x7b\xfe\x7c\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\xfe\x85\xfe\x00\x00\x87\xfe\x00\x00\x90\xfe\x00\x00\x73\xfe\x00\x00\x8a\xfe\x8c\xfe\x59\xfe\x8b\xfe\x88\xfe\x86\xfe\x83\xfe\x82\xfe\x81\xfe\x80\xfe\x7f\xfe\x06\xff\xa4\xfe\x62\xfe\xf0\xfe\xee\xfe\xea\xfe\x56\xfe\x56\xfe\x00\x00\x5e\xfe\x04\xff\x00\x00\x01\xff\x5e\xfe\x03\xff\x00\x00\xfc\xfe\x00\x00\x63\xfe\xa7\xfe\x61\xfe\xa5\xfe\xad\xfe\xac\xfe\xab\xfe\xaa\xfe\x00\x00\x00\x00\x00\x00\x43\xff\xe1\xfe\x5e\xfe\x00\x00\x00\x00\x07\xff\x00\x00\x00\x00\x5b\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x3b\xff\x38\xff\x56\xfe\x56\xfe\x15\xff\x5e\xfe\x18\xff\x5e\xfe\x00\x00\x00\x00\x1f\xff\x1d\xff\x5e\xfe\x00\x00\x00\x00\x24\xff\x22\xff\x5e\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\xfe\x00\x00\x00\x00\x00\x00\x5e\xfe\xc9\xfe\x00\x00\xcc\xfe\xdc\xfe\x43\xff\xd8\xfe\x00\x00\xd6\xfe\x5e\xfe\xce\xfe\x00\x00\xd1\xfe\x00\x00\xd4\xfe\x0e\xff\x0a\xff\x0e\xff\x6e\xfe\x00\x00\x00\x00\x6e\xfe\x00\x00\x00\x00\x19\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xae\xfe\x00\x00\xb8\xfe\xba\xfe\x00\x00\xc0\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc5\xfe\x00\x00\x00\x00\x00\x00\x02\xff\xf6\xfe\x00\x00\x5e\xfe\x5e\xfe\xfb\xfe\x00\x00\x00\x00\x5e\xfe\x00\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe6\xfe\x00\x00\x00\x00\x00\x00\xff\xfe\x00\x00\x00\x00\xfa\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe2\xfe\xe3\xfe\xe4\xfe\x44\xff\x41\xff\x33\xff\x56\xfe\x56\xfe\x00\x00\xe5\xfe\xc1\xfe\x00\x00\x00\x00\x00\x00\xb1\xfe\x00\x00\x00\x00\x00\x00\x6e\xfe\x16\xff\x5e\xfe\x6e\xfe\x5e\xfe\x1e\xff\x6e\xfe\x5e\xfe\x23\xff\x11\xff\x00\x00\x09\xff\x00\x00\x0d\xff\xd3\xfe\xd0\xfe\x00\x00\xd5\xfe\x00\x00\xca\xfe\x00\x00\xc8\xfe\xcb\xfe\xda\xfe\xcf\xfe\x0b\xff\x0f\xff\x00\x00\x20\xff\x00\x00\x1b\xff\x00\x00\x14\xff\x35\xff\x00\x00\x37\xff\x00\x00\x3a\xff\xaf\xfe\xb9\xfe\xbf\xfe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf4\xfe\x00\x00\x00\x00\xf8\xfe\x5e\xfe\xfd\xfe\x5e\xfe\xef\xfe\x00\x00\xec\xfe\xe7\xfe\x00\x00\xe8\xfe\xeb\xfe\xe9\xfe\xed\xfe\x00\x00\x00\x00\xf5\xfe\x00\x00\xf3\xfe\x00\x00\xc4\xfe\x34\xff\x32\xff\x00\x00\x30\xff\x3f\xff\x39\xff\x36\xff\x17\xff\x6e\xfe\x6e\xfe\x21\xff\x1c\xff\x42\xff\x00\x00\x31\xff\xf7\xfe\x5e\xfe\xf9\xfe\xfe\xfe\x00\x00\x40\xff\x00\x00\xf2\xfe"# happyCheck :: HappyAddr happyCheck = HappyA# "\xff\xff\x03\x00\x01\x00\x01\x00\x16\x00\x02\x00\x02\x00\x02\x00\x16\x00\x02\x00\x0c\x00\x02\x00\x0b\x00\x04\x00\x02\x00\x06\x00\x0a\x00\x06\x00\x16\x00\x02\x00\x17\x00\x04\x00\x02\x00\x06\x00\x04\x00\x02\x00\x06\x00\x01\x00\x03\x00\x02\x00\x02\x00\x02\x00\x02\x00\x19\x00\x03\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x0c\x00\x16\x00\x03\x00\x02\x00\x02\x00\x02\x00\x19\x00\x03\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x0c\x00\xdc\x00\x03\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x0c\x00\xde\x00\x03\x00\xdd\x00\x4b\x00\x6c\x00\x03\x00\x03\x00\x6c\x00\x16\x00\xde\x00\x0c\x00\x01\x00\x06\x00\x06\x00\x0a\x00\x6c\x00\x03\x00\x60\x00\x7a\x00\x16\x00\x6b\x00\x7a\x00\x17\x00\x03\x00\x6b\x00\x68\x00\x73\x00\xd7\x00\x17\x00\x7a\x00\x73\x00\x17\x00\xbf\x00\xc0\x00\x79\x00\x6f\x00\xc3\x00\x6d\x00\x79\x00\x76\x00\x73\x00\x73\x00\xdc\x00\x6f\x00\x6f\x00\x6f\x00\x2a\x00\x6f\x00\x2c\x00\x7d\x00\x0a\x00\x7b\x00\x73\x00\x17\x00\x71\x00\x75\x00\x74\x00\x7d\x00\x7d\x00\x7d\x00\x72\x00\x7d\x00\x18\x00\x72\x00\x17\x00\x71\x00\x73\x00\x1b\x00\x73\x00\x71\x00\x71\x00\x71\x00\x71\x00\x47\x00\x47\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x46\x00\x4e\x00\x4e\x00\x71\x00\x71\x00\x71\x00\x18\x00\x46\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x3b\x00\x18\x00\x73\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x18\x00\x18\x00\x73\x00\x19\x00\x73\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\x73\x00\xc2\x00\xc3\x00\x73\x00\xc5\x00\xc6\x00\xbf\x00\xc0\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xbc\x00\xbd\x00\xbe\x00\x73\x00\xd8\x00\xd8\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\x73\x00\xc2\x00\xc3\x00\x73\x00\xc5\x00\xc6\x00\xbc\x00\xbd\x00\xbe\x00\xca\x00\xcb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\x6c\x00\xc2\x00\xc3\x00\x01\x00\xc5\x00\xc6\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\x73\x00\xc2\x00\xc3\x00\x7a\x00\xc5\x00\xc6\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\x73\x00\xc2\x00\xc3\x00\x01\x00\xc5\x00\x04\x00\x05\x00\x11\x00\x01\x00\x13\x00\x73\x00\x73\x00\x73\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x04\x00\x05\x00\xd7\x00\xd8\x00\xd8\x00\xd9\x00\xbf\x00\xc0\x00\xc1\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x02\x00\x05\x00\x04\x00\x02\x00\x06\x00\x04\x00\xd7\x00\x06\x00\xc1\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x0c\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\xc1\x00\x14\x00\x15\x00\xdc\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\x01\x00\x01\x00\x04\x00\x05\x00\xd8\x00\xd9\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0c\x00\xd7\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\xba\x00\x01\x00\x06\x00\x07\x00\x08\x00\x09\x00\x06\x00\x07\x00\x08\x00\x09\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\xba\x00\x01\x00\x02\x00\x01\x00\x06\x00\x07\x00\x08\x00\x09\x00\x06\x00\x07\x00\x08\x00\x09\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x02\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\x01\x00\xbf\x00\xc0\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x02\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\xca\x00\xcb\x00\xc7\x00\xc8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x02\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\x01\x00\x02\x00\xd7\x00\xd8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x02\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\x01\x00\x02\x00\xd7\x00\xd8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x02\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\x04\x00\x05\x00\xd7\x00\xd8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\xd7\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\xb9\x00\xba\x00\x01\x00\xc4\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x02\x00\x02\x00\x04\x00\x04\x00\x06\x00\x06\x00\x02\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x04\x00\x05\x00\xbb\x00\x02\x00\x01\x00\x04\x00\x02\x00\x06\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x04\x00\x05\x00\x01\x00\x02\x00\xb9\x00\xba\x00\x01\x00\x02\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x04\x00\x05\x00\x01\x00\x02\x00\x01\x00\x02\x00\xd7\x00\xd8\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x04\x00\x05\x00\x01\x00\x02\x00\x01\x00\x02\x00\xb9\x00\xba\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x01\x00\x05\x00\x01\x00\x02\x00\x04\x00\x05\x00\x01\x00\x02\x00\xc1\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x04\x00\x05\x00\x5e\x00\x5f\x00\x00\x00\x01\x00\xdc\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x00\x00\x01\x00\x00\x00\x01\x00\x00\x00\x01\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x00\x00\x01\x00\x00\x00\x01\x00\x00\x00\x01\x00\xdd\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x00\x00\x01\x00\x00\x00\x01\x00\x00\x00\x01\x00\x01\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x00\x00\x01\x00\x00\x00\x01\x00\x00\x00\x01\x00\xda\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x05\x00\x00\x00\x01\x00\x00\x00\x01\x00\x14\x00\x15\x00\xd8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xd8\x00\xd7\x00\xbb\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\x18\x00\x18\x00\x0a\x00\x19\x00\x06\x00\x0a\x00\xd8\x00\x0a\x00\x4b\x00\x0a\x00\x0e\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x6e\x00\x0a\x00\x69\x00\x02\x00\x0a\x00\x1b\x00\x03\x00\x1b\x00\x0a\x00\x1b\x00\x1b\x00\x06\x00\x1b\x00\x1c\x00\x7c\x00\x2a\x00\x77\x00\x06\x00\x2a\x00\x0b\x00\x1d\x00\x01\x00\x21\x00\x6d\x00\x02\x00\x1b\x00\x2a\x00\x0e\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2e\x00\x2a\x00\x39\x00\x3a\x00\x2a\x00\x7b\x00\x06\x00\x37\x00\x01\x00\x3b\x00\x06\x00\x2d\x00\x44\x00\x43\x00\x45\x00\x43\x00\x41\x00\x06\x00\x49\x00\x40\x00\x0e\x00\x42\x00\x42\x00\x44\x00\x44\x00\x4e\x00\x51\x00\x50\x00\x57\x00\x02\x00\x55\x00\x56\x00\xdd\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x39\x00\x3a\x00\x73\x00\x73\x00\x73\x00\x62\x00\x63\x00\x64\x00\x65\x00\xdc\x00\x67\x00\x57\x00\x45\x00\x4e\x00\x4f\x00\x50\x00\x49\x00\x52\x00\x0e\x00\x4e\x00\x4f\x00\x50\x00\xd7\x00\x52\x00\x51\x00\x39\x00\x3a\x00\x02\x00\x55\x00\x56\x00\x4b\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x4a\x00\x45\x00\x0a\x00\x4d\x00\x4e\x00\x49\x00\x63\x00\x64\x00\x4e\x00\x66\x00\x50\x00\x4a\x00\x02\x00\x51\x00\x4d\x00\x4e\x00\x0a\x00\x55\x00\x56\x00\x0e\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x39\x00\x3a\x00\x02\x00\x6d\x00\x0a\x00\x60\x00\x63\x00\x0a\x00\x0a\x00\x2a\x00\xdc\x00\x0a\x00\x45\x00\x68\x00\x02\x00\x02\x00\x49\x00\x7b\x00\x33\x00\x0e\x00\x35\x00\x28\x00\x37\x00\x2a\x00\x51\x00\x1f\x00\x0a\x00\x76\x00\x55\x00\x56\x00\x02\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x2a\x00\x39\x00\x3a\x00\x2a\x00\x2a\x00\x69\x00\x63\x00\x2a\x00\x0e\x00\x2f\x00\x30\x00\xd7\x00\xdb\x00\x45\x00\x0a\x00\x0a\x00\x02\x00\x49\x00\x35\x00\x77\x00\x37\x00\x02\x00\x2a\x00\x0a\x00\x02\x00\x51\x00\x39\x00\x3a\x00\x30\x00\x55\x00\x56\x00\x69\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\xc2\x00\x45\x00\x02\x00\x1b\x00\x0a\x00\x49\x00\x63\x00\x02\x00\x77\x00\x2a\x00\x2a\x00\xdc\x00\xdc\x00\x51\x00\x39\x00\x3a\x00\x30\x00\x55\x00\x56\x00\x2b\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x0a\x00\x45\x00\x3c\x00\x3d\x00\x3e\x00\x49\x00\x40\x00\x26\x00\x42\x00\x28\x00\x44\x00\x2a\x00\xd7\x00\x51\x00\x0a\x00\x69\x00\x0a\x00\x55\x00\x56\x00\x0a\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x6a\x00\x24\x00\x6b\x00\x26\x00\x77\x00\x28\x00\x1b\x00\x2a\x00\x1b\x00\x1e\x00\x1a\x00\x1b\x00\x6f\x00\x20\x00\x78\x00\x22\x00\x79\x00\x6f\x00\x6b\x00\x6b\x00\x6b\x00\x6a\x00\xdc\x00\xd7\x00\x69\x00\x29\x00\x7d\x00\x6f\x00\x6b\x00\x6b\x00\x6b\x00\x7d\x00\x79\x00\x79\x00\x79\x00\x78\x00\x6f\x00\x6b\x00\x77\x00\x6f\x00\x6b\x00\x7d\x00\x79\x00\x79\x00\x79\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x7d\x00\x79\x00\x6b\x00\x7d\x00\x79\x00\x6b\x00\x6b\x00\x6f\x00\x6b\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x6b\x00\x6b\x00\x79\x00\x6b\x00\x6b\x00\x79\x00\x79\x00\x7d\x00\x79\x00\x02\x00\x02\x00\xdc\x00\x02\x00\x02\x00\x79\x00\x79\x00\x02\x00\x79\x00\x79\x00\x02\x00\xd7\x00\x02\x00\xdc\x00\x02\x00\xdc\x00\x02\x00\xdc\x00\x02\x00\xdc\x00\x02\x00\x02\x00\xd7\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x01\x00\x01\x00\xdc\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\xd8\x00\x01\x00\xd7\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\xba\x00\x02\x00\x01\x00\x01\x00\xba\x00\x01\x00\x01\x00\xd8\x00\x02\x00\xba\x00\xd7\x00\x02\x00\x02\x00\xba\x00\x02\x00\xd7\x00\xba\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x0a\x00\x01\x00\xba\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x01\x00\xd7\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\x02\x00\xd7\x00\xba\x00\x02\x00\x05\x00\x02\x00\x02\x00\x02\x00\x01\x00\xb9\x00\x02\x00\x02\x00\x02\x00\x01\x00\xd7\x00\x02\x00\x01\x00\x00\x00\x02\x00\x05\x00\x70\x00\x61\x00\x53\x00\x00\x00\x00\x00\x23\x00\x0f\x00\x07\x00\x09\x00\x08\x00\x00\x00\x00\x00\x5e\x00\x48\x00\x00\x00\x4f\x00\x4c\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x0b\x00\x5d\x00\x03\x00\x03\x00\x03\x00\x03\x00\x00\x00\x32\x00\x03\x00\xff\xff\x03\x00\x03\x00\x03\x00\x03\x00\x0b\x00\x38\x00\x22\x00\x03\x00\x03\x00\x03\x00\xff\xff\x64\x00\xff\xff\x64\x00\xff\xff\x29\x00\x03\x00\xff\xff\x22\x00\x25\x00\x25\x00\xff\xff\x64\x00\x64\x00\x10\x00\x12\x00\xff\xff\x10\x00\x13\x00\x0d\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\x15\x00\xff\xff\xff\xff\x3f\x00\x3f\x00\xff\xff\xff\xff\xff\xff\x3f\x00\x22\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x34\x00\xff\xff\x34\x00\x36\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"# happyTable :: HappyAddr happyTable = HappyA# "\x00\x00\x1a\x00\x0a\x01\x0f\x01\x8b\x01\xb2\x01\xab\x01\x7e\x02\x8a\x01\xec\x02\x1b\x00\x3e\x00\x0b\x01\x98\x01\x49\x00\x40\x00\x54\x01\x63\x01\x87\x01\x3e\x00\x89\x01\x43\x00\x3e\x00\x40\x00\x43\x00\x49\x00\x40\x00\x0a\x00\x4e\x01\x49\x00\x49\x00\x49\x00\x49\x00\x8e\x01\x1a\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x1b\x00\x86\x01\xe5\x01\x49\x00\x49\x00\x49\x00\x8c\x01\x1a\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x1b\x00\x05\x00\x1a\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x1b\x00\xff\xff\x1a\x00\x27\x00\x09\x02\x4f\x00\x0f\x01\x0f\x01\x3c\x00\x7c\x01\xff\xff\x1b\x00\x26\x00\x04\x01\x04\x01\x43\x01\x2d\x01\x8d\x02\x05\x00\x3d\x00\x79\x01\xa9\x01\x3d\x00\x88\x01\x8d\x02\x56\x01\x06\x00\x7a\x01\x42\x00\x85\x01\x3d\x00\x7a\x01\x84\x01\x5a\x01\x5b\x01\x57\x01\xb1\x01\x5c\x01\xd7\x01\x57\x01\x07\x00\x7a\x01\x78\x01\x05\x00\xb3\x01\xac\x01\x7f\x02\x99\x02\xed\x02\x9a\x02\xad\x01\x51\x00\xd8\x01\x7e\x01\x7b\x01\x4e\x00\x99\x01\x64\x01\xad\x01\xad\x01\xad\x01\x45\x00\xad\x01\x8f\x01\x44\x00\x77\x01\x4d\x00\x7a\x01\x52\x00\x7e\x01\x4c\x00\x4b\x00\x4a\x00\x2c\x01\x10\x01\x86\x02\x2a\x01\x29\x01\x20\x01\x1f\x01\x1e\x01\x69\x01\x68\x01\x67\x01\x8e\x02\x8c\x02\xbb\x02\x31\x01\xf3\x01\xf2\x01\x8d\x01\xba\x02\xf1\x01\x4e\x02\x49\x02\x44\x02\x43\x02\x32\x02\x31\x02\x30\x02\x53\x00\x83\x01\x7a\x01\x2f\x02\xc9\x02\xc6\x02\xe1\x02\xdf\x02\xdd\x02\x12\x03\x11\x03\x82\x01\x81\x01\x7a\x01\x80\x01\x78\x01\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x78\x01\x21\x00\x22\x00\x78\x01\x23\x00\x2e\x00\x55\x01\x56\x01\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\x4f\x01\x50\x01\x51\x01\x78\x01\x43\x00\x43\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x75\x01\x21\x00\x22\x00\x78\x01\x23\x00\x2e\x00\xe6\x01\xe7\x01\xe8\x01\x30\x00\x31\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x2e\x01\x21\x00\x22\x00\x29\x01\x23\x00\x24\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x75\x01\x21\x00\x22\x00\x3d\x00\x23\x00\x2e\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x75\x01\x21\x00\x22\x00\x28\x01\x23\x00\xa4\x01\xa5\x01\x3f\x02\x27\x01\x40\x02\x75\x01\x75\x01\x7e\x01\xa6\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\xa4\x01\xa5\x01\x42\x00\x43\x00\x6f\x01\x70\x01\xa7\x01\xa8\x01\xa9\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x3e\x00\xa5\x01\x3f\x00\x3e\x00\x40\x00\x9b\x01\x42\x00\x40\x00\xa9\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\xce\x01\xb2\x02\x3e\x00\x3e\x00\x9a\x01\x97\x01\x40\x00\x40\x00\xa9\x01\xb3\x02\xb4\x02\x05\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\xcf\x01\xd0\x01\xc9\x01\x12\x01\xb6\x02\xb7\x02\x6c\x01\x6d\x01\x13\x01\x14\x01\x15\x01\x16\x01\xb8\x02\x42\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\xc5\x01\xca\x01\x90\x02\x13\x01\x14\x01\x15\x01\x16\x01\x13\x01\x14\x01\x15\x01\x16\x01\x26\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x12\x01\xc6\x01\x55\x00\x56\x00\x90\x02\x13\x01\x14\x01\x15\x01\x16\x01\x13\x01\x14\x01\x15\x01\x16\x01\x25\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x25\x02\x26\x02\x3e\x00\x3e\x00\x94\x01\x93\x01\x40\x00\x40\x00\x24\x01\x5f\x01\x60\x01\x23\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x21\x02\x22\x02\x3e\x00\x3e\x00\x92\x01\x91\x01\x40\x00\x40\x00\x30\x00\x31\x00\x30\x01\x31\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x6d\x02\x6e\x02\x3e\x00\x3e\x00\x90\x01\xeb\x01\x40\x00\x40\x00\xf6\x01\xf7\x01\x42\x00\x43\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x55\x00\x56\x00\x3e\x00\x3e\x00\xea\x01\xe9\x01\x40\x00\x40\x00\xd2\x01\xd3\x01\x42\x00\x43\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x64\x02\x65\x02\x3e\x00\x3e\x00\xe8\x01\xb5\x01\x40\x00\x40\x00\x42\x02\x43\x02\x42\x00\x43\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\xdf\x01\x42\x00\x3e\x00\x3e\x00\xb0\x01\x53\x02\x40\x00\x40\x00\xcf\x01\xd0\x01\x22\x01\x4b\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x01\x01\x01\x02\x01\x94\x02\x3e\x00\x3e\x00\x29\x02\x9d\x02\x40\x00\x40\x00\x1e\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\xbb\x01\xbc\x01\x95\x02\x3e\x00\x1d\x01\xea\x02\x1b\x01\x40\x00\xbd\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x1c\x02\x1d\x02\x69\x02\x6a\x02\xcf\x01\xd0\x01\xf9\x02\xfa\x02\x1e\x02\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\xbb\x01\xbc\x01\xfc\x02\xfd\x02\xf9\x02\xfa\x02\x42\x00\x43\x00\x1a\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x1c\x02\x1d\x02\xd2\x01\xd3\x01\xe4\x02\xe5\x02\xcf\x01\xd0\x01\x19\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x18\x01\x52\x02\xd2\x01\xd3\x01\xb6\x02\xb7\x02\x04\x03\x05\x03\xa9\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x4d\x02\xb6\x02\xb7\x02\x0a\x00\x0b\x00\x46\x00\x48\x00\x05\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x48\x02\x46\x00\x47\x00\x46\x00\x16\x01\x46\x00\xe1\x01\x04\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x9c\x02\x46\x00\xe0\x01\x46\x00\xda\x01\x46\x00\xd9\x01\x51\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x98\x02\x46\x00\xd5\x01\x46\x00\xd4\x01\x46\x00\xaf\x01\x97\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\xbc\x01\x46\x00\xae\x01\x46\x00\x5b\x02\x46\x00\x3c\x02\x77\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x1d\x02\x46\x00\x38\x02\x46\x00\x35\x02\x1b\x03\xb4\x02\x74\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x72\x01\x42\x00\x95\x02\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x47\x01\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\x7f\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x48\x01\x49\x01\x4a\x01\x7f\x01\x74\x01\x43\x01\x7d\x01\x04\x01\x43\x01\x43\x00\x51\x00\xf7\x01\x51\x00\x0c\x00\x51\x00\x51\x00\x43\x01\x51\x00\x43\x01\x43\x01\x43\x01\x43\x01\x07\x02\x43\x01\x05\x02\x67\x01\x43\x01\x61\x02\x66\x01\x61\x02\x51\x00\x52\x00\x6a\x02\x04\x01\xc2\x01\xc3\x01\x08\x02\x44\x01\xf0\x01\x04\x01\x9c\x01\x0b\x01\x4f\x02\x62\x01\x45\x02\xd7\x01\x61\x01\x22\x02\x17\x02\x0c\x00\x95\x02\x9c\x01\x9c\x01\x46\x02\x96\x02\x50\x02\x0d\x00\x0e\x00\x44\x01\xd8\x01\x04\x01\xfe\x02\x52\x01\x65\x02\x04\x01\x23\x02\xd4\x02\x62\x02\x0f\x00\xd6\x02\x6b\x02\x04\x01\x10\x00\xd2\x02\x0c\x00\xa1\x01\xd0\x02\xa2\x01\xa2\x01\x05\x01\x11\x00\x8b\x02\x4b\x01\x5d\x01\x12\x00\x13\x00\x42\x01\x14\x00\x15\x00\x16\x00\x17\x00\x27\x00\x0d\x00\x0e\x00\x75\x01\x75\x01\x7e\x01\x28\x00\x29\x00\x2a\x00\x2b\x00\x05\x00\x2c\x00\x45\x01\x0f\x00\x05\x01\x06\x01\x07\x01\x10\x00\x08\x01\x0c\x00\x05\x01\x06\x01\x07\x01\x42\x00\x81\x02\x11\x00\x0d\x00\x0e\x00\x0b\x02\x12\x00\x13\x00\xd6\x01\x14\x00\x15\x00\x16\x00\x17\x00\x27\x00\x0b\x01\x0f\x00\x43\x01\x0c\x01\x0d\x01\x10\x00\x37\x01\x38\x01\x05\x01\x39\x01\xbc\x02\x84\x02\x07\x02\x11\x00\x0c\x01\x0d\x01\x43\x01\x12\x00\x13\x00\x0c\x00\x14\x00\x15\x00\x16\x00\x17\x00\x27\x00\x0d\x00\x0e\x00\x05\x02\xd7\x01\x43\x01\x3e\x01\x3c\x01\x43\x01\x43\x01\x17\x02\x05\x00\x43\x01\x0f\x00\x06\x00\x03\x02\x02\x02\x10\x00\xd8\x01\x18\x02\x0c\x00\x19\x02\xda\x02\x1a\x02\xb9\x01\x11\x00\x4a\x02\x43\x01\x07\x00\x12\x00\x13\x00\xfc\x01\x14\x00\x15\x00\x16\x00\x17\x00\x27\x00\x4b\x02\x0d\x00\x0e\x00\x37\x02\x90\x02\x03\x02\x3b\x01\x17\x02\x0c\x00\x91\x02\x92\x02\x42\x00\xbf\x01\x0f\x00\x43\x01\x43\x01\xfb\x01\x10\x00\xff\x02\xf0\x01\x1a\x02\xfa\x01\x90\x02\x51\x00\xed\x01\x11\x00\x0d\x00\x0e\x00\xf0\x02\x12\x00\x13\x00\xf8\x01\x14\x00\x15\x00\x16\x00\x17\x00\x27\x00\xd4\x01\x0f\x00\xe0\x01\x1e\x02\x43\x01\x10\x00\x3a\x01\xab\x01\xf0\x01\x9c\x01\x90\x02\x05\x00\x05\x00\x11\x00\x0d\x00\x0e\x00\x16\x03\x12\x00\x13\x00\x1f\x02\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x43\x01\x0f\x00\x9d\x01\x9e\x01\x9f\x01\x10\x00\xa0\x01\xdb\x02\xa1\x01\xb8\x01\xa2\x01\xb9\x01\x42\x00\x11\x00\x51\x00\xef\x01\x51\x00\x12\x00\x13\x00\x51\x00\x14\x00\x15\x00\x16\x00\x17\x00\x42\x01\xed\x01\xb6\x01\xb4\x01\xb7\x01\xf0\x01\xb8\x01\xc6\x01\xb9\x01\xca\x01\xc7\x01\xdb\x01\xdc\x01\x55\x02\xcb\x01\xee\x01\xcc\x01\x57\x01\x54\x02\x52\x02\x4d\x02\x48\x02\x3e\x02\x05\x00\x42\x00\xa0\x02\xdd\x01\xad\x01\x9f\x02\x9c\x02\x98\x02\x88\x02\xad\x01\x57\x01\x57\x01\x57\x01\xee\x01\x9e\x02\x7c\x02\xf0\x01\x7d\x02\x7b\x02\xad\x01\x57\x01\x57\x01\x57\x01\x78\x02\x75\x02\xd5\x02\xd1\x02\xab\x02\xad\x01\x57\x01\xaa\x02\xad\x01\x57\x01\xa7\x02\xe0\x02\xeb\x02\xde\x02\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\xdc\x02\x01\x03\x57\x01\x00\x03\x1a\x03\x57\x01\x57\x01\xad\x01\x57\x01\x5f\x02\x5d\x02\x05\x00\x5b\x02\x5a\x02\x57\x01\x57\x01\x58\x02\x57\x01\x57\x01\x57\x02\x42\x00\x3e\x02\x05\x00\x3c\x02\x3b\x02\x3a\x02\x05\x00\x37\x02\x05\x00\x35\x02\x34\x02\x42\x00\x2f\x02\x2e\x02\x2d\x02\x2c\x02\x2b\x02\x29\x02\xdf\x01\x27\x02\x05\x00\x17\x02\x16\x02\x15\x02\x14\x02\x13\x02\x12\x02\x11\x02\x10\x02\x0f\x02\x0e\x02\x0c\x02\x43\x00\x8b\x02\x42\x00\x88\x02\x86\x02\x84\x02\x83\x02\x81\x02\x73\x02\x72\x02\x71\x02\x6f\x02\x67\x02\x77\x02\x61\x02\x8b\x02\xcc\x02\x74\x02\xce\x02\xcc\x02\x43\x00\xc9\x02\xc8\x02\x42\x00\xc6\x02\xc4\x02\xc5\x02\xc1\x02\x42\x00\xc2\x02\xbf\x02\xbe\x02\xba\x02\xb9\x02\xb2\x02\xb1\x02\xb0\x02\xaf\x02\xae\x02\x11\x03\xa9\x02\xa6\x02\xa5\x02\xa4\x02\xa3\x02\xa2\x02\xf7\x02\xf6\x02\xf5\x02\xf4\x02\xf3\x02\xf2\x02\xef\x02\x42\x00\xea\x02\xe9\x02\xe8\x02\xe6\x02\xda\x02\xd9\x02\xd8\x02\x42\x00\x10\x03\x0c\x03\x43\x02\x0b\x03\x09\x03\x07\x03\x06\x03\x18\x03\x1a\x03\x19\x03\x16\x03\x15\x03\x42\x00\x1d\x03\xef\x02\x2b\x01\x1e\x03\x72\x01\xc1\x01\x24\x00\x5d\x01\x40\x01\x3f\x01\x95\x01\x02\x01\x70\x01\x6a\x01\x6d\x01\x33\x01\x32\x01\x08\x00\x52\x01\x00\x02\x62\x01\x58\x01\x4c\x01\xff\x01\xfe\x01\xfd\x01\xfc\x01\xd0\x01\x89\x02\x1b\x01\xe2\x01\x5f\x02\x5d\x02\x58\x02\x0c\x02\xf4\x01\x7a\x02\x00\x00\x77\x02\x74\x02\xbf\x02\xac\x02\xd3\x02\xe3\x01\x79\x02\xa9\x02\xa6\x02\xef\x02\x00\x00\x3d\x01\x00\x00\x36\x01\x00\x00\x27\x02\x09\x03\x00\x00\xc2\x02\xce\x02\xca\x02\x00\x00\x35\x01\x34\x01\xe6\x02\xe2\x02\x00\x00\x0c\x03\x0d\x03\x13\x03\x00\x00\x00\x00\x00\x00\xcc\x02\x00\x00\x07\x03\x00\x00\x00\x00\x6f\x02\x67\x02\x00\x00\x00\x00\x00\x00\xcf\x02\x0e\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x02\x00\x00\xf7\x02\xfa\x02\x00\x00\x00\x00\x00\x00\x00\x00\x02\x03\x00\x00\x00\x00\x00\x00\xc0\x01\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\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# happyReduceArr = Happy_Data_Array.array (3, 425) [ (3 , happyReduce_3), (4 , happyReduce_4), (5 , happyReduce_5), (6 , happyReduce_6), (7 , happyReduce_7), (8 , happyReduce_8), (9 , happyReduce_9), (10 , happyReduce_10), (11 , happyReduce_11), (12 , happyReduce_12), (13 , happyReduce_13), (14 , happyReduce_14), (15 , happyReduce_15), (16 , happyReduce_16), (17 , happyReduce_17), (18 , happyReduce_18), (19 , happyReduce_19), (20 , happyReduce_20), (21 , happyReduce_21), (22 , happyReduce_22), (23 , happyReduce_23), (24 , happyReduce_24), (25 , happyReduce_25), (26 , happyReduce_26), (27 , happyReduce_27), (28 , happyReduce_28), (29 , happyReduce_29), (30 , happyReduce_30), (31 , happyReduce_31), (32 , happyReduce_32), (33 , happyReduce_33), (34 , happyReduce_34), (35 , happyReduce_35), (36 , happyReduce_36), (37 , happyReduce_37), (38 , happyReduce_38), (39 , happyReduce_39), (40 , happyReduce_40), (41 , happyReduce_41), (42 , happyReduce_42), (43 , happyReduce_43), (44 , happyReduce_44), (45 , happyReduce_45), (46 , happyReduce_46), (47 , happyReduce_47), (48 , happyReduce_48), (49 , happyReduce_49), (50 , happyReduce_50), (51 , happyReduce_51), (52 , happyReduce_52), (53 , happyReduce_53), (54 , happyReduce_54), (55 , happyReduce_55), (56 , happyReduce_56), (57 , happyReduce_57), (58 , happyReduce_58), (59 , happyReduce_59), (60 , happyReduce_60), (61 , happyReduce_61), (62 , happyReduce_62), (63 , happyReduce_63), (64 , happyReduce_64), (65 , happyReduce_65), (66 , happyReduce_66), (67 , happyReduce_67), (68 , happyReduce_68), (69 , happyReduce_69), (70 , happyReduce_70), (71 , happyReduce_71), (72 , happyReduce_72), (73 , happyReduce_73), (74 , happyReduce_74), (75 , happyReduce_75), (76 , happyReduce_76), (77 , happyReduce_77), (78 , happyReduce_78), (79 , happyReduce_79), (80 , happyReduce_80), (81 , happyReduce_81), (82 , happyReduce_82), (83 , happyReduce_83), (84 , happyReduce_84), (85 , happyReduce_85), (86 , happyReduce_86), (87 , happyReduce_87), (88 , happyReduce_88), (89 , happyReduce_89), (90 , happyReduce_90), (91 , happyReduce_91), (92 , happyReduce_92), (93 , happyReduce_93), (94 , happyReduce_94), (95 , happyReduce_95), (96 , happyReduce_96), (97 , happyReduce_97), (98 , happyReduce_98), (99 , happyReduce_99), (100 , happyReduce_100), (101 , happyReduce_101), (102 , happyReduce_102), (103 , happyReduce_103), (104 , happyReduce_104), (105 , happyReduce_105), (106 , happyReduce_106), (107 , happyReduce_107), (108 , happyReduce_108), (109 , happyReduce_109), (110 , happyReduce_110), (111 , happyReduce_111), (112 , happyReduce_112), (113 , happyReduce_113), (114 , happyReduce_114), (115 , happyReduce_115), (116 , happyReduce_116), (117 , happyReduce_117), (118 , happyReduce_118), (119 , happyReduce_119), (120 , happyReduce_120), (121 , happyReduce_121), (122 , happyReduce_122), (123 , happyReduce_123), (124 , happyReduce_124), (125 , happyReduce_125), (126 , happyReduce_126), (127 , happyReduce_127), (128 , happyReduce_128), (129 , happyReduce_129), (130 , happyReduce_130), (131 , happyReduce_131), (132 , happyReduce_132), (133 , happyReduce_133), (134 , happyReduce_134), (135 , happyReduce_135), (136 , happyReduce_136), (137 , happyReduce_137), (138 , happyReduce_138), (139 , happyReduce_139), (140 , happyReduce_140), (141 , happyReduce_141), (142 , happyReduce_142), (143 , happyReduce_143), (144 , happyReduce_144), (145 , happyReduce_145), (146 , happyReduce_146), (147 , happyReduce_147), (148 , happyReduce_148), (149 , happyReduce_149), (150 , happyReduce_150), (151 , happyReduce_151), (152 , happyReduce_152), (153 , happyReduce_153), (154 , happyReduce_154), (155 , happyReduce_155), (156 , happyReduce_156), (157 , happyReduce_157), (158 , happyReduce_158), (159 , happyReduce_159), (160 , happyReduce_160), (161 , happyReduce_161), (162 , happyReduce_162), (163 , happyReduce_163), (164 , happyReduce_164), (165 , happyReduce_165), (166 , happyReduce_166), (167 , happyReduce_167), (168 , happyReduce_168), (169 , happyReduce_169), (170 , happyReduce_170), (171 , happyReduce_171), (172 , happyReduce_172), (173 , happyReduce_173), (174 , happyReduce_174), (175 , happyReduce_175), (176 , happyReduce_176), (177 , happyReduce_177), (178 , happyReduce_178), (179 , happyReduce_179), (180 , happyReduce_180), (181 , happyReduce_181), (182 , happyReduce_182), (183 , happyReduce_183), (184 , happyReduce_184), (185 , happyReduce_185), (186 , happyReduce_186), (187 , happyReduce_187), (188 , happyReduce_188), (189 , happyReduce_189), (190 , happyReduce_190), (191 , happyReduce_191), (192 , happyReduce_192), (193 , happyReduce_193), (194 , happyReduce_194), (195 , happyReduce_195), (196 , happyReduce_196), (197 , happyReduce_197), (198 , happyReduce_198), (199 , happyReduce_199), (200 , happyReduce_200), (201 , happyReduce_201), (202 , happyReduce_202), (203 , happyReduce_203), (204 , happyReduce_204), (205 , happyReduce_205), (206 , happyReduce_206), (207 , happyReduce_207), (208 , happyReduce_208), (209 , happyReduce_209), (210 , happyReduce_210), (211 , happyReduce_211), (212 , happyReduce_212), (213 , happyReduce_213), (214 , happyReduce_214), (215 , happyReduce_215), (216 , happyReduce_216), (217 , happyReduce_217), (218 , happyReduce_218), (219 , happyReduce_219), (220 , happyReduce_220), (221 , happyReduce_221), (222 , happyReduce_222), (223 , happyReduce_223), (224 , happyReduce_224), (225 , happyReduce_225), (226 , happyReduce_226), (227 , happyReduce_227), (228 , happyReduce_228), (229 , happyReduce_229), (230 , happyReduce_230), (231 , happyReduce_231), (232 , happyReduce_232), (233 , happyReduce_233), (234 , happyReduce_234), (235 , happyReduce_235), (236 , happyReduce_236), (237 , happyReduce_237), (238 , happyReduce_238), (239 , happyReduce_239), (240 , happyReduce_240), (241 , happyReduce_241), (242 , happyReduce_242), (243 , happyReduce_243), (244 , happyReduce_244), (245 , happyReduce_245), (246 , happyReduce_246), (247 , happyReduce_247), (248 , happyReduce_248), (249 , happyReduce_249), (250 , happyReduce_250), (251 , happyReduce_251), (252 , happyReduce_252), (253 , happyReduce_253), (254 , happyReduce_254), (255 , happyReduce_255), (256 , happyReduce_256), (257 , happyReduce_257), (258 , happyReduce_258), (259 , happyReduce_259), (260 , happyReduce_260), (261 , happyReduce_261), (262 , happyReduce_262), (263 , happyReduce_263), (264 , happyReduce_264), (265 , happyReduce_265), (266 , happyReduce_266), (267 , happyReduce_267), (268 , happyReduce_268), (269 , happyReduce_269), (270 , happyReduce_270), (271 , happyReduce_271), (272 , happyReduce_272), (273 , happyReduce_273), (274 , happyReduce_274), (275 , happyReduce_275), (276 , happyReduce_276), (277 , happyReduce_277), (278 , happyReduce_278), (279 , happyReduce_279), (280 , happyReduce_280), (281 , happyReduce_281), (282 , happyReduce_282), (283 , happyReduce_283), (284 , happyReduce_284), (285 , happyReduce_285), (286 , happyReduce_286), (287 , happyReduce_287), (288 , happyReduce_288), (289 , happyReduce_289), (290 , happyReduce_290), (291 , happyReduce_291), (292 , happyReduce_292), (293 , happyReduce_293), (294 , happyReduce_294), (295 , happyReduce_295), (296 , happyReduce_296), (297 , happyReduce_297), (298 , happyReduce_298), (299 , happyReduce_299), (300 , happyReduce_300), (301 , happyReduce_301), (302 , happyReduce_302), (303 , happyReduce_303), (304 , happyReduce_304), (305 , happyReduce_305), (306 , happyReduce_306), (307 , happyReduce_307), (308 , happyReduce_308), (309 , happyReduce_309), (310 , happyReduce_310), (311 , happyReduce_311), (312 , happyReduce_312), (313 , happyReduce_313), (314 , happyReduce_314), (315 , happyReduce_315), (316 , happyReduce_316), (317 , happyReduce_317), (318 , happyReduce_318), (319 , happyReduce_319), (320 , happyReduce_320), (321 , happyReduce_321), (322 , happyReduce_322), (323 , happyReduce_323), (324 , happyReduce_324), (325 , happyReduce_325), (326 , happyReduce_326), (327 , happyReduce_327), (328 , happyReduce_328), (329 , happyReduce_329), (330 , happyReduce_330), (331 , happyReduce_331), (332 , happyReduce_332), (333 , happyReduce_333), (334 , happyReduce_334), (335 , happyReduce_335), (336 , happyReduce_336), (337 , happyReduce_337), (338 , happyReduce_338), (339 , happyReduce_339), (340 , happyReduce_340), (341 , happyReduce_341), (342 , happyReduce_342), (343 , happyReduce_343), (344 , happyReduce_344), (345 , happyReduce_345), (346 , happyReduce_346), (347 , happyReduce_347), (348 , happyReduce_348), (349 , happyReduce_349), (350 , happyReduce_350), (351 , happyReduce_351), (352 , happyReduce_352), (353 , happyReduce_353), (354 , happyReduce_354), (355 , happyReduce_355), (356 , happyReduce_356), (357 , happyReduce_357), (358 , happyReduce_358), (359 , happyReduce_359), (360 , happyReduce_360), (361 , happyReduce_361), (362 , happyReduce_362), (363 , happyReduce_363), (364 , happyReduce_364), (365 , happyReduce_365), (366 , happyReduce_366), (367 , happyReduce_367), (368 , happyReduce_368), (369 , happyReduce_369), (370 , happyReduce_370), (371 , happyReduce_371), (372 , happyReduce_372), (373 , happyReduce_373), (374 , happyReduce_374), (375 , happyReduce_375), (376 , happyReduce_376), (377 , happyReduce_377), (378 , happyReduce_378), (379 , happyReduce_379), (380 , happyReduce_380), (381 , happyReduce_381), (382 , happyReduce_382), (383 , happyReduce_383), (384 , happyReduce_384), (385 , happyReduce_385), (386 , happyReduce_386), (387 , happyReduce_387), (388 , happyReduce_388), (389 , happyReduce_389), (390 , happyReduce_390), (391 , happyReduce_391), (392 , happyReduce_392), (393 , happyReduce_393), (394 , happyReduce_394), (395 , happyReduce_395), (396 , happyReduce_396), (397 , happyReduce_397), (398 , happyReduce_398), (399 , happyReduce_399), (400 , happyReduce_400), (401 , happyReduce_401), (402 , happyReduce_402), (403 , happyReduce_403), (404 , happyReduce_404), (405 , happyReduce_405), (406 , happyReduce_406), (407 , happyReduce_407), (408 , happyReduce_408), (409 , happyReduce_409), (410 , happyReduce_410), (411 , happyReduce_411), (412 , happyReduce_412), (413 , happyReduce_413), (414 , happyReduce_414), (415 , happyReduce_415), (416 , happyReduce_416), (417 , happyReduce_417), (418 , happyReduce_418), (419 , happyReduce_419), (420 , happyReduce_420), (421 , happyReduce_421), (422 , happyReduce_422), (423 , happyReduce_423), (424 , happyReduce_424), (425 , happyReduce_425) ] happy_n_terms = 223 :: Int happy_n_nonterms = 126 :: Int #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_3 = happyMonadReduce 1# 0# happyReduction_3 happyReduction_3 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TStringLit happy_var_1)) -> ( case TLEncoding.decodeUtf8' happy_var_1 of Right t -> Right t Left err -> Left "invalid utf8 string")}) ) (\r -> happyReturn (happyIn6 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_4 = happySpecReduce_1 1# happyReduction_4 happyReduction_4 happy_x_1 = case happyOut6 happy_x_1 of { happy_var_1 -> happyIn7 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_5 = happySpecReduce_1 2# happyReduction_5 happyReduction_5 happy_x_1 = case happyOutTok happy_x_1 of { (Lexeme _ (TId happy_var_1)) -> happyIn8 (Ident (TLEncoding.decodeUtf8 happy_var_1) )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_6 = happySpecReduce_1 3# happyReduction_6 happyReduction_6 happy_x_1 = happyIn9 (I32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_7 = happySpecReduce_1 3# happyReduction_7 happyReduction_7 happy_x_1 = happyIn9 (I64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_8 = happySpecReduce_1 3# happyReduction_8 happyReduction_8 happy_x_1 = happyIn9 (F32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_9 = happySpecReduce_1 3# happyReduction_9 happyReduction_9 happy_x_1 = happyIn9 (F64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_10 = happySpecReduce_1 4# happyReduction_10 happyReduction_10 happy_x_1 = case happyOut12 happy_x_1 of { happy_var_1 -> happyIn10 (Index happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_11 = happySpecReduce_1 4# happyReduction_11 happyReduction_11 happy_x_1 = case happyOut8 happy_x_1 of { happy_var_1 -> happyIn10 (Named happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_12 = happyMonadReduce 1# 5# happyReduction_12 happyReduction_12 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TIntLit happy_var_1)) -> ( if happy_var_1 >= -(2^31) && happy_var_1 < 2^32 then Right happy_var_1 else Left ("Int literal value is out of signed int32 boundaries: " ++ show happy_var_1))}) ) (\r -> happyReturn (happyIn11 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_13 = happyMonadReduce 1# 6# happyReduction_13 happyReduction_13 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TIntLit happy_var_1)) -> ( if happy_var_1 >= 0 && happy_var_1 < 2^32 then Right (fromIntegral happy_var_1) else Left ("Int literal value is out of unsigned int32 boundaries: " ++ show happy_var_1))}) ) (\r -> happyReturn (happyIn12 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_14 = happyMonadReduce 1# 7# happyReduction_14 happyReduction_14 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TIntLit happy_var_1)) -> ( if happy_var_1 >= -(2^63) && happy_var_1 < 2^64 then Right happy_var_1 else Left ("Int literal value is out of signed int64 boundaries: " ++ show happy_var_1))}) ) (\r -> happyReturn (happyIn13 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_15 = happyMonadReduce 1# 8# happyReduction_15 happyReduction_15 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TIntLit happy_var_1)) -> ( let maxInt = 340282356779733623858607532500980858880 in if happy_var_1 <= maxInt && happy_var_1 >= -maxInt then return $ fromIntegral happy_var_1 else Left "constant out of range")}) ) (\r -> happyReturn (happyIn14 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_16 = happyMonadReduce 1# 8# happyReduction_16 happyReduction_16 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TFloatLit happy_var_1)) -> ( asFloat happy_var_1)}) ) (\r -> happyReturn (happyIn14 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_17 = happyMonadReduce 1# 9# happyReduction_17 happyReduction_17 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TIntLit happy_var_1)) -> ( let maxInt = round (maxFinite :: Double) in if happy_var_1 <= maxInt && happy_var_1 >= -maxInt then return $ fromIntegral happy_var_1 else Left "constant out of range")}) ) (\r -> happyReturn (happyIn15 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_18 = happyMonadReduce 1# 9# happyReduction_18 happyReduction_18 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOutTok happy_x_1 of { (Lexeme _ (TFloatLit happy_var_1)) -> ( asDouble happy_var_1)}) ) (\r -> happyReturn (happyIn15 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_19 = happySpecReduce_1 10# happyReduction_19 happyReduction_19 happy_x_1 = happyIn16 (Unreachable ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_20 = happySpecReduce_1 10# happyReduction_20 happyReduction_20 happy_x_1 = happyIn16 (Nop ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_21 = happySpecReduce_2 10# happyReduction_21 happyReduction_21 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (Br happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_22 = happySpecReduce_2 10# happyReduction_22 happyReduction_22 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (BrIf happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_23 = happySpecReduce_2 10# happyReduction_23 happyReduction_23 happy_x_2 happy_x_1 = case happyOut123 happy_x_2 of { happy_var_2 -> happyIn16 (BrTable (reverse $ tail happy_var_2) (head happy_var_2) )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_24 = happySpecReduce_1 10# happyReduction_24 happyReduction_24 happy_x_1 = happyIn16 (Return ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_25 = happySpecReduce_2 10# happyReduction_25 happyReduction_25 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (Call happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_26 = happySpecReduce_1 10# happyReduction_26 happyReduction_26 happy_x_1 = happyIn16 (Drop ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_27 = happySpecReduce_1 10# happyReduction_27 happyReduction_27 happy_x_1 = happyIn16 (Select ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_28 = happySpecReduce_2 10# happyReduction_28 happyReduction_28 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (GetLocal happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_29 = happySpecReduce_2 10# happyReduction_29 happyReduction_29 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (SetLocal happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_30 = happySpecReduce_2 10# happyReduction_30 happyReduction_30 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (TeeLocal happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_31 = happySpecReduce_2 10# happyReduction_31 happyReduction_31 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (GetGlobal happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_32 = happySpecReduce_2 10# happyReduction_32 happyReduction_32 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn16 (SetGlobal happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_33 = happySpecReduce_2 10# happyReduction_33 happyReduction_33 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (I32Load happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_34 = happySpecReduce_2 10# happyReduction_34 happyReduction_34 happy_x_2 happy_x_1 = case happyOut31 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_35 = happySpecReduce_2 10# happyReduction_35 happyReduction_35 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (F32Load happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_36 = happySpecReduce_2 10# happyReduction_36 happyReduction_36 happy_x_2 happy_x_1 = case happyOut31 happy_x_2 of { happy_var_2 -> happyIn16 (F64Load happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_37 = happySpecReduce_2 10# happyReduction_37 happyReduction_37 happy_x_2 happy_x_1 = case happyOut28 happy_x_2 of { happy_var_2 -> happyIn16 (I32Load8S happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_38 = happySpecReduce_2 10# happyReduction_38 happyReduction_38 happy_x_2 happy_x_1 = case happyOut28 happy_x_2 of { happy_var_2 -> happyIn16 (I32Load8U happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_39 = happySpecReduce_2 10# happyReduction_39 happyReduction_39 happy_x_2 happy_x_1 = case happyOut29 happy_x_2 of { happy_var_2 -> happyIn16 (I32Load16S happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_40 = happySpecReduce_2 10# happyReduction_40 happyReduction_40 happy_x_2 happy_x_1 = case happyOut29 happy_x_2 of { happy_var_2 -> happyIn16 (I32Load16U happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_41 = happySpecReduce_2 10# happyReduction_41 happyReduction_41 happy_x_2 happy_x_1 = case happyOut28 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load8S happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_42 = happySpecReduce_2 10# happyReduction_42 happyReduction_42 happy_x_2 happy_x_1 = case happyOut28 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load8U happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_43 = happySpecReduce_2 10# happyReduction_43 happyReduction_43 happy_x_2 happy_x_1 = case happyOut29 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load16S happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_44 = happySpecReduce_2 10# happyReduction_44 happyReduction_44 happy_x_2 happy_x_1 = case happyOut29 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load16U happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_45 = happySpecReduce_2 10# happyReduction_45 happyReduction_45 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load32S happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_46 = happySpecReduce_2 10# happyReduction_46 happyReduction_46 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (I64Load32U happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_47 = happySpecReduce_2 10# happyReduction_47 happyReduction_47 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (I32Store happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_48 = happySpecReduce_2 10# happyReduction_48 happyReduction_48 happy_x_2 happy_x_1 = case happyOut31 happy_x_2 of { happy_var_2 -> happyIn16 (I64Store happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_49 = happySpecReduce_2 10# happyReduction_49 happyReduction_49 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (F32Store happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_50 = happySpecReduce_2 10# happyReduction_50 happyReduction_50 happy_x_2 happy_x_1 = case happyOut31 happy_x_2 of { happy_var_2 -> happyIn16 (F64Store happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_51 = happySpecReduce_2 10# happyReduction_51 happyReduction_51 happy_x_2 happy_x_1 = case happyOut28 happy_x_2 of { happy_var_2 -> happyIn16 (I32Store8 happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_52 = happySpecReduce_2 10# happyReduction_52 happyReduction_52 happy_x_2 happy_x_1 = case happyOut29 happy_x_2 of { happy_var_2 -> happyIn16 (I32Store16 happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_53 = happySpecReduce_2 10# happyReduction_53 happyReduction_53 happy_x_2 happy_x_1 = case happyOut28 happy_x_2 of { happy_var_2 -> happyIn16 (I64Store8 happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_54 = happySpecReduce_2 10# happyReduction_54 happyReduction_54 happy_x_2 happy_x_1 = case happyOut29 happy_x_2 of { happy_var_2 -> happyIn16 (I64Store16 happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_55 = happySpecReduce_2 10# happyReduction_55 happyReduction_55 happy_x_2 happy_x_1 = case happyOut30 happy_x_2 of { happy_var_2 -> happyIn16 (I64Store32 happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_56 = happySpecReduce_1 10# happyReduction_56 happyReduction_56 happy_x_1 = happyIn16 (CurrentMemory ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_57 = happySpecReduce_1 10# happyReduction_57 happyReduction_57 happy_x_1 = happyIn16 (GrowMemory ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_58 = happySpecReduce_1 10# happyReduction_58 happyReduction_58 happy_x_1 = happyIn16 (CurrentMemory ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_59 = happySpecReduce_1 10# happyReduction_59 happyReduction_59 happy_x_1 = happyIn16 (GrowMemory ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_60 = happySpecReduce_2 10# happyReduction_60 happyReduction_60 happy_x_2 happy_x_1 = case happyOut11 happy_x_2 of { happy_var_2 -> happyIn16 (I32Const happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_61 = happySpecReduce_2 10# happyReduction_61 happyReduction_61 happy_x_2 happy_x_1 = case happyOut13 happy_x_2 of { happy_var_2 -> happyIn16 (I64Const happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_62 = happySpecReduce_2 10# happyReduction_62 happyReduction_62 happy_x_2 happy_x_1 = case happyOut14 happy_x_2 of { happy_var_2 -> happyIn16 (F32Const happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_63 = happySpecReduce_2 10# happyReduction_63 happyReduction_63 happy_x_2 happy_x_1 = case happyOut15 happy_x_2 of { happy_var_2 -> happyIn16 (F64Const happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_64 = happySpecReduce_1 10# happyReduction_64 happyReduction_64 happy_x_1 = happyIn16 (IUnOp BS32 IClz ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_65 = happySpecReduce_1 10# happyReduction_65 happyReduction_65 happy_x_1 = happyIn16 (IUnOp BS32 ICtz ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_66 = happySpecReduce_1 10# happyReduction_66 happyReduction_66 happy_x_1 = happyIn16 (IUnOp BS32 IPopcnt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_67 = happySpecReduce_1 10# happyReduction_67 happyReduction_67 happy_x_1 = happyIn16 (IBinOp BS32 IAdd ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_68 = happySpecReduce_1 10# happyReduction_68 happyReduction_68 happy_x_1 = happyIn16 (IBinOp BS32 ISub ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_69 = happySpecReduce_1 10# happyReduction_69 happyReduction_69 happy_x_1 = happyIn16 (IBinOp BS32 IMul ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_70 = happySpecReduce_1 10# happyReduction_70 happyReduction_70 happy_x_1 = happyIn16 (IBinOp BS32 IDivS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_71 = happySpecReduce_1 10# happyReduction_71 happyReduction_71 happy_x_1 = happyIn16 (IBinOp BS32 IDivU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_72 = happySpecReduce_1 10# happyReduction_72 happyReduction_72 happy_x_1 = happyIn16 (IBinOp BS32 IRemS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_73 = happySpecReduce_1 10# happyReduction_73 happyReduction_73 happy_x_1 = happyIn16 (IBinOp BS32 IRemU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_74 = happySpecReduce_1 10# happyReduction_74 happyReduction_74 happy_x_1 = happyIn16 (IBinOp BS32 IAnd ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_75 = happySpecReduce_1 10# happyReduction_75 happyReduction_75 happy_x_1 = happyIn16 (IBinOp BS32 IOr ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_76 = happySpecReduce_1 10# happyReduction_76 happyReduction_76 happy_x_1 = happyIn16 (IBinOp BS32 IXor ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_77 = happySpecReduce_1 10# happyReduction_77 happyReduction_77 happy_x_1 = happyIn16 (IBinOp BS32 IShl ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_78 = happySpecReduce_1 10# happyReduction_78 happyReduction_78 happy_x_1 = happyIn16 (IBinOp BS32 IShrS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_79 = happySpecReduce_1 10# happyReduction_79 happyReduction_79 happy_x_1 = happyIn16 (IBinOp BS32 IShrU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_80 = happySpecReduce_1 10# happyReduction_80 happyReduction_80 happy_x_1 = happyIn16 (IBinOp BS32 IRotl ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_81 = happySpecReduce_1 10# happyReduction_81 happyReduction_81 happy_x_1 = happyIn16 (IBinOp BS32 IRotr ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_82 = happySpecReduce_1 10# happyReduction_82 happyReduction_82 happy_x_1 = happyIn16 (IUnOp BS64 IClz ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_83 = happySpecReduce_1 10# happyReduction_83 happyReduction_83 happy_x_1 = happyIn16 (IUnOp BS64 ICtz ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_84 = happySpecReduce_1 10# happyReduction_84 happyReduction_84 happy_x_1 = happyIn16 (IUnOp BS64 IPopcnt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_85 = happySpecReduce_1 10# happyReduction_85 happyReduction_85 happy_x_1 = happyIn16 (IBinOp BS64 IAdd ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_86 = happySpecReduce_1 10# happyReduction_86 happyReduction_86 happy_x_1 = happyIn16 (IBinOp BS64 ISub ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_87 = happySpecReduce_1 10# happyReduction_87 happyReduction_87 happy_x_1 = happyIn16 (IBinOp BS64 IMul ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_88 = happySpecReduce_1 10# happyReduction_88 happyReduction_88 happy_x_1 = happyIn16 (IBinOp BS64 IDivS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_89 = happySpecReduce_1 10# happyReduction_89 happyReduction_89 happy_x_1 = happyIn16 (IBinOp BS64 IDivU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_90 = happySpecReduce_1 10# happyReduction_90 happyReduction_90 happy_x_1 = happyIn16 (IBinOp BS64 IRemS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_91 = happySpecReduce_1 10# happyReduction_91 happyReduction_91 happy_x_1 = happyIn16 (IBinOp BS64 IRemU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_92 = happySpecReduce_1 10# happyReduction_92 happyReduction_92 happy_x_1 = happyIn16 (IBinOp BS64 IAnd ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_93 = happySpecReduce_1 10# happyReduction_93 happyReduction_93 happy_x_1 = happyIn16 (IBinOp BS64 IOr ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_94 = happySpecReduce_1 10# happyReduction_94 happyReduction_94 happy_x_1 = happyIn16 (IBinOp BS64 IXor ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_95 = happySpecReduce_1 10# happyReduction_95 happyReduction_95 happy_x_1 = happyIn16 (IBinOp BS64 IShl ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_96 = happySpecReduce_1 10# happyReduction_96 happyReduction_96 happy_x_1 = happyIn16 (IBinOp BS64 IShrS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_97 = happySpecReduce_1 10# happyReduction_97 happyReduction_97 happy_x_1 = happyIn16 (IBinOp BS64 IShrU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_98 = happySpecReduce_1 10# happyReduction_98 happyReduction_98 happy_x_1 = happyIn16 (IBinOp BS64 IRotl ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_99 = happySpecReduce_1 10# happyReduction_99 happyReduction_99 happy_x_1 = happyIn16 (IBinOp BS64 IRotr ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_100 = happySpecReduce_1 10# happyReduction_100 happyReduction_100 happy_x_1 = happyIn16 (FUnOp BS32 FAbs ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_101 = happySpecReduce_1 10# happyReduction_101 happyReduction_101 happy_x_1 = happyIn16 (FUnOp BS32 FNeg ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_102 = happySpecReduce_1 10# happyReduction_102 happyReduction_102 happy_x_1 = happyIn16 (FUnOp BS32 FCeil ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_103 = happySpecReduce_1 10# happyReduction_103 happyReduction_103 happy_x_1 = happyIn16 (FUnOp BS32 FFloor ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_104 = happySpecReduce_1 10# happyReduction_104 happyReduction_104 happy_x_1 = happyIn16 (FUnOp BS32 FTrunc ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_105 = happySpecReduce_1 10# happyReduction_105 happyReduction_105 happy_x_1 = happyIn16 (FUnOp BS32 FNearest ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_106 = happySpecReduce_1 10# happyReduction_106 happyReduction_106 happy_x_1 = happyIn16 (FUnOp BS32 FSqrt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_107 = happySpecReduce_1 10# happyReduction_107 happyReduction_107 happy_x_1 = happyIn16 (FBinOp BS32 FAdd ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_108 = happySpecReduce_1 10# happyReduction_108 happyReduction_108 happy_x_1 = happyIn16 (FBinOp BS32 FSub ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_109 = happySpecReduce_1 10# happyReduction_109 happyReduction_109 happy_x_1 = happyIn16 (FBinOp BS32 FMul ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_110 = happySpecReduce_1 10# happyReduction_110 happyReduction_110 happy_x_1 = happyIn16 (FBinOp BS32 FDiv ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_111 = happySpecReduce_1 10# happyReduction_111 happyReduction_111 happy_x_1 = happyIn16 (FBinOp BS32 FMin ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_112 = happySpecReduce_1 10# happyReduction_112 happyReduction_112 happy_x_1 = happyIn16 (FBinOp BS32 FMax ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_113 = happySpecReduce_1 10# happyReduction_113 happyReduction_113 happy_x_1 = happyIn16 (FBinOp BS32 FCopySign ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_114 = happySpecReduce_1 10# happyReduction_114 happyReduction_114 happy_x_1 = happyIn16 (FUnOp BS64 FAbs ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_115 = happySpecReduce_1 10# happyReduction_115 happyReduction_115 happy_x_1 = happyIn16 (FUnOp BS64 FNeg ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_116 = happySpecReduce_1 10# happyReduction_116 happyReduction_116 happy_x_1 = happyIn16 (FUnOp BS64 FCeil ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_117 = happySpecReduce_1 10# happyReduction_117 happyReduction_117 happy_x_1 = happyIn16 (FUnOp BS64 FFloor ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_118 = happySpecReduce_1 10# happyReduction_118 happyReduction_118 happy_x_1 = happyIn16 (FUnOp BS64 FTrunc ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_119 = happySpecReduce_1 10# happyReduction_119 happyReduction_119 happy_x_1 = happyIn16 (FUnOp BS64 FNearest ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_120 = happySpecReduce_1 10# happyReduction_120 happyReduction_120 happy_x_1 = happyIn16 (FUnOp BS64 FSqrt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_121 = happySpecReduce_1 10# happyReduction_121 happyReduction_121 happy_x_1 = happyIn16 (FBinOp BS64 FAdd ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_122 = happySpecReduce_1 10# happyReduction_122 happyReduction_122 happy_x_1 = happyIn16 (FBinOp BS64 FSub ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_123 = happySpecReduce_1 10# happyReduction_123 happyReduction_123 happy_x_1 = happyIn16 (FBinOp BS64 FMul ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_124 = happySpecReduce_1 10# happyReduction_124 happyReduction_124 happy_x_1 = happyIn16 (FBinOp BS64 FDiv ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_125 = happySpecReduce_1 10# happyReduction_125 happyReduction_125 happy_x_1 = happyIn16 (FBinOp BS64 FMin ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_126 = happySpecReduce_1 10# happyReduction_126 happyReduction_126 happy_x_1 = happyIn16 (FBinOp BS64 FMax ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_127 = happySpecReduce_1 10# happyReduction_127 happyReduction_127 happy_x_1 = happyIn16 (FBinOp BS64 FCopySign ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_128 = happySpecReduce_1 10# happyReduction_128 happyReduction_128 happy_x_1 = happyIn16 (I32Eqz ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_129 = happySpecReduce_1 10# happyReduction_129 happyReduction_129 happy_x_1 = happyIn16 (IRelOp BS32 IEq ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_130 = happySpecReduce_1 10# happyReduction_130 happyReduction_130 happy_x_1 = happyIn16 (IRelOp BS32 INe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_131 = happySpecReduce_1 10# happyReduction_131 happyReduction_131 happy_x_1 = happyIn16 (IRelOp BS32 ILtS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_132 = happySpecReduce_1 10# happyReduction_132 happyReduction_132 happy_x_1 = happyIn16 (IRelOp BS32 ILtU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_133 = happySpecReduce_1 10# happyReduction_133 happyReduction_133 happy_x_1 = happyIn16 (IRelOp BS32 IGtS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_134 = happySpecReduce_1 10# happyReduction_134 happyReduction_134 happy_x_1 = happyIn16 (IRelOp BS32 IGtU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_135 = happySpecReduce_1 10# happyReduction_135 happyReduction_135 happy_x_1 = happyIn16 (IRelOp BS32 ILeS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_136 = happySpecReduce_1 10# happyReduction_136 happyReduction_136 happy_x_1 = happyIn16 (IRelOp BS32 ILeU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_137 = happySpecReduce_1 10# happyReduction_137 happyReduction_137 happy_x_1 = happyIn16 (IRelOp BS32 IGeS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_138 = happySpecReduce_1 10# happyReduction_138 happyReduction_138 happy_x_1 = happyIn16 (IRelOp BS32 IGeU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_139 = happySpecReduce_1 10# happyReduction_139 happyReduction_139 happy_x_1 = happyIn16 (I64Eqz ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_140 = happySpecReduce_1 10# happyReduction_140 happyReduction_140 happy_x_1 = happyIn16 (IRelOp BS64 IEq ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_141 = happySpecReduce_1 10# happyReduction_141 happyReduction_141 happy_x_1 = happyIn16 (IRelOp BS64 INe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_142 = happySpecReduce_1 10# happyReduction_142 happyReduction_142 happy_x_1 = happyIn16 (IRelOp BS64 ILtS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_143 = happySpecReduce_1 10# happyReduction_143 happyReduction_143 happy_x_1 = happyIn16 (IRelOp BS64 ILtU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_144 = happySpecReduce_1 10# happyReduction_144 happyReduction_144 happy_x_1 = happyIn16 (IRelOp BS64 IGtS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_145 = happySpecReduce_1 10# happyReduction_145 happyReduction_145 happy_x_1 = happyIn16 (IRelOp BS64 IGtU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_146 = happySpecReduce_1 10# happyReduction_146 happyReduction_146 happy_x_1 = happyIn16 (IRelOp BS64 ILeS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_147 = happySpecReduce_1 10# happyReduction_147 happyReduction_147 happy_x_1 = happyIn16 (IRelOp BS64 ILeU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_148 = happySpecReduce_1 10# happyReduction_148 happyReduction_148 happy_x_1 = happyIn16 (IRelOp BS64 IGeS ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_149 = happySpecReduce_1 10# happyReduction_149 happyReduction_149 happy_x_1 = happyIn16 (IRelOp BS64 IGeU ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_150 = happySpecReduce_1 10# happyReduction_150 happyReduction_150 happy_x_1 = happyIn16 (FRelOp BS32 FEq ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_151 = happySpecReduce_1 10# happyReduction_151 happyReduction_151 happy_x_1 = happyIn16 (FRelOp BS32 FNe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_152 = happySpecReduce_1 10# happyReduction_152 happyReduction_152 happy_x_1 = happyIn16 (FRelOp BS32 FLt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_153 = happySpecReduce_1 10# happyReduction_153 happyReduction_153 happy_x_1 = happyIn16 (FRelOp BS32 FGt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_154 = happySpecReduce_1 10# happyReduction_154 happyReduction_154 happy_x_1 = happyIn16 (FRelOp BS32 FLe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_155 = happySpecReduce_1 10# happyReduction_155 happyReduction_155 happy_x_1 = happyIn16 (FRelOp BS32 FGe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_156 = happySpecReduce_1 10# happyReduction_156 happyReduction_156 happy_x_1 = happyIn16 (FRelOp BS64 FEq ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_157 = happySpecReduce_1 10# happyReduction_157 happyReduction_157 happy_x_1 = happyIn16 (FRelOp BS64 FNe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_158 = happySpecReduce_1 10# happyReduction_158 happyReduction_158 happy_x_1 = happyIn16 (FRelOp BS64 FLt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_159 = happySpecReduce_1 10# happyReduction_159 happyReduction_159 happy_x_1 = happyIn16 (FRelOp BS64 FGt ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_160 = happySpecReduce_1 10# happyReduction_160 happyReduction_160 happy_x_1 = happyIn16 (FRelOp BS64 FLe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_161 = happySpecReduce_1 10# happyReduction_161 happyReduction_161 happy_x_1 = happyIn16 (FRelOp BS64 FGe ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_162 = happySpecReduce_1 10# happyReduction_162 happyReduction_162 happy_x_1 = happyIn16 (I32WrapI64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_163 = happySpecReduce_1 10# happyReduction_163 happyReduction_163 happy_x_1 = happyIn16 (ITruncFS BS32 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_164 = happySpecReduce_1 10# happyReduction_164 happyReduction_164 happy_x_1 = happyIn16 (ITruncFU BS32 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_165 = happySpecReduce_1 10# happyReduction_165 happyReduction_165 happy_x_1 = happyIn16 (ITruncFS BS32 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_166 = happySpecReduce_1 10# happyReduction_166 happyReduction_166 happy_x_1 = happyIn16 (ITruncFU BS32 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_167 = happySpecReduce_1 10# happyReduction_167 happyReduction_167 happy_x_1 = happyIn16 (I64ExtendSI32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_168 = happySpecReduce_1 10# happyReduction_168 happyReduction_168 happy_x_1 = happyIn16 (I64ExtendUI32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_169 = happySpecReduce_1 10# happyReduction_169 happyReduction_169 happy_x_1 = happyIn16 (ITruncFS BS64 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_170 = happySpecReduce_1 10# happyReduction_170 happyReduction_170 happy_x_1 = happyIn16 (ITruncFU BS64 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_171 = happySpecReduce_1 10# happyReduction_171 happyReduction_171 happy_x_1 = happyIn16 (ITruncFS BS64 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_172 = happySpecReduce_1 10# happyReduction_172 happyReduction_172 happy_x_1 = happyIn16 (ITruncFU BS64 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_173 = happySpecReduce_1 10# happyReduction_173 happyReduction_173 happy_x_1 = happyIn16 (FConvertIS BS32 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_174 = happySpecReduce_1 10# happyReduction_174 happyReduction_174 happy_x_1 = happyIn16 (FConvertIU BS32 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_175 = happySpecReduce_1 10# happyReduction_175 happyReduction_175 happy_x_1 = happyIn16 (FConvertIS BS32 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_176 = happySpecReduce_1 10# happyReduction_176 happyReduction_176 happy_x_1 = happyIn16 (FConvertIU BS32 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_177 = happySpecReduce_1 10# happyReduction_177 happyReduction_177 happy_x_1 = happyIn16 (F32DemoteF64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_178 = happySpecReduce_1 10# happyReduction_178 happyReduction_178 happy_x_1 = happyIn16 (FConvertIS BS64 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_179 = happySpecReduce_1 10# happyReduction_179 happyReduction_179 happy_x_1 = happyIn16 (FConvertIU BS64 BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_180 = happySpecReduce_1 10# happyReduction_180 happyReduction_180 happy_x_1 = happyIn16 (FConvertIS BS64 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_181 = happySpecReduce_1 10# happyReduction_181 happyReduction_181 happy_x_1 = happyIn16 (FConvertIU BS64 BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_182 = happySpecReduce_1 10# happyReduction_182 happyReduction_182 happy_x_1 = happyIn16 (F64PromoteF32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_183 = happySpecReduce_1 10# happyReduction_183 happyReduction_183 happy_x_1 = happyIn16 (IReinterpretF BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_184 = happySpecReduce_1 10# happyReduction_184 happyReduction_184 happy_x_1 = happyIn16 (IReinterpretF BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_185 = happySpecReduce_1 10# happyReduction_185 happyReduction_185 happy_x_1 = happyIn16 (FReinterpretI BS32 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_186 = happySpecReduce_1 10# happyReduction_186 happyReduction_186 happy_x_1 = happyIn16 (FReinterpretI BS64 ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_187 = happySpecReduce_2 11# happyReduction_187 happyReduction_187 happy_x_2 happy_x_1 = case happyOut18 happy_x_2 of { happy_var_2 -> happyIn17 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_188 = happySpecReduce_0 11# happyReduction_188 happyReduction_188 = happyIn17 (AnonimousTypeUse $ FuncType [] [] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_189 = happyReduce 4# 12# happyReduction_189 happyReduction_189 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut10 happy_x_2 of { happy_var_2 -> case happyOut19 happy_x_4 of { happy_var_4 -> happyIn18 (IndexedTypeUse happy_var_2 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_190 = happySpecReduce_1 12# happyReduction_190 happyReduction_190 happy_x_1 = case happyOut26 happy_x_1 of { happy_var_1 -> happyIn18 (AnonimousTypeUse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_191 = happySpecReduce_2 13# happyReduction_191 happyReduction_191 happy_x_2 happy_x_1 = case happyOut26 happy_x_2 of { happy_var_2 -> happyIn19 (Just happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_192 = happySpecReduce_0 13# happyReduction_192 happyReduction_192 = happyIn19 (Nothing ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_193 = happyReduce 4# 14# happyReduction_193 happyReduction_193 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut21 happy_x_3 of { happy_var_3 -> happyIn20 (TypeDef happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_194 = happySpecReduce_3 15# happyReduction_194 happyReduction_194 happy_x_3 happy_x_2 happy_x_1 = case happyOut22 happy_x_3 of { happy_var_3 -> happyIn21 (happy_var_3 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_195 = happySpecReduce_1 16# happyReduction_195 happyReduction_195 happy_x_1 = happyIn22 (emptyFuncType ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_196 = happySpecReduce_2 16# happyReduction_196 happyReduction_196 happy_x_2 happy_x_1 = case happyOut23 happy_x_2 of { happy_var_2 -> happyIn22 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_197 = happyReduce 4# 17# happyReduction_197 happyReduction_197 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut22 happy_x_4 of { happy_var_4 -> happyIn23 (mergeFuncType (FuncType (map (ParamType Nothing) happy_var_2) []) happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_198 = happyReduce 5# 17# happyReduction_198 happyReduction_198 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut8 happy_x_2 of { happy_var_2 -> case happyOut9 happy_x_3 of { happy_var_3 -> case happyOut22 happy_x_5 of { happy_var_5 -> happyIn23 (mergeFuncType (FuncType [ParamType (Just happy_var_2) happy_var_3] []) happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_199 = happySpecReduce_1 17# happyReduction_199 happyReduction_199 happy_x_1 = case happyOut25 happy_x_1 of { happy_var_1 -> happyIn23 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_200 = happySpecReduce_1 18# happyReduction_200 happyReduction_200 happy_x_1 = happyIn24 (emptyFuncType ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_201 = happySpecReduce_2 18# happyReduction_201 happyReduction_201 happy_x_2 happy_x_1 = case happyOut25 happy_x_2 of { happy_var_2 -> happyIn24 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_202 = happyReduce 4# 19# happyReduction_202 happyReduction_202 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut24 happy_x_4 of { happy_var_4 -> happyIn25 (mergeFuncType (FuncType [] happy_var_2) happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_203 = happySpecReduce_3 20# happyReduction_203 happyReduction_203 happy_x_3 happy_x_2 happy_x_1 = case happyOut26 happy_x_1 of { happy_var_1 -> case happyOut27 happy_x_3 of { happy_var_3 -> happyIn26 (mergeFuncType happy_var_1 happy_var_3 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_204 = happySpecReduce_1 20# happyReduction_204 happyReduction_204 happy_x_1 = case happyOut27 happy_x_1 of { happy_var_1 -> happyIn26 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_205 = happySpecReduce_3 21# happyReduction_205 happyReduction_205 happy_x_3 happy_x_2 happy_x_1 = case happyOut117 happy_x_2 of { happy_var_2 -> happyIn27 (FuncType (map (ParamType Nothing) happy_var_2) [] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_206 = happyReduce 4# 21# happyReduction_206 happyReduction_206 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut8 happy_x_2 of { happy_var_2 -> case happyOut9 happy_x_3 of { happy_var_3 -> happyIn27 (FuncType [ParamType (Just happy_var_2) happy_var_3] [] ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_207 = happySpecReduce_3 21# happyReduction_207 happyReduction_207 happy_x_3 happy_x_2 happy_x_1 = case happyOut117 happy_x_2 of { happy_var_2 -> happyIn27 (FuncType [] happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_208 = happyMonadReduce 2# 22# happyReduction_208 happyReduction_208 (happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut121 happy_x_1 of { happy_var_1 -> case happyOut118 happy_x_2 of { happy_var_2 -> ( parseMemArg 1 happy_var_1 happy_var_2)}}) ) (\r -> happyReturn (happyIn28 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_209 = happyMonadReduce 2# 23# happyReduction_209 happyReduction_209 (happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut121 happy_x_1 of { happy_var_1 -> case happyOut118 happy_x_2 of { happy_var_2 -> ( parseMemArg 2 happy_var_1 happy_var_2)}}) ) (\r -> happyReturn (happyIn29 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_210 = happyMonadReduce 2# 24# happyReduction_210 happyReduction_210 (happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut121 happy_x_1 of { happy_var_1 -> case happyOut118 happy_x_2 of { happy_var_2 -> ( parseMemArg 4 happy_var_1 happy_var_2)}}) ) (\r -> happyReturn (happyIn30 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_211 = happyMonadReduce 2# 25# happyReduction_211 happyReduction_211 (happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut121 happy_x_1 of { happy_var_1 -> case happyOut118 happy_x_2 of { happy_var_2 -> ( parseMemArg 8 happy_var_1 happy_var_2)}}) ) (\r -> happyReturn (happyIn31 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_212 = happySpecReduce_1 26# happyReduction_212 happyReduction_212 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> happyIn32 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_213 = happySpecReduce_1 26# happyReduction_213 happyReduction_213 happy_x_1 = case happyOut47 happy_x_1 of { happy_var_1 -> happyIn32 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_214 = happySpecReduce_1 27# happyReduction_214 happyReduction_214 happy_x_1 = case happyOut16 happy_x_1 of { happy_var_1 -> happyIn33 ([PlainInstr happy_var_1] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_215 = happySpecReduce_2 27# happyReduction_215 happyReduction_215 happy_x_2 happy_x_1 = case happyOut41 happy_x_2 of { happy_var_2 -> happyIn33 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_216 = happyMonadReduce 3# 27# happyReduction_216 happyReduction_216 (happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut34 happy_x_3 of { happy_var_3 -> ( (: []) `fmap` happy_var_3 happy_var_2)}}) ) (\r -> happyReturn (happyIn33 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_217 = happyMonadReduce 3# 27# happyReduction_217 happyReduction_217 (happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut36 happy_x_3 of { happy_var_3 -> ( (: []) `fmap` happy_var_3 happy_var_2)}}) ) (\r -> happyReturn (happyIn33 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_218 = happyMonadReduce 3# 27# happyReduction_218 happyReduction_218 (happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut38 happy_x_3 of { happy_var_3 -> ( happy_var_3 happy_var_2)}}) ) (\r -> happyReturn (happyIn33 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_219 = happySpecReduce_2 28# happyReduction_219 happyReduction_219 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> happyIn34 (\ident -> if ident == happy_var_2 || isNothing happy_var_2 then Right $ BlockInstr ident [] [] else Left "Block labels have to match" )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_220 = happyReduce 4# 28# happyReduction_220 happyReduction_220 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut119 happy_x_4 of { happy_var_4 -> happyIn34 (\ident -> if ident == happy_var_4 || isNothing happy_var_4 then Right $ BlockInstr ident [] (happy_var_1 ++ concat happy_var_2) else Left "Block labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_221 = happySpecReduce_2 28# happyReduction_221 happyReduction_221 happy_x_2 happy_x_1 = case happyOut35 happy_x_2 of { happy_var_2 -> happyIn34 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_222 = happyReduce 6# 29# happyReduction_222 happyReduction_222 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_4 of { happy_var_4 -> case happyOut119 happy_x_6 of { happy_var_6 -> happyIn35 (\ident -> if ident == happy_var_6 || isNothing happy_var_6 then Right $ BlockInstr ident [happy_var_2] (concat happy_var_4) else Left "Block labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_223 = happyReduce 4# 29# happyReduction_223 happyReduction_223 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut119 happy_x_4 of { happy_var_4 -> happyIn35 (\ident -> if ident == happy_var_4 || isNothing happy_var_4 then Right $ BlockInstr ident [] (happy_var_1 ++ concat happy_var_2) else Left "Block labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_224 = happySpecReduce_2 30# happyReduction_224 happyReduction_224 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> happyIn36 (\ident -> if ident == happy_var_2 || isNothing happy_var_2 then Right $ LoopInstr ident [] [] else Left "Loop labels have to match" )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_225 = happyReduce 4# 30# happyReduction_225 happyReduction_225 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut119 happy_x_4 of { happy_var_4 -> happyIn36 (\ident -> if ident == happy_var_4 || isNothing happy_var_4 then Right $ LoopInstr ident [] (happy_var_1 ++ concat happy_var_2) else Left "Loop labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_226 = happySpecReduce_2 30# happyReduction_226 happyReduction_226 happy_x_2 happy_x_1 = case happyOut37 happy_x_2 of { happy_var_2 -> happyIn36 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_227 = happyReduce 6# 31# happyReduction_227 happyReduction_227 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_4 of { happy_var_4 -> case happyOut119 happy_x_6 of { happy_var_6 -> happyIn37 (\ident -> if ident == happy_var_6 || isNothing happy_var_6 then Right $ LoopInstr ident [happy_var_2] (concat happy_var_4) else Left "Loop labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_228 = happyReduce 4# 31# happyReduction_228 happyReduction_228 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut119 happy_x_4 of { happy_var_4 -> happyIn37 (\ident -> if ident == happy_var_4 || isNothing happy_var_4 then Right $ LoopInstr ident [] (happy_var_1 ++ concat happy_var_2) else Left "Loop labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_229 = happySpecReduce_1 32# happyReduction_229 happyReduction_229 happy_x_1 = case happyOut40 happy_x_1 of { happy_var_1 -> happyIn38 (\ident -> if ident == (snd happy_var_1) || isNothing (snd happy_var_1) then Right [IfInstr ident [] [] $ fst happy_var_1] else Left "If labels have to match" )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_230 = happySpecReduce_3 32# happyReduction_230 happyReduction_230 happy_x_3 happy_x_2 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut40 happy_x_3 of { happy_var_3 -> happyIn38 (\ident -> if ident == (snd happy_var_3) || isNothing (snd happy_var_3) then Right [IfInstr ident [] (happy_var_1 ++ concat happy_var_2) $ fst happy_var_3] else Left "If labels have to match" )}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_231 = happySpecReduce_2 32# happyReduction_231 happyReduction_231 happy_x_2 happy_x_1 = case happyOut39 happy_x_2 of { happy_var_2 -> happyIn38 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_232 = happyReduce 5# 33# happyReduction_232 happyReduction_232 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_4 of { happy_var_4 -> case happyOut40 happy_x_5 of { happy_var_5 -> happyIn39 (\ident -> if ident == (snd happy_var_5) || isNothing (snd happy_var_5) then Right [IfInstr ident [happy_var_2] (concat happy_var_4) $ fst happy_var_5] else Left "If labels have to match" ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_233 = happySpecReduce_3 33# happyReduction_233 happyReduction_233 happy_x_3 happy_x_2 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut40 happy_x_3 of { happy_var_3 -> happyIn39 (\ident -> if ident == (snd happy_var_3) || isNothing (snd happy_var_3) then Right [IfInstr ident [] (happy_var_1 ++ concat happy_var_2) $ fst happy_var_3] else Left "If labels have to match" )}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_234 = happySpecReduce_2 34# happyReduction_234 happyReduction_234 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> happyIn40 (([], happy_var_2) )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_235 = happyMonadReduce 5# 34# happyReduction_235 happyReduction_235 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_3 of { happy_var_3 -> case happyOut119 happy_x_5 of { happy_var_5 -> ( if matchIdents happy_var_2 happy_var_5 then Right (concat happy_var_3, if isNothing happy_var_2 then happy_var_5 else happy_var_2) else Left "If labels have to match")}}}) ) (\r -> happyReturn (happyIn40 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_236 = happySpecReduce_2 35# happyReduction_236 happyReduction_236 happy_x_2 happy_x_1 = case happyOut42 happy_x_2 of { happy_var_2 -> happyIn41 ((PlainInstr $ CallIndirect $ fst happy_var_2) : snd happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_237 = happySpecReduce_0 35# happyReduction_237 happyReduction_237 = happyIn41 ([PlainInstr $ CallIndirect $ AnonimousTypeUse $ FuncType [] []] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_238 = happyReduce 4# 36# happyReduction_238 happyReduction_238 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut10 happy_x_2 of { happy_var_2 -> case happyOut43 happy_x_4 of { happy_var_4 -> happyIn42 ((IndexedTypeUse happy_var_2 $ fst happy_var_4, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_239 = happySpecReduce_1 36# happyReduction_239 happyReduction_239 happy_x_1 = case happyOut44 happy_x_1 of { happy_var_1 -> happyIn42 ((AnonimousTypeUse $ fromMaybe (FuncType [] []) $ fst happy_var_1, snd happy_var_1) )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_240 = happySpecReduce_2 37# happyReduction_240 happyReduction_240 happy_x_2 happy_x_1 = case happyOut44 happy_x_2 of { happy_var_2 -> happyIn43 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_241 = happySpecReduce_0 37# happyReduction_241 happyReduction_241 = happyIn43 ((Nothing, []) ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_242 = happyReduce 4# 38# happyReduction_242 happyReduction_242 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut43 happy_x_4 of { happy_var_4 -> happyIn44 (let ft = fromMaybe emptyFuncType $ fst happy_var_4 in (Just $ ft { params = map (ParamType Nothing) happy_var_2 ++ params ft }, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_243 = happySpecReduce_1 38# happyReduction_243 happyReduction_243 happy_x_1 = case happyOut46 happy_x_1 of { happy_var_1 -> happyIn44 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_244 = happySpecReduce_2 39# happyReduction_244 happyReduction_244 happy_x_2 happy_x_1 = case happyOut46 happy_x_2 of { happy_var_2 -> happyIn45 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_245 = happySpecReduce_0 39# happyReduction_245 happyReduction_245 = happyIn45 ((Nothing, []) ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_246 = happyReduce 4# 40# happyReduction_246 happyReduction_246 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut45 happy_x_4 of { happy_var_4 -> happyIn46 (let ft = fromMaybe emptyFuncType $ fst happy_var_4 in (Just $ ft { results = happy_var_2 ++ results ft }, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_247 = happySpecReduce_1 40# happyReduction_247 happyReduction_247 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> happyIn46 ((Nothing, happy_var_1) )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_248 = happySpecReduce_2 41# happyReduction_248 happyReduction_248 happy_x_2 happy_x_1 = case happyOut48 happy_x_2 of { happy_var_2 -> happyIn47 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_249 = happySpecReduce_3 42# happyReduction_249 happyReduction_249 happy_x_3 happy_x_2 happy_x_1 = case happyOut16 happy_x_1 of { happy_var_1 -> case happyOut111 happy_x_2 of { happy_var_2 -> happyIn48 (concat happy_var_2 ++ [PlainInstr happy_var_1] )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_250 = happySpecReduce_2 42# happyReduction_250 happyReduction_250 happy_x_2 happy_x_1 = case happyOut56 happy_x_2 of { happy_var_2 -> happyIn48 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_251 = happySpecReduce_3 42# happyReduction_251 happyReduction_251 happy_x_3 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut49 happy_x_3 of { happy_var_3 -> happyIn48 ([happy_var_3 happy_var_2] )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_252 = happySpecReduce_3 42# happyReduction_252 happyReduction_252 happy_x_3 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut51 happy_x_3 of { happy_var_3 -> happyIn48 ([happy_var_3 happy_var_2] )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_253 = happyReduce 4# 42# happyReduction_253 happyReduction_253 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut53 happy_x_4 of { happy_var_4 -> happyIn48 (happy_var_4 happy_var_2 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_254 = happySpecReduce_1 43# happyReduction_254 happyReduction_254 happy_x_1 = happyIn49 (\ident -> BlockInstr ident [] [] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_255 = happySpecReduce_2 43# happyReduction_255 happyReduction_255 happy_x_2 happy_x_1 = case happyOut50 happy_x_2 of { happy_var_2 -> happyIn49 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_256 = happySpecReduce_3 43# happyReduction_256 happyReduction_256 happy_x_3 happy_x_2 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn49 (\ident -> BlockInstr ident [] (happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_257 = happyReduce 5# 44# happyReduction_257 happyReduction_257 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_4 of { happy_var_4 -> happyIn50 (\ident -> BlockInstr ident [happy_var_2] (concat happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_258 = happySpecReduce_3 44# happyReduction_258 happyReduction_258 happy_x_3 happy_x_2 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn50 (\ident -> BlockInstr ident [] (happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_259 = happySpecReduce_1 45# happyReduction_259 happyReduction_259 happy_x_1 = happyIn51 (\ident -> LoopInstr ident [] [] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_260 = happySpecReduce_2 45# happyReduction_260 happyReduction_260 happy_x_2 happy_x_1 = case happyOut52 happy_x_2 of { happy_var_2 -> happyIn51 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_261 = happySpecReduce_3 45# happyReduction_261 happyReduction_261 happy_x_3 happy_x_2 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn51 (\ident -> LoopInstr ident [] (happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_262 = happyReduce 5# 46# happyReduction_262 happyReduction_262 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_4 of { happy_var_4 -> happyIn52 (\ident -> LoopInstr ident [happy_var_2] (concat happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_263 = happySpecReduce_3 46# happyReduction_263 happyReduction_263 happy_x_3 happy_x_2 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn52 (\ident -> LoopInstr ident [] (happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_264 = happyReduce 5# 47# happyReduction_264 happyReduction_264 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut54 happy_x_5 of { happy_var_5 -> happyIn53 (\ident -> let (pred, (trueBranch, falseBranch)) = happy_var_5 in pred ++ [IfInstr ident [happy_var_2] trueBranch falseBranch] ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_265 = happySpecReduce_1 47# happyReduction_265 happyReduction_265 happy_x_1 = case happyOut54 happy_x_1 of { happy_var_1 -> happyIn53 (\ident -> let (pred, (trueBranch, falseBranch)) = happy_var_1 in pred ++ [IfInstr ident [] trueBranch falseBranch] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_266 = happyReduce 4# 48# happyReduction_266 happyReduction_266 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut113 happy_x_2 of { happy_var_2 -> case happyOut55 happy_x_4 of { happy_var_4 -> happyIn54 (([], (concat happy_var_2, happy_var_4)) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_267 = happySpecReduce_3 48# happyReduction_267 happyReduction_267 happy_x_3 happy_x_2 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut54 happy_x_3 of { happy_var_3 -> happyIn54 (let (pred, branches) = happy_var_3 in (happy_var_1 ++ pred, branches) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_268 = happySpecReduce_1 49# happyReduction_268 happyReduction_268 happy_x_1 = happyIn55 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_269 = happyReduce 5# 49# happyReduction_269 happyReduction_269 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut113 happy_x_3 of { happy_var_3 -> happyIn55 (concat happy_var_3 ) `HappyStk` happyRest} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_270 = happySpecReduce_1 50# happyReduction_270 happyReduction_270 happy_x_1 = happyIn56 ([PlainInstr $ CallIndirect $ AnonimousTypeUse $ FuncType [] []] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_271 = happySpecReduce_2 50# happyReduction_271 happyReduction_271 happy_x_2 happy_x_1 = case happyOut57 happy_x_2 of { happy_var_2 -> happyIn56 (snd happy_var_2 ++ [PlainInstr $ CallIndirect $ fst happy_var_2] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_272 = happyReduce 4# 51# happyReduction_272 happyReduction_272 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut10 happy_x_2 of { happy_var_2 -> case happyOut58 happy_x_4 of { happy_var_4 -> happyIn57 ((IndexedTypeUse happy_var_2 $ fst happy_var_4, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_273 = happySpecReduce_1 51# happyReduction_273 happyReduction_273 happy_x_1 = case happyOut59 happy_x_1 of { happy_var_1 -> happyIn57 ((AnonimousTypeUse $ fromMaybe (FuncType [] []) $ fst happy_var_1, snd happy_var_1) )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_274 = happySpecReduce_2 52# happyReduction_274 happyReduction_274 happy_x_2 happy_x_1 = case happyOut59 happy_x_2 of { happy_var_2 -> happyIn58 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_275 = happySpecReduce_1 52# happyReduction_275 happyReduction_275 happy_x_1 = happyIn58 ((Nothing, []) ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_276 = happyReduce 4# 53# happyReduction_276 happyReduction_276 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut58 happy_x_4 of { happy_var_4 -> happyIn59 (let ft = fromMaybe emptyFuncType $ fst happy_var_4 in (Just $ ft { params = map (ParamType Nothing) happy_var_2 ++ params ft }, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_277 = happySpecReduce_1 53# happyReduction_277 happyReduction_277 happy_x_1 = case happyOut61 happy_x_1 of { happy_var_1 -> happyIn59 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_278 = happySpecReduce_2 54# happyReduction_278 happyReduction_278 happy_x_2 happy_x_1 = case happyOut61 happy_x_2 of { happy_var_2 -> happyIn60 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_279 = happySpecReduce_1 54# happyReduction_279 happyReduction_279 happy_x_1 = happyIn60 ((Nothing, []) ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_280 = happyReduce 4# 55# happyReduction_280 happyReduction_280 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut60 happy_x_4 of { happy_var_4 -> happyIn61 (let ft = fromMaybe emptyFuncType $ fst happy_var_4 in (Just $ ft { results = happy_var_2 ++ results ft }, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_281 = happySpecReduce_3 55# happyReduction_281 happyReduction_281 happy_x_3 happy_x_2 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut111 happy_x_2 of { happy_var_2 -> happyIn61 ((Nothing, happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_282 = happyReduce 4# 56# happyReduction_282 happyReduction_282 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut17 happy_x_3 of { happy_var_3 -> happyIn62 (ImportFunc happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_283 = happyReduce 4# 56# happyReduction_283 happyReduction_283 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut86 happy_x_3 of { happy_var_3 -> happyIn62 (ImportTable happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_284 = happyReduce 4# 56# happyReduction_284 happyReduction_284 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut84 happy_x_3 of { happy_var_3 -> happyIn62 (ImportMemory happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_285 = happyReduce 4# 56# happyReduction_285 happyReduction_285 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut76 happy_x_3 of { happy_var_3 -> happyIn62 (ImportGlobal happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_286 = happyReduce 6# 57# happyReduction_286 happyReduction_286 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut7 happy_x_3 of { happy_var_3 -> case happyOut62 happy_x_5 of { happy_var_5 -> happyIn63 (Import [] happy_var_2 happy_var_3 happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_287 = happySpecReduce_3 58# happyReduction_287 happyReduction_287 happy_x_3 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut65 happy_x_3 of { happy_var_3 -> happyIn64 (happy_var_3 happy_var_2 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_288 = happySpecReduce_1 59# happyReduction_288 happyReduction_288 happy_x_1 = happyIn65 (\i -> MFFunc emptyFunction { ident = i } ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_289 = happySpecReduce_3 59# happyReduction_289 happyReduction_289 happy_x_3 happy_x_2 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn65 (\i -> MFFunc emptyFunction { ident = i, body = happy_var_1 ++ concat happy_var_2 } )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_290 = happySpecReduce_2 59# happyReduction_290 happyReduction_290 happy_x_2 happy_x_1 = case happyOut66 happy_x_2 of { happy_var_2 -> happyIn65 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_291 = happyReduce 4# 60# happyReduction_291 happyReduction_291 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut65 happy_x_4 of { happy_var_4 -> happyIn66 (\ident -> case happy_var_4 ident of MFImport imp -> MFImport imp { reExportAs = happy_var_2 : reExportAs imp } MFFunc func -> MFFunc func { exportFuncAs = happy_var_2 : exportFuncAs func } _ -> error "unexpected field" ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_292 = happySpecReduce_1 60# happyReduction_292 happyReduction_292 happy_x_1 = case happyOut67 happy_x_1 of { happy_var_1 -> happyIn66 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_293 = happyReduce 6# 61# happyReduction_293 happyReduction_293 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut7 happy_x_3 of { happy_var_3 -> case happyOut17 happy_x_5 of { happy_var_5 -> happyIn67 (\ident -> MFImport $ Import [] happy_var_2 happy_var_3 $ ImportFunc ident happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_294 = happySpecReduce_1 61# happyReduction_294 happyReduction_294 happy_x_1 = case happyOut68 happy_x_1 of { happy_var_1 -> happyIn67 (MFFunc . happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_295 = happyReduce 4# 62# happyReduction_295 happyReduction_295 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut10 happy_x_2 of { happy_var_2 -> case happyOut69 happy_x_4 of { happy_var_4 -> happyIn68 (\i -> let (AnonimousTypeUse signature) = funcType happy_var_4 in let typeSign = if signature == emptyFuncType then Nothing else Just signature in happy_var_4 { funcType = IndexedTypeUse happy_var_2 typeSign, ident = i } ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_296 = happySpecReduce_1 62# happyReduction_296 happyReduction_296 happy_x_1 = case happyOut70 happy_x_1 of { happy_var_1 -> happyIn68 (\i -> happy_var_1 { ident = i } )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_297 = happySpecReduce_1 63# happyReduction_297 happyReduction_297 happy_x_1 = happyIn69 (emptyFunction ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_298 = happySpecReduce_2 63# happyReduction_298 happyReduction_298 happy_x_2 happy_x_1 = case happyOut70 happy_x_2 of { happy_var_2 -> happyIn69 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_299 = happyReduce 4# 64# happyReduction_299 happyReduction_299 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut69 happy_x_4 of { happy_var_4 -> happyIn70 (prependFuncParams (map (ParamType Nothing) happy_var_2) happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_300 = happyReduce 5# 64# happyReduction_300 happyReduction_300 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut8 happy_x_2 of { happy_var_2 -> case happyOut9 happy_x_3 of { happy_var_3 -> case happyOut69 happy_x_5 of { happy_var_5 -> happyIn70 (prependFuncParams [ParamType (Just happy_var_2) happy_var_3] happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_301 = happySpecReduce_1 64# happyReduction_301 happyReduction_301 happy_x_1 = case happyOut72 happy_x_1 of { happy_var_1 -> happyIn70 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_302 = happySpecReduce_1 65# happyReduction_302 happyReduction_302 happy_x_1 = happyIn71 (emptyFunction ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_303 = happySpecReduce_2 65# happyReduction_303 happyReduction_303 happy_x_2 happy_x_1 = case happyOut72 happy_x_2 of { happy_var_2 -> happyIn71 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_304 = happySpecReduce_3 65# happyReduction_304 happyReduction_304 happy_x_3 happy_x_2 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn71 (emptyFunction { body = happy_var_1 ++ concat happy_var_2 } )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_305 = happyReduce 4# 66# happyReduction_305 happyReduction_305 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut71 happy_x_4 of { happy_var_4 -> happyIn72 (prependFuncResults happy_var_2 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_306 = happySpecReduce_1 66# happyReduction_306 happyReduction_306 happy_x_1 = case happyOut74 happy_x_1 of { happy_var_1 -> happyIn72 (emptyFunction { locals = fst happy_var_1, body = snd happy_var_1 } )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_307 = happySpecReduce_1 67# happyReduction_307 happyReduction_307 happy_x_1 = happyIn73 (([], []) ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_308 = happySpecReduce_3 67# happyReduction_308 happyReduction_308 happy_x_3 happy_x_2 happy_x_1 = case happyOut33 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn73 (([], happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_309 = happySpecReduce_2 67# happyReduction_309 happyReduction_309 happy_x_2 happy_x_1 = case happyOut74 happy_x_2 of { happy_var_2 -> happyIn73 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_310 = happyReduce 4# 68# happyReduction_310 happyReduction_310 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut117 happy_x_2 of { happy_var_2 -> case happyOut73 happy_x_4 of { happy_var_4 -> happyIn74 ((map (LocalType Nothing) happy_var_2 ++ fst happy_var_4, snd happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_311 = happyReduce 5# 68# happyReduction_311 happyReduction_311 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut8 happy_x_2 of { happy_var_2 -> case happyOut9 happy_x_3 of { happy_var_3 -> case happyOut73 happy_x_5 of { happy_var_5 -> happyIn74 ((LocalType (Just happy_var_2) happy_var_3 : fst happy_var_5, snd happy_var_5) ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_312 = happySpecReduce_3 68# happyReduction_312 happyReduction_312 happy_x_3 happy_x_2 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn74 (([], happy_var_1 ++ concat happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_313 = happySpecReduce_3 69# happyReduction_313 happyReduction_313 happy_x_3 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut77 happy_x_3 of { happy_var_3 -> happyIn75 (happy_var_3 happy_var_2 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_314 = happySpecReduce_1 70# happyReduction_314 happyReduction_314 happy_x_1 = case happyOut9 happy_x_1 of { happy_var_1 -> happyIn76 (Const happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_315 = happyReduce 4# 70# happyReduction_315 happyReduction_315 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_3 of { happy_var_3 -> happyIn76 (Mut happy_var_3 ) `HappyStk` happyRest} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_316 = happySpecReduce_3 71# happyReduction_316 happyReduction_316 happy_x_3 happy_x_2 happy_x_1 = case happyOut9 happy_x_1 of { happy_var_1 -> case happyOut113 happy_x_2 of { happy_var_2 -> happyIn77 (\ident -> MFGlobal $ Global [] ident (Const happy_var_1) $ concat happy_var_2 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_317 = happySpecReduce_2 71# happyReduction_317 happyReduction_317 happy_x_2 happy_x_1 = case happyOut78 happy_x_2 of { happy_var_2 -> happyIn77 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_318 = happyReduce 5# 72# happyReduction_318 happyReduction_318 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut9 happy_x_2 of { happy_var_2 -> case happyOut113 happy_x_4 of { happy_var_4 -> happyIn78 (\ident -> MFGlobal $ Global [] ident (Mut happy_var_2) $ concat happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_319 = happyReduce 4# 72# happyReduction_319 happyReduction_319 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut77 happy_x_4 of { happy_var_4 -> happyIn78 (\ident -> case happy_var_4 ident of MFImport imp -> MFImport imp { reExportAs = happy_var_2 : reExportAs imp } MFGlobal global -> MFGlobal global { exportGlobalAs = happy_var_2 : exportGlobalAs global } _ -> error "unexpected field" ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_320 = happyReduce 6# 72# happyReduction_320 happyReduction_320 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut7 happy_x_3 of { happy_var_3 -> case happyOut76 happy_x_5 of { happy_var_5 -> happyIn78 (\ident -> MFImport $ Import [] happy_var_2 happy_var_3 $ ImportGlobal ident happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_321 = happySpecReduce_3 73# happyReduction_321 happyReduction_321 happy_x_3 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut80 happy_x_3 of { happy_var_3 -> happyIn79 (happy_var_3 happy_var_2 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_322 = happySpecReduce_1 74# happyReduction_322 happyReduction_322 happy_x_1 = case happyOut83 happy_x_1 of { happy_var_1 -> happyIn80 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_323 = happySpecReduce_2 74# happyReduction_323 happyReduction_323 happy_x_2 happy_x_1 = case happyOut82 happy_x_2 of { happy_var_2 -> happyIn80 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_324 = happySpecReduce_1 75# happyReduction_324 happyReduction_324 happy_x_1 = case happyOut115 happy_x_1 of { happy_var_1 -> happyIn81 (LBS.concat happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_325 = happyReduce 4# 76# happyReduction_325 happyReduction_325 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut80 happy_x_4 of { happy_var_4 -> happyIn82 (\ident -> case happy_var_4 ident of [MFImport imp] -> [MFImport imp { reExportAs = happy_var_2 : reExportAs imp }] (MFMem (Memory exps i l)):rest -> (MFMem (Memory (happy_var_2:exps) i l)):rest _ -> error "unexpected field" ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_326 = happyReduce 6# 76# happyReduction_326 happyReduction_326 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut7 happy_x_3 of { happy_var_3 -> case happyOut84 happy_x_5 of { happy_var_5 -> happyIn82 (\ident -> [MFImport $ Import [] happy_var_2 happy_var_3 $ ImportMemory ident happy_var_5] ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_327 = happyReduce 4# 76# happyReduction_327 happyReduction_327 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut81 happy_x_2 of { happy_var_2 -> happyIn82 (\ident -> let m = fromIntegral $ LBS.length happy_var_2 in [ MFMem $ Memory [] ident $ Limit m $ Just m, MFData $ DataSegment (fromMaybe (Index 0) $ Named `fmap` ident) [PlainInstr $ I32Const 0] happy_var_2 ] ) `HappyStk` happyRest} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_328 = happySpecReduce_2 77# happyReduction_328 happyReduction_328 happy_x_2 happy_x_1 = case happyOut84 happy_x_1 of { happy_var_1 -> happyIn83 (\ident -> [MFMem $ Memory [] ident happy_var_1] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_329 = happySpecReduce_2 78# happyReduction_329 happyReduction_329 happy_x_2 happy_x_1 = case happyOut12 happy_x_1 of { happy_var_1 -> case happyOut122 happy_x_2 of { happy_var_2 -> happyIn84 (Limit (fromIntegral happy_var_1) (fromIntegral `fmap` happy_var_2) )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_330 = happySpecReduce_1 79# happyReduction_330 happyReduction_330 happy_x_1 = happyIn85 (AnyFunc ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_331 = happySpecReduce_2 80# happyReduction_331 happyReduction_331 happy_x_2 happy_x_1 = case happyOut84 happy_x_1 of { happy_var_1 -> case happyOut85 happy_x_2 of { happy_var_2 -> happyIn86 (TableType happy_var_1 happy_var_2 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_332 = happySpecReduce_3 81# happyReduction_332 happyReduction_332 happy_x_3 happy_x_2 happy_x_1 = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut88 happy_x_3 of { happy_var_3 -> happyIn87 (happy_var_3 happy_var_2 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_333 = happySpecReduce_2 82# happyReduction_333 happyReduction_333 happy_x_2 happy_x_1 = case happyOut86 happy_x_1 of { happy_var_1 -> happyIn88 (\ident -> [MFTable $ Table [] ident happy_var_1] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_334 = happyReduce 6# 82# happyReduction_334 happyReduction_334 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut85 happy_x_1 of { happy_var_1 -> case happyOut112 happy_x_4 of { happy_var_4 -> happyIn88 (\ident -> let funcsLen = fromIntegral $ length happy_var_4 in [ MFTable $ Table [] ident $ TableType (Limit funcsLen (Just funcsLen)) happy_var_1, MFElem $ ElemSegment (fromMaybe (Index 0) $ Named `fmap` ident) [PlainInstr $ I32Const 0] happy_var_4 ] ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_335 = happySpecReduce_2 82# happyReduction_335 happyReduction_335 happy_x_2 happy_x_1 = case happyOut89 happy_x_2 of { happy_var_2 -> happyIn88 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_336 = happyReduce 6# 83# happyReduction_336 happyReduction_336 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut7 happy_x_3 of { happy_var_3 -> case happyOut86 happy_x_5 of { happy_var_5 -> happyIn89 (\ident -> [MFImport $ Import [] happy_var_2 happy_var_3 $ ImportTable ident happy_var_5] ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_337 = happyReduce 4# 83# happyReduction_337 happyReduction_337 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut88 happy_x_4 of { happy_var_4 -> happyIn89 (\ident -> case happy_var_4 ident of [MFImport imp] -> [MFImport imp { reExportAs = happy_var_2 : reExportAs imp }] (MFTable (Table exps i t)):rest -> (MFTable (Table (happy_var_2:exps) i t)):rest _ -> error "unexpected field" ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_338 = happySpecReduce_3 84# happyReduction_338 happyReduction_338 happy_x_3 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn90 (ExportFunc happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_339 = happySpecReduce_3 84# happyReduction_339 happyReduction_339 happy_x_3 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn90 (ExportTable happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_340 = happySpecReduce_3 84# happyReduction_340 happyReduction_340 happy_x_3 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn90 (ExportMemory happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_341 = happySpecReduce_3 84# happyReduction_341 happyReduction_341 happy_x_3 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn90 (ExportGlobal happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_342 = happyReduce 5# 85# happyReduction_342 happyReduction_342 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut7 happy_x_2 of { happy_var_2 -> case happyOut90 happy_x_4 of { happy_var_4 -> happyIn91 (Export happy_var_2 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_343 = happySpecReduce_3 86# happyReduction_343 happyReduction_343 happy_x_3 happy_x_2 happy_x_1 = case happyOut10 happy_x_2 of { happy_var_2 -> happyIn92 (StartFunction happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_344 = happySpecReduce_3 87# happyReduction_344 happyReduction_344 happy_x_3 happy_x_2 happy_x_1 = case happyOut111 happy_x_2 of { happy_var_2 -> happyIn93 (concat happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_345 = happySpecReduce_1 87# happyReduction_345 happyReduction_345 happy_x_1 = case happyOut48 happy_x_1 of { happy_var_1 -> happyIn93 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_346 = happyReduce 6# 88# happyReduction_346 happyReduction_346 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut120 happy_x_2 of { happy_var_2 -> case happyOut93 happy_x_4 of { happy_var_4 -> case happyOut112 happy_x_5 of { happy_var_5 -> happyIn94 (ElemSegment (fromMaybe (Index 0) happy_var_2) happy_var_4 happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_347 = happyReduce 6# 89# happyReduction_347 happyReduction_347 (happy_x_6 `HappyStk` happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut120 happy_x_2 of { happy_var_2 -> case happyOut93 happy_x_4 of { happy_var_4 -> case happyOut81 happy_x_5 of { happy_var_5 -> happyIn95 (DataSegment (fromMaybe (Index 0) happy_var_2) happy_var_4 happy_var_5 ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_348 = happySpecReduce_1 90# happyReduction_348 happyReduction_348 happy_x_1 = case happyOut20 happy_x_1 of { happy_var_1 -> happyIn96 (MFType happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_349 = happySpecReduce_1 90# happyReduction_349 happyReduction_349 happy_x_1 = case happyOut63 happy_x_1 of { happy_var_1 -> happyIn96 (MFImport happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_350 = happySpecReduce_1 90# happyReduction_350 happyReduction_350 happy_x_1 = case happyOut91 happy_x_1 of { happy_var_1 -> happyIn96 (MFExport happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_351 = happySpecReduce_1 90# happyReduction_351 happyReduction_351 happy_x_1 = case happyOut92 happy_x_1 of { happy_var_1 -> happyIn96 (MFStart happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_352 = happySpecReduce_1 90# happyReduction_352 happyReduction_352 happy_x_1 = case happyOut94 happy_x_1 of { happy_var_1 -> happyIn96 (MFElem happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_353 = happySpecReduce_1 90# happyReduction_353 happyReduction_353 happy_x_1 = case happyOut95 happy_x_1 of { happy_var_1 -> happyIn96 (MFData happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_354 = happySpecReduce_1 90# happyReduction_354 happyReduction_354 happy_x_1 = case happyOut64 happy_x_1 of { happy_var_1 -> happyIn96 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_355 = happySpecReduce_1 90# happyReduction_355 happyReduction_355 happy_x_1 = case happyOut75 happy_x_1 of { happy_var_1 -> happyIn96 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_356 = happySpecReduce_1 91# happyReduction_356 happyReduction_356 happy_x_1 = case happyOut87 happy_x_1 of { happy_var_1 -> happyIn97 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_357 = happySpecReduce_1 91# happyReduction_357 happyReduction_357 happy_x_1 = case happyOut79 happy_x_1 of { happy_var_1 -> happyIn97 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_358 = happySpecReduce_1 92# happyReduction_358 happyReduction_358 happy_x_1 = case happyOut96 happy_x_1 of { happy_var_1 -> happyIn98 ([happy_var_1] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_359 = happySpecReduce_1 92# happyReduction_359 happyReduction_359 happy_x_1 = case happyOut97 happy_x_1 of { happy_var_1 -> happyIn98 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_360 = happySpecReduce_2 93# happyReduction_360 happyReduction_360 happy_x_2 happy_x_1 = case happyOut98 happy_x_2 of { happy_var_2 -> happyIn99 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_361 = happyReduce 5# 94# happyReduction_361 happyReduction_361 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut114 happy_x_3 of { happy_var_3 -> happyIn100 (concat happy_var_3 ) `HappyStk` happyRest} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_362 = happyReduce 4# 94# happyReduction_362 happyReduction_362 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut98 happy_x_2 of { happy_var_2 -> case happyOut114 happy_x_3 of { happy_var_3 -> happyIn100 (happy_var_2 ++ concat happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_363 = happyMonadReduce 1# 95# happyReduction_363 happyReduction_363 (happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut100 happy_x_1 of { happy_var_1 -> ( desugarize happy_var_1)}) ) (\r -> happyReturn (happyIn101 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_364 = happySpecReduce_2 96# happyReduction_364 happyReduction_364 happy_x_2 happy_x_1 = case happyOut110 happy_x_1 of { happy_var_1 -> happyIn102 (happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_365 = happySpecReduce_2 97# happyReduction_365 happyReduction_365 happy_x_2 happy_x_1 = case happyOut104 happy_x_2 of { happy_var_2 -> happyIn103 (happy_var_2 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_366 = happySpecReduce_1 98# happyReduction_366 happyReduction_366 happy_x_1 = case happyOut105 happy_x_1 of { happy_var_1 -> happyIn104 (ModuleDef happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_367 = happyReduce 4# 98# happyReduction_367 happyReduction_367 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut6 happy_x_2 of { happy_var_2 -> case happyOut119 happy_x_3 of { happy_var_3 -> happyIn104 (Register happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_368 = happySpecReduce_1 98# happyReduction_368 happyReduction_368 happy_x_1 = case happyOut106 happy_x_1 of { happy_var_1 -> happyIn104 (Action happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_369 = happySpecReduce_1 98# happyReduction_369 happyReduction_369 happy_x_1 = case happyOut107 happy_x_1 of { happy_var_1 -> happyIn104 (Assertion happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_370 = happySpecReduce_1 98# happyReduction_370 happyReduction_370 happy_x_1 = case happyOut109 happy_x_1 of { happy_var_1 -> happyIn104 (Meta happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_371 = happyReduce 5# 99# happyReduction_371 happyReduction_371 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut81 happy_x_4 of { happy_var_4 -> happyIn105 (BinaryModDef happy_var_2 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_372 = happyReduce 5# 99# happyReduction_372 happyReduction_372 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut116 happy_x_4 of { happy_var_4 -> happyIn105 (TextModDef happy_var_2 (TL.concat happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_373 = happyMonadReduce 4# 99# happyReduction_373 happyReduction_373 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut114 happy_x_3 of { happy_var_3 -> ( RawModDef happy_var_2 `fmap` (desugarize $ concat happy_var_3))}}) ) (\r -> happyReturn (happyIn105 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_374 = happyMonadReduce 2# 99# happyReduction_374 happyReduction_374 (happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) tk = happyThen ((case happyOut98 happy_x_1 of { happy_var_1 -> case happyOut114 happy_x_2 of { happy_var_2 -> ( RawModDef Nothing `fmap` (desugarize $ happy_var_1 ++ concat happy_var_2))}}) ) (\r -> happyReturn (happyIn105 r)) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_375 = happyReduce 5# 100# happyReduction_375 happyReduction_375 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut6 happy_x_3 of { happy_var_3 -> case happyOut111 happy_x_4 of { happy_var_4 -> happyIn106 (Invoke happy_var_2 happy_var_3 (map (map constInstructionToValue) happy_var_4) ) `HappyStk` happyRest}}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_376 = happyReduce 4# 100# happyReduction_376 happyReduction_376 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut6 happy_x_3 of { happy_var_3 -> happyIn106 (Get happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_377 = happyReduce 5# 101# happyReduction_377 happyReduction_377 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut106 happy_x_3 of { happy_var_3 -> case happyOut111 happy_x_4 of { happy_var_4 -> happyIn107 (AssertReturn happy_var_3 (map (map constInstructionToValue) happy_var_4) ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_378 = happyReduce 4# 101# happyReduction_378 happyReduction_378 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut106 happy_x_3 of { happy_var_3 -> happyIn107 (AssertReturnCanonicalNaN happy_var_3 ) `HappyStk` happyRest} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_379 = happyReduce 4# 101# happyReduction_379 happyReduction_379 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut106 happy_x_3 of { happy_var_3 -> happyIn107 (AssertReturnArithmeticNaN happy_var_3 ) `HappyStk` happyRest} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_380 = happyReduce 5# 101# happyReduction_380 happyReduction_380 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut108 happy_x_3 of { happy_var_3 -> case happyOut6 happy_x_4 of { happy_var_4 -> happyIn107 (AssertTrap happy_var_3 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_381 = happyReduce 5# 101# happyReduction_381 happyReduction_381 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut105 happy_x_3 of { happy_var_3 -> case happyOut6 happy_x_4 of { happy_var_4 -> happyIn107 (AssertMalformed happy_var_3 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_382 = happyReduce 5# 101# happyReduction_382 happyReduction_382 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut105 happy_x_3 of { happy_var_3 -> case happyOut6 happy_x_4 of { happy_var_4 -> happyIn107 (AssertInvalid happy_var_3 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_383 = happyReduce 5# 101# happyReduction_383 happyReduction_383 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut105 happy_x_3 of { happy_var_3 -> case happyOut6 happy_x_4 of { happy_var_4 -> happyIn107 (AssertUnlinkable happy_var_3 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_384 = happyReduce 5# 101# happyReduction_384 happyReduction_384 (happy_x_5 `HappyStk` happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut106 happy_x_3 of { happy_var_3 -> case happyOut6 happy_x_4 of { happy_var_4 -> happyIn107 (AssertExhaustion happy_var_3 happy_var_4 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_385 = happySpecReduce_1 102# happyReduction_385 happyReduction_385 happy_x_1 = case happyOut106 happy_x_1 of { happy_var_1 -> happyIn108 (Left happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_386 = happySpecReduce_1 102# happyReduction_386 happyReduction_386 happy_x_1 = case happyOut105 happy_x_1 of { happy_var_1 -> happyIn108 (Right happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_387 = happyReduce 4# 103# happyReduction_387 happyReduction_387 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut102 happy_x_3 of { happy_var_3 -> happyIn109 (Script happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_388 = happyReduce 4# 103# happyReduction_388 happyReduction_388 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut6 happy_x_3 of { happy_var_3 -> happyIn109 (Input happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_389 = happyReduce 4# 103# happyReduction_389 happyReduction_389 (happy_x_4 `HappyStk` happy_x_3 `HappyStk` happy_x_2 `HappyStk` happy_x_1 `HappyStk` happyRest) = case happyOut119 happy_x_2 of { happy_var_2 -> case happyOut6 happy_x_3 of { happy_var_3 -> happyIn109 (Output happy_var_2 happy_var_3 ) `HappyStk` happyRest}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_390 = happySpecReduce_1 104# happyReduction_390 happyReduction_390 happy_x_1 = case happyOut124 happy_x_1 of { happy_var_1 -> happyIn110 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_391 = happySpecReduce_1 105# happyReduction_391 happyReduction_391 happy_x_1 = case happyOut125 happy_x_1 of { happy_var_1 -> happyIn111 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_392 = happySpecReduce_1 106# happyReduction_392 happyReduction_392 happy_x_1 = case happyOut126 happy_x_1 of { happy_var_1 -> happyIn112 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_393 = happySpecReduce_1 107# happyReduction_393 happyReduction_393 happy_x_1 = case happyOut127 happy_x_1 of { happy_var_1 -> happyIn113 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_394 = happySpecReduce_1 108# happyReduction_394 happyReduction_394 happy_x_1 = case happyOut128 happy_x_1 of { happy_var_1 -> happyIn114 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_395 = happySpecReduce_1 109# happyReduction_395 happyReduction_395 happy_x_1 = case happyOut129 happy_x_1 of { happy_var_1 -> happyIn115 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_396 = happySpecReduce_1 110# happyReduction_396 happyReduction_396 happy_x_1 = case happyOut130 happy_x_1 of { happy_var_1 -> happyIn116 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_397 = happySpecReduce_1 111# happyReduction_397 happyReduction_397 happy_x_1 = case happyOut131 happy_x_1 of { happy_var_1 -> happyIn117 (reverse happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_398 = happySpecReduce_1 112# happyReduction_398 happyReduction_398 happy_x_1 = case happyOutTok happy_x_1 of { (Lexeme _ (TKeyword (asAlign -> Just happy_var_1))) -> happyIn118 (Just happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_399 = happySpecReduce_0 112# happyReduction_399 happyReduction_399 = happyIn118 (Nothing ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_400 = happySpecReduce_1 113# happyReduction_400 happyReduction_400 happy_x_1 = case happyOut8 happy_x_1 of { happy_var_1 -> happyIn119 (Just happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_401 = happySpecReduce_0 113# happyReduction_401 happyReduction_401 = happyIn119 (Nothing ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_402 = happySpecReduce_1 114# happyReduction_402 happyReduction_402 happy_x_1 = case happyOut10 happy_x_1 of { happy_var_1 -> happyIn120 (Just happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_403 = happySpecReduce_0 114# happyReduction_403 happyReduction_403 = happyIn120 (Nothing ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_404 = happySpecReduce_1 115# happyReduction_404 happyReduction_404 happy_x_1 = case happyOutTok happy_x_1 of { (Lexeme _ (TKeyword (asOffset -> Just happy_var_1))) -> happyIn121 (Just happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_405 = happySpecReduce_0 115# happyReduction_405 happyReduction_405 = happyIn121 (Nothing ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_406 = happySpecReduce_1 116# happyReduction_406 happyReduction_406 happy_x_1 = case happyOut12 happy_x_1 of { happy_var_1 -> happyIn122 (Just happy_var_1 )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_407 = happySpecReduce_0 116# happyReduction_407 happyReduction_407 = happyIn122 (Nothing ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_408 = happySpecReduce_2 117# happyReduction_408 happyReduction_408 happy_x_2 happy_x_1 = case happyOut123 happy_x_1 of { happy_var_1 -> case happyOut10 happy_x_2 of { happy_var_2 -> happyIn123 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_409 = happySpecReduce_1 117# happyReduction_409 happyReduction_409 happy_x_1 = case happyOut10 happy_x_1 of { happy_var_1 -> happyIn123 ([happy_var_1] )} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_410 = happySpecReduce_2 118# happyReduction_410 happyReduction_410 happy_x_2 happy_x_1 = case happyOut124 happy_x_1 of { happy_var_1 -> case happyOut103 happy_x_2 of { happy_var_2 -> happyIn124 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_411 = happySpecReduce_0 118# happyReduction_411 happyReduction_411 = happyIn124 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_412 = happySpecReduce_2 119# happyReduction_412 happyReduction_412 happy_x_2 happy_x_1 = case happyOut125 happy_x_1 of { happy_var_1 -> case happyOut47 happy_x_2 of { happy_var_2 -> happyIn125 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_413 = happySpecReduce_0 119# happyReduction_413 happyReduction_413 = happyIn125 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_414 = happySpecReduce_2 120# happyReduction_414 happyReduction_414 happy_x_2 happy_x_1 = case happyOut126 happy_x_1 of { happy_var_1 -> case happyOut10 happy_x_2 of { happy_var_2 -> happyIn126 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_415 = happySpecReduce_0 120# happyReduction_415 happyReduction_415 = happyIn126 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_416 = happySpecReduce_2 121# happyReduction_416 happyReduction_416 happy_x_2 happy_x_1 = case happyOut127 happy_x_1 of { happy_var_1 -> case happyOut32 happy_x_2 of { happy_var_2 -> happyIn127 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_417 = happySpecReduce_0 121# happyReduction_417 happyReduction_417 = happyIn127 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_418 = happySpecReduce_2 122# happyReduction_418 happyReduction_418 happy_x_2 happy_x_1 = case happyOut128 happy_x_1 of { happy_var_1 -> case happyOut99 happy_x_2 of { happy_var_2 -> happyIn128 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_419 = happySpecReduce_0 122# happyReduction_419 happyReduction_419 = happyIn128 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_420 = happySpecReduce_2 123# happyReduction_420 happyReduction_420 happy_x_2 happy_x_1 = case happyOut129 happy_x_1 of { happy_var_1 -> case happyOutTok happy_x_2 of { (Lexeme _ (TStringLit happy_var_2)) -> happyIn129 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_421 = happySpecReduce_0 123# happyReduction_421 happyReduction_421 = happyIn129 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_422 = happySpecReduce_2 124# happyReduction_422 happyReduction_422 happy_x_2 happy_x_1 = case happyOut130 happy_x_1 of { happy_var_1 -> case happyOut6 happy_x_2 of { happy_var_2 -> happyIn130 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_423 = happySpecReduce_0 124# happyReduction_423 happyReduction_423 = happyIn130 ([] ) #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_424 = happySpecReduce_2 125# happyReduction_424 happyReduction_424 happy_x_2 happy_x_1 = case happyOut131 happy_x_1 of { happy_var_1 -> case happyOut9 happy_x_2 of { happy_var_2 -> happyIn131 (happy_var_2 : happy_var_1 )}} #if __GLASGOW_HASKELL__ >= 710 #endif happyReduce_425 = happySpecReduce_0 125# happyReduction_425 happyReduction_425 = happyIn131 ([] ) happyNewToken action sts stk [] = happyDoAction 222# notHappyAtAll action sts stk [] happyNewToken action sts stk (tk:tks) = let cont i = happyDoAction i tk action sts stk tks in case tk of { Lexeme _ TOpenBracket -> cont 1#; Lexeme _ TCloseBracket -> cont 2#; Lexeme _ (TKeyword "func") -> cont 3#; Lexeme _ (TKeyword "param") -> cont 4#; Lexeme _ (TKeyword "result") -> cont 5#; Lexeme _ (TKeyword "i32") -> cont 6#; Lexeme _ (TKeyword "i64") -> cont 7#; Lexeme _ (TKeyword "f32") -> cont 8#; Lexeme _ (TKeyword "f64") -> cont 9#; Lexeme _ (TKeyword "mut") -> cont 10#; Lexeme _ (TKeyword "anyfunc") -> cont 11#; Lexeme _ (TKeyword "type") -> cont 12#; Lexeme _ (TKeyword "unreachable") -> cont 13#; Lexeme _ (TKeyword "nop") -> cont 14#; Lexeme _ (TKeyword "br") -> cont 15#; Lexeme _ (TKeyword "br_if") -> cont 16#; Lexeme _ (TKeyword "br_table") -> cont 17#; Lexeme _ (TKeyword "return") -> cont 18#; Lexeme _ (TKeyword "call") -> cont 19#; Lexeme _ (TKeyword "call_indirect") -> cont 20#; Lexeme _ (TKeyword "drop") -> cont 21#; Lexeme _ (TKeyword "select") -> cont 22#; Lexeme _ (TKeyword "get_local") -> cont 23#; Lexeme _ (TKeyword "set_local") -> cont 24#; Lexeme _ (TKeyword "tee_local") -> cont 25#; Lexeme _ (TKeyword "get_global") -> cont 26#; Lexeme _ (TKeyword "set_global") -> cont 27#; Lexeme _ (TKeyword "i32.load") -> cont 28#; Lexeme _ (TKeyword "i64.load") -> cont 29#; Lexeme _ (TKeyword "f32.load") -> cont 30#; Lexeme _ (TKeyword "f64.load") -> cont 31#; Lexeme _ (TKeyword "i32.load8_s") -> cont 32#; Lexeme _ (TKeyword "i32.load8_u") -> cont 33#; Lexeme _ (TKeyword "i32.load16_s") -> cont 34#; Lexeme _ (TKeyword "i32.load16_u") -> cont 35#; Lexeme _ (TKeyword "i64.load8_s") -> cont 36#; Lexeme _ (TKeyword "i64.load8_u") -> cont 37#; Lexeme _ (TKeyword "i64.load16_s") -> cont 38#; Lexeme _ (TKeyword "i64.load16_u") -> cont 39#; Lexeme _ (TKeyword "i64.load32_s") -> cont 40#; Lexeme _ (TKeyword "i64.load32_u") -> cont 41#; Lexeme _ (TKeyword "i32.store") -> cont 42#; Lexeme _ (TKeyword "i64.store") -> cont 43#; Lexeme _ (TKeyword "f32.store") -> cont 44#; Lexeme _ (TKeyword "f64.store") -> cont 45#; Lexeme _ (TKeyword "i32.store8") -> cont 46#; Lexeme _ (TKeyword "i32.store16") -> cont 47#; Lexeme _ (TKeyword "i64.store8") -> cont 48#; Lexeme _ (TKeyword "i64.store16") -> cont 49#; Lexeme _ (TKeyword "i64.store32") -> cont 50#; Lexeme _ (TKeyword "current_memory") -> cont 51#; Lexeme _ (TKeyword "grow_memory") -> cont 52#; Lexeme _ (TKeyword "memory.size") -> cont 53#; Lexeme _ (TKeyword "memory.grow") -> cont 54#; Lexeme _ (TKeyword "i32.const") -> cont 55#; Lexeme _ (TKeyword "i64.const") -> cont 56#; Lexeme _ (TKeyword "f32.const") -> cont 57#; Lexeme _ (TKeyword "f64.const") -> cont 58#; Lexeme _ (TKeyword "i32.clz") -> cont 59#; Lexeme _ (TKeyword "i32.ctz") -> cont 60#; Lexeme _ (TKeyword "i32.popcnt") -> cont 61#; Lexeme _ (TKeyword "i32.add") -> cont 62#; Lexeme _ (TKeyword "i32.sub") -> cont 63#; Lexeme _ (TKeyword "i32.mul") -> cont 64#; Lexeme _ (TKeyword "i32.div_s") -> cont 65#; Lexeme _ (TKeyword "i32.div_u") -> cont 66#; Lexeme _ (TKeyword "i32.rem_s") -> cont 67#; Lexeme _ (TKeyword "i32.rem_u") -> cont 68#; Lexeme _ (TKeyword "i32.and") -> cont 69#; Lexeme _ (TKeyword "i32.or") -> cont 70#; Lexeme _ (TKeyword "i32.xor") -> cont 71#; Lexeme _ (TKeyword "i32.shl") -> cont 72#; Lexeme _ (TKeyword "i32.shr_s") -> cont 73#; Lexeme _ (TKeyword "i32.shr_u") -> cont 74#; Lexeme _ (TKeyword "i32.rotl") -> cont 75#; Lexeme _ (TKeyword "i32.rotr") -> cont 76#; Lexeme _ (TKeyword "i64.clz") -> cont 77#; Lexeme _ (TKeyword "i64.ctz") -> cont 78#; Lexeme _ (TKeyword "i64.popcnt") -> cont 79#; Lexeme _ (TKeyword "i64.add") -> cont 80#; Lexeme _ (TKeyword "i64.sub") -> cont 81#; Lexeme _ (TKeyword "i64.mul") -> cont 82#; Lexeme _ (TKeyword "i64.div_s") -> cont 83#; Lexeme _ (TKeyword "i64.div_u") -> cont 84#; Lexeme _ (TKeyword "i64.rem_s") -> cont 85#; Lexeme _ (TKeyword "i64.rem_u") -> cont 86#; Lexeme _ (TKeyword "i64.and") -> cont 87#; Lexeme _ (TKeyword "i64.or") -> cont 88#; Lexeme _ (TKeyword "i64.xor") -> cont 89#; Lexeme _ (TKeyword "i64.shl") -> cont 90#; Lexeme _ (TKeyword "i64.shr_s") -> cont 91#; Lexeme _ (TKeyword "i64.shr_u") -> cont 92#; Lexeme _ (TKeyword "i64.rotl") -> cont 93#; Lexeme _ (TKeyword "i64.rotr") -> cont 94#; Lexeme _ (TKeyword "f32.abs") -> cont 95#; Lexeme _ (TKeyword "f32.neg") -> cont 96#; Lexeme _ (TKeyword "f32.ceil") -> cont 97#; Lexeme _ (TKeyword "f32.floor") -> cont 98#; Lexeme _ (TKeyword "f32.trunc") -> cont 99#; Lexeme _ (TKeyword "f32.nearest") -> cont 100#; Lexeme _ (TKeyword "f32.sqrt") -> cont 101#; Lexeme _ (TKeyword "f32.add") -> cont 102#; Lexeme _ (TKeyword "f32.sub") -> cont 103#; Lexeme _ (TKeyword "f32.mul") -> cont 104#; Lexeme _ (TKeyword "f32.div") -> cont 105#; Lexeme _ (TKeyword "f32.min") -> cont 106#; Lexeme _ (TKeyword "f32.max") -> cont 107#; Lexeme _ (TKeyword "f32.copysign") -> cont 108#; Lexeme _ (TKeyword "f64.abs") -> cont 109#; Lexeme _ (TKeyword "f64.neg") -> cont 110#; Lexeme _ (TKeyword "f64.ceil") -> cont 111#; Lexeme _ (TKeyword "f64.floor") -> cont 112#; Lexeme _ (TKeyword "f64.trunc") -> cont 113#; Lexeme _ (TKeyword "f64.nearest") -> cont 114#; Lexeme _ (TKeyword "f64.sqrt") -> cont 115#; Lexeme _ (TKeyword "f64.add") -> cont 116#; Lexeme _ (TKeyword "f64.sub") -> cont 117#; Lexeme _ (TKeyword "f64.mul") -> cont 118#; Lexeme _ (TKeyword "f64.div") -> cont 119#; Lexeme _ (TKeyword "f64.min") -> cont 120#; Lexeme _ (TKeyword "f64.max") -> cont 121#; Lexeme _ (TKeyword "f64.copysign") -> cont 122#; Lexeme _ (TKeyword "i32.eqz") -> cont 123#; Lexeme _ (TKeyword "i32.eq") -> cont 124#; Lexeme _ (TKeyword "i32.ne") -> cont 125#; Lexeme _ (TKeyword "i32.lt_s") -> cont 126#; Lexeme _ (TKeyword "i32.lt_u") -> cont 127#; Lexeme _ (TKeyword "i32.gt_s") -> cont 128#; Lexeme _ (TKeyword "i32.gt_u") -> cont 129#; Lexeme _ (TKeyword "i32.le_s") -> cont 130#; Lexeme _ (TKeyword "i32.le_u") -> cont 131#; Lexeme _ (TKeyword "i32.ge_s") -> cont 132#; Lexeme _ (TKeyword "i32.ge_u") -> cont 133#; Lexeme _ (TKeyword "i64.eqz") -> cont 134#; Lexeme _ (TKeyword "i64.eq") -> cont 135#; Lexeme _ (TKeyword "i64.ne") -> cont 136#; Lexeme _ (TKeyword "i64.lt_s") -> cont 137#; Lexeme _ (TKeyword "i64.lt_u") -> cont 138#; Lexeme _ (TKeyword "i64.gt_s") -> cont 139#; Lexeme _ (TKeyword "i64.gt_u") -> cont 140#; Lexeme _ (TKeyword "i64.le_s") -> cont 141#; Lexeme _ (TKeyword "i64.le_u") -> cont 142#; Lexeme _ (TKeyword "i64.ge_s") -> cont 143#; Lexeme _ (TKeyword "i64.ge_u") -> cont 144#; Lexeme _ (TKeyword "f32.eq") -> cont 145#; Lexeme _ (TKeyword "f32.ne") -> cont 146#; Lexeme _ (TKeyword "f32.lt") -> cont 147#; Lexeme _ (TKeyword "f32.gt") -> cont 148#; Lexeme _ (TKeyword "f32.le") -> cont 149#; Lexeme _ (TKeyword "f32.ge") -> cont 150#; Lexeme _ (TKeyword "f64.eq") -> cont 151#; Lexeme _ (TKeyword "f64.ne") -> cont 152#; Lexeme _ (TKeyword "f64.lt") -> cont 153#; Lexeme _ (TKeyword "f64.gt") -> cont 154#; Lexeme _ (TKeyword "f64.le") -> cont 155#; Lexeme _ (TKeyword "f64.ge") -> cont 156#; Lexeme _ (TKeyword "i32.wrap/i64") -> cont 157#; Lexeme _ (TKeyword "i32.trunc_s/f32") -> cont 158#; Lexeme _ (TKeyword "i32.trunc_u/f32") -> cont 159#; Lexeme _ (TKeyword "i32.trunc_s/f64") -> cont 160#; Lexeme _ (TKeyword "i32.trunc_u/f64") -> cont 161#; Lexeme _ (TKeyword "i64.extend_s/i32") -> cont 162#; Lexeme _ (TKeyword "i64.extend_u/i32") -> cont 163#; Lexeme _ (TKeyword "i64.trunc_s/f32") -> cont 164#; Lexeme _ (TKeyword "i64.trunc_u/f32") -> cont 165#; Lexeme _ (TKeyword "i64.trunc_s/f64") -> cont 166#; Lexeme _ (TKeyword "i64.trunc_u/f64") -> cont 167#; Lexeme _ (TKeyword "f32.convert_s/i32") -> cont 168#; Lexeme _ (TKeyword "f32.convert_u/i32") -> cont 169#; Lexeme _ (TKeyword "f32.convert_s/i64") -> cont 170#; Lexeme _ (TKeyword "f32.convert_u/i64") -> cont 171#; Lexeme _ (TKeyword "f32.demote/f64") -> cont 172#; Lexeme _ (TKeyword "f64.convert_s/i32") -> cont 173#; Lexeme _ (TKeyword "f64.convert_u/i32") -> cont 174#; Lexeme _ (TKeyword "f64.convert_s/i64") -> cont 175#; Lexeme _ (TKeyword "f64.convert_u/i64") -> cont 176#; Lexeme _ (TKeyword "f64.promote/f32") -> cont 177#; Lexeme _ (TKeyword "i32.reinterpret/f32") -> cont 178#; Lexeme _ (TKeyword "i64.reinterpret/f64") -> cont 179#; Lexeme _ (TKeyword "f32.reinterpret/i32") -> cont 180#; Lexeme _ (TKeyword "f64.reinterpret/i64") -> cont 181#; Lexeme _ (TKeyword "block") -> cont 182#; Lexeme _ (TKeyword "loop") -> cont 183#; Lexeme _ (TKeyword "if") -> cont 184#; Lexeme _ (TKeyword "else") -> cont 185#; Lexeme _ (TKeyword "end") -> cont 186#; Lexeme _ (TKeyword "then") -> cont 187#; Lexeme _ (TKeyword "table") -> cont 188#; Lexeme _ (TKeyword "memory") -> cont 189#; Lexeme _ (TKeyword "global") -> cont 190#; Lexeme _ (TKeyword "import") -> cont 191#; Lexeme _ (TKeyword "export") -> cont 192#; Lexeme _ (TKeyword "local") -> cont 193#; Lexeme _ (TKeyword "elem") -> cont 194#; Lexeme _ (TKeyword "data") -> cont 195#; Lexeme _ (TKeyword "offset") -> cont 196#; Lexeme _ (TKeyword "start") -> cont 197#; Lexeme _ (TKeyword "module") -> cont 198#; Lexeme _ (TKeyword "binary") -> cont 199#; Lexeme _ (TKeyword "quote") -> cont 200#; Lexeme _ (TKeyword "register") -> cont 201#; Lexeme _ (TKeyword "invoke") -> cont 202#; Lexeme _ (TKeyword "get") -> cont 203#; Lexeme _ (TKeyword "assert_return") -> cont 204#; Lexeme _ (TKeyword "assert_return_canonical_nan") -> cont 205#; Lexeme _ (TKeyword "assert_return_arithmetic_nan") -> cont 206#; Lexeme _ (TKeyword "assert_trap") -> cont 207#; Lexeme _ (TKeyword "assert_malformed") -> cont 208#; Lexeme _ (TKeyword "assert_invalid") -> cont 209#; Lexeme _ (TKeyword "assert_unlinkable") -> cont 210#; Lexeme _ (TKeyword "assert_exhaustion") -> cont 211#; Lexeme _ (TKeyword "script") -> cont 212#; Lexeme _ (TKeyword "input") -> cont 213#; Lexeme _ (TKeyword "output") -> cont 214#; Lexeme _ (TId happy_dollar_dollar) -> cont 215#; Lexeme _ (TIntLit happy_dollar_dollar) -> cont 216#; Lexeme _ (TFloatLit happy_dollar_dollar) -> cont 217#; Lexeme _ (TKeyword (asOffset -> Just happy_dollar_dollar)) -> cont 218#; Lexeme _ (TKeyword (asAlign -> Just happy_dollar_dollar)) -> cont 219#; Lexeme _ (TStringLit happy_dollar_dollar) -> cont 220#; Lexeme _ EOF -> cont 221#; _ -> happyError' ((tk:tks), []) } happyError_ explist 222# tk tks = happyError' (tks, explist) happyError_ explist _ tk tks = happyError' ((tk:tks), explist) happyThen :: () => Either String a -> (a -> Either String b) -> Either String b happyThen = (>>=) happyReturn :: () => a -> Either String a happyReturn = (return) happyThen1 m k tks = (>>=) m (\a -> k a tks) happyReturn1 :: () => a -> b -> Either String a happyReturn1 = \a tks -> (return) a happyError' :: () => ([(Lexeme)], [String]) -> Either String a happyError' = (\(tokens, _) -> happyError tokens) parseModule tks = happySomeParser where happySomeParser = happyThen (happyParse 0# tks) (\x -> happyReturn (happyOut101 x)) parseModuleFields tks = happySomeParser where happySomeParser = happyThen (happyParse 1# tks) (\x -> happyReturn (happyOut100 x)) parseScript tks = happySomeParser where happySomeParser = happyThen (happyParse 2# tks) (\x -> happyReturn (happyOut102 x)) happySeq = happyDontSeq -- partial function by intention prependFuncParams :: [ParamType] -> Function -> Function prependFuncParams prep f@(Function { funcType = AnonimousTypeUse ft }) = f { funcType = AnonimousTypeUse $ ft { params = prep ++ params ft } } prependFuncResults :: [ValueType] -> Function -> Function prependFuncResults prep f@(Function { funcType = AnonimousTypeUse ft }) = f { funcType = AnonimousTypeUse $ ft { results = prep ++ results ft } } mergeFuncType :: FuncType -> FuncType -> FuncType mergeFuncType (FuncType lps lrs) (FuncType rps rrs) = FuncType (lps ++ rps) (lrs ++ rrs) matchIdents :: Maybe Ident -> Maybe Ident -> Bool matchIdents Nothing _ = True matchIdents _ Nothing = True matchIdents a b = a == b asOffset :: LBS.ByteString -> Maybe Natural asOffset str = do num <- TL.stripPrefix "offset=" $ TLEncoding.decodeUtf8 str fromIntegral . fst <$> eitherToMaybe (TLRead.decimal num) asAlign :: LBS.ByteString -> Maybe Natural asAlign str = do num <- TL.stripPrefix "align=" $ TLEncoding.decodeUtf8 str fromIntegral . fst <$> eitherToMaybe (TLRead.decimal num) parseMemArg :: Natural -> Maybe Natural -> Maybe Natural -> Either String MemArg parseMemArg defAlign optOffset optAlign = do let offset = fromMaybe 0 optOffset let parsedAlign = fromIntegral $ fromMaybe defAlign optAlign if parsedAlign == 0 then Left "alignment" else return () let align = fromIntegral $ round $ logBase 2 parsedAlign if 2 ^ align /= parsedAlign then Left "alignment" else return () if offset >= 2 ^ 32 || align >= 2 ^ 32 then Left "u32 is out of boundaries" else return $ MemArg offset align eitherToMaybe :: Either left right -> Maybe right eitherToMaybe = either (const Nothing) Just integerToWord32 :: Integer -> Word32 integerToWord32 i | i >= 0 && i <= 2 ^ 32 = fromIntegral i | i < 0 && i >= -(2 ^ 31) = 0xFFFFFFFF - (fromIntegral (abs i)) + 1 | otherwise = error "I32 is out of bounds." integerToWord64 :: Integer -> Word64 integerToWord64 i | i >= 0 && i <= 2 ^ 64 = fromIntegral i | i < 0 && i >= -(2 ^ 63) = 0xFFFFFFFFFFFFFFFF - (fromIntegral (abs i)) + 1 | otherwise = error "I64 is out of bounds." data FuncType = FuncType { params :: [ParamType], results :: [ValueType] } deriving (Show, Eq, Generic, NFData) emptyFuncType :: FuncType emptyFuncType = FuncType [] [] data ParamType = ParamType { ident :: Maybe Ident, paramType :: ValueType } deriving (Show, Eq, Generic, NFData) newtype Ident = Ident TL.Text deriving (Show, Eq, Generic, NFData) data Index = Named Ident | Index Natural deriving (Show, Eq, Generic, NFData) type LabelIndex = Index type FuncIndex = Index type TypeIndex = Index type LocalIndex = Index type GlobalIndex = Index type TableIndex = Index type MemoryIndex = Index data PlainInstr = -- Control instructions Unreachable | Nop | Br LabelIndex | BrIf LabelIndex | BrTable [LabelIndex] LabelIndex | Return | Call FuncIndex | CallIndirect TypeUse -- Parametric instructions | Drop | Select -- Variable instructions | GetLocal LocalIndex | SetLocal LocalIndex | TeeLocal LocalIndex | GetGlobal GlobalIndex | SetGlobal GlobalIndex -- Memory instructions | I32Load MemArg | I64Load MemArg | F32Load MemArg | F64Load MemArg | I32Load8S MemArg | I32Load8U MemArg | I32Load16S MemArg | I32Load16U MemArg | I64Load8S MemArg | I64Load8U MemArg | I64Load16S MemArg | I64Load16U MemArg | I64Load32S MemArg | I64Load32U MemArg | I32Store MemArg | I64Store MemArg | F32Store MemArg | F64Store MemArg | I32Store8 MemArg | I32Store16 MemArg | I64Store8 MemArg | I64Store16 MemArg | I64Store32 MemArg | CurrentMemory | GrowMemory -- Numeric instructions | I32Const Integer | I64Const Integer | F32Const Float | F64Const Double | IUnOp BitSize IUnOp | IBinOp BitSize IBinOp | I32Eqz | I64Eqz | IRelOp BitSize IRelOp | FUnOp BitSize FUnOp | FBinOp BitSize FBinOp | FRelOp BitSize FRelOp | I32WrapI64 | ITruncFU {- Int Size -} BitSize {- Float Size -} BitSize | ITruncFS {- Int Size -} BitSize {- Float Size -} BitSize | I64ExtendSI32 | I64ExtendUI32 | FConvertIU {- Float Size -} BitSize {- Int Size -} BitSize | FConvertIS {- Float Size -} BitSize {- Int Size -} BitSize | F32DemoteF64 | F64PromoteF32 | IReinterpretF BitSize | FReinterpretI BitSize deriving (Show, Eq, Generic, NFData) data TypeDef = TypeDef (Maybe Ident) FuncType deriving (Show, Eq, Generic, NFData) data TypeUse = IndexedTypeUse TypeIndex (Maybe FuncType) | AnonimousTypeUse FuncType deriving (Show, Eq, Generic, NFData) data Instruction = PlainInstr PlainInstr | BlockInstr { label :: Maybe Ident, resultType :: [ValueType], body :: [Instruction] } | LoopInstr { label :: Maybe Ident, resultType :: [ValueType], body :: [Instruction] } | IfInstr { label :: Maybe Ident, resultType :: [ValueType], trueBranch :: [Instruction], falseBranch :: [Instruction] } deriving (Show, Eq, Generic, NFData) data Import = Import { reExportAs :: [TL.Text], sourceModule :: TL.Text, name :: TL.Text, desc :: ImportDesc } deriving (Show, Eq, Generic, NFData) data ImportDesc = ImportFunc (Maybe Ident) TypeUse | ImportTable (Maybe Ident) TableType | ImportMemory (Maybe Ident) Limit | ImportGlobal (Maybe Ident) GlobalType deriving (Show, Eq, Generic, NFData) data LocalType = LocalType { ident :: Maybe Ident, localType :: ValueType } deriving (Show, Eq, Generic, NFData) data Function = Function { exportFuncAs :: [TL.Text], ident :: Maybe Ident, funcType :: TypeUse, locals :: [LocalType], body :: [Instruction] } deriving (Show, Eq, Generic, NFData) emptyFunction :: Function emptyFunction = Function { exportFuncAs = [], ident = Nothing, funcType = AnonimousTypeUse emptyFuncType, locals = [], body = [] } data Global = Global { exportGlobalAs :: [TL.Text], ident :: Maybe Ident, globalType :: GlobalType, initializer :: [Instruction] } deriving (Show, Eq, Generic, NFData) data Memory = Memory [TL.Text] (Maybe Ident) Limit deriving (Show, Eq, Generic, NFData) data Table = Table [TL.Text] (Maybe Ident) TableType deriving (Show, Eq, Generic, NFData) data ExportDesc = ExportFunc FuncIndex | ExportTable TableIndex | ExportMemory MemoryIndex | ExportGlobal GlobalIndex deriving (Show, Eq, Generic, NFData) data Export = Export { name :: TL.Text, desc :: ExportDesc } deriving (Show, Eq, Generic, NFData) data StartFunction = StartFunction FuncIndex deriving (Show, Eq, Generic, NFData) data ElemSegment = ElemSegment { tableIndex :: TableIndex, offset :: [Instruction], funcIndexes :: [FuncIndex] } deriving (Show, Eq, Generic, NFData) data DataSegment = DataSegment { memIndex :: MemoryIndex, offset :: [Instruction], datastring :: LBS.ByteString } deriving (Show, Eq, Generic, NFData) data ModuleField = MFType TypeDef | MFImport Import | MFFunc Function | MFTable Table | MFMem Memory | MFGlobal Global | MFExport Export | MFStart StartFunction | MFElem ElemSegment | MFData DataSegment deriving(Show, Eq, Generic, NFData) happyError (Lexeme _ EOF : []) = Left $ "Error occuried during parsing phase at the end of file" happyError (Lexeme Nothing tok : tokens) = Left $ "Error occuried during parsing phase at the end of file" happyError (Lexeme (Just (AlexPn abs line col)) tok : tokens) = Left $ "Error occuried during parsing phase. " ++ "Line " ++ show line ++ ", " ++ "Column " ++ show col ++ ", " ++ "Token " ++ show tok ++ ". " ++ "Token lookahed: " ++ show (take 3 tokens) data Module = Module { types :: [TypeDef], functions :: [Function], tables :: [Table], mems :: [Memory], globals :: [Global], elems :: [ElemSegment], datas :: [DataSegment], start :: Maybe StartFunction, imports :: [Import], exports :: [Export] } deriving (Show, Eq) type Script = [Command] data ModuleDef = RawModDef (Maybe Ident) S.Module | TextModDef (Maybe Ident) TL.Text | BinaryModDef (Maybe Ident) LBS.ByteString deriving (Show, Eq) data Command = ModuleDef ModuleDef | Register TL.Text (Maybe Ident) | Action Action | Assertion Assertion | Meta Meta deriving (Show, Eq) data Action = Invoke (Maybe Ident) TL.Text [S.Expression] | Get (Maybe Ident) TL.Text deriving (Show, Eq) type FailureString = TL.Text data Assertion = AssertReturn Action [S.Expression] | AssertReturnCanonicalNaN Action | AssertReturnArithmeticNaN Action | AssertTrap (Either Action ModuleDef) FailureString | AssertMalformed ModuleDef FailureString | AssertInvalid ModuleDef FailureString | AssertUnlinkable ModuleDef FailureString | AssertExhaustion Action FailureString deriving (Show, Eq) data Meta = Script (Maybe Ident) Script | Input (Maybe Ident) TL.Text | Output (Maybe Ident) TL.Text deriving (Show, Eq) type Labels = [Maybe Ident] data FunCtx = FunCtx { ctxMod :: Module, ctxLabels :: Labels, ctxLocals :: [LocalType], ctxParams :: [ParamType] } deriving (Eq, Show) constInstructionToValue :: Instruction -> S.Instruction Natural constInstructionToValue (PlainInstr (I32Const v)) = S.I32Const $ integerToWord32 v constInstructionToValue (PlainInstr (F32Const v)) = S.F32Const v constInstructionToValue (PlainInstr (I64Const v)) = S.I64Const $ integerToWord64 v constInstructionToValue (PlainInstr (F64Const v)) = S.F64Const v constInstructionToValue _ = error "Only const instructions supported as arguments for actions" desugarize :: [ModuleField] -> Either String S.Module desugarize fields = do checkImportsOrder fields let mod = Module { types = reverse $ foldl' extractTypeDef (reverse $ explicitTypeDefs fields) fields, functions = extract extractFunction fields, tables = extract extractTable fields, imports = extract extractImport fields, mems = extract extractMemory fields, globals = extract extractGlobal fields, elems = extract extractElemSegment fields, datas = extract extractDataSegment fields, start = extractStart fields, exports = [] } funs <- mapM (synFunctionToStruct mod) $ functions mod elements <- mapM (synElemToStruct mod) $ elems mod segments <- mapM (synDataToStruct mod) $ datas mod globs <- mapM (synGlobalToStruct mod) $ globals mod return S.Module { S.types = map synTypeDefToStruct $ types mod, S.functions = funs, S.tables = map synTableToStruct $ tables mod, S.imports = map (synImportToStruct $ types mod) $ imports mod, S.elems = elements, S.datas = segments, S.mems = map synMemoryToStruct $ mems mod, S.globals = globs, S.start = fmap (synStartToStruct mod) $ start mod, S.exports = synExportsToStruct mod $ extractExports mod fields } where -- utils extract :: ([a] -> ModuleField -> [a]) -> [ModuleField] -> [a] extract extractor = reverse . foldl' extractor [] findWithIndex :: (a -> Bool) -> [a] -> Maybe (a, Int) findWithIndex pred l = find (pred . fst) $ zip l [0..] -- types synTypeDefToStruct :: TypeDef -> S.FuncType synTypeDefToStruct (TypeDef _ FuncType { params, results }) = S.FuncType (map paramType params) results explicitTypeDefs :: [ModuleField] -> [TypeDef] explicitTypeDefs = map (\(MFType def) -> def) . filter isTypeDef where isTypeDef (MFType _) = True isTypeDef _ = False checkImportsOrder :: [ModuleField] -> Either String () checkImportsOrder fields = foldM checkDef False fields >> return () where checkDef nonImportOccured (MFImport _) = if nonImportOccured then Left "Import sections have to be before any definition" else Right False checkDef _ (MFFunc _) = return True checkDef _ (MFGlobal _) = return True checkDef _ (MFMem _) = return True checkDef _ (MFTable _) = return True checkDef nonImportOccured _ = return nonImportOccured extractTypeDef :: [TypeDef] -> ModuleField -> [TypeDef] extractTypeDef defs (MFType _) = defs -- should be extracted before implicit defs extractTypeDef defs (MFImport Import { desc = ImportFunc _ typeUse }) = matchTypeUse defs typeUse extractTypeDef defs (MFFunc Function { funcType, body }) = extractTypeDefFromInstructions (matchTypeUse defs funcType) body extractTypeDef defs (MFGlobal Global { initializer }) = extractTypeDefFromInstructions defs initializer extractTypeDef defs (MFElem ElemSegment { offset }) = extractTypeDefFromInstructions defs offset extractTypeDef defs (MFData DataSegment { offset }) = extractTypeDefFromInstructions defs offset extractTypeDef defs _ = defs extractTypeDefFromInstructions :: [TypeDef] -> [Instruction] -> [TypeDef] extractTypeDefFromInstructions = foldl' extractTypeDefFromInstruction extractTypeDefFromInstruction :: [TypeDef] -> Instruction -> [TypeDef] extractTypeDefFromInstruction defs (PlainInstr (CallIndirect typeUse)) = matchTypeUse defs typeUse extractTypeDefFromInstruction defs (BlockInstr { body }) = extractTypeDefFromInstructions defs body extractTypeDefFromInstruction defs (LoopInstr { body }) = extractTypeDefFromInstructions defs body extractTypeDefFromInstruction defs (IfInstr { trueBranch, falseBranch }) = extractTypeDefFromInstructions defs $ trueBranch ++ falseBranch extractTypeDefFromInstruction defs _ = defs funcTypesEq :: FuncType -> FuncType -> Bool funcTypesEq l r = let paramTypes = map paramType . params in paramTypes l == paramTypes r && results l == results r matchTypeFunc :: FuncType -> TypeDef -> Bool matchTypeFunc funcType (TypeDef _ ft) = funcTypesEq ft funcType matchTypeUse :: [TypeDef] -> TypeUse -> [TypeDef] matchTypeUse defs (AnonimousTypeUse funcType) = if any (matchTypeFunc funcType) defs then defs else (TypeDef Nothing funcType) : defs matchTypeUse defs _ = defs getTypeIndex :: [TypeDef] -> TypeUse -> Maybe Natural getTypeIndex defs (AnonimousTypeUse funcType) = fromIntegral <$> findIndex (matchTypeFunc funcType) defs getTypeIndex defs (IndexedTypeUse (Named ident) (Just funcType)) = do (def, idx) <- findWithIndex (\(TypeDef i _) -> i == Just ident) defs guard $ matchTypeFunc funcType def return $ fromIntegral idx getTypeIndex defs (IndexedTypeUse (Named ident) Nothing) = fromIntegral <$> findIndex (\(TypeDef i _) -> i == Just ident) defs getTypeIndex defs (IndexedTypeUse (Index n) (Just funcType)) = do guard $ matchTypeFunc funcType $ defs !! fromIntegral n return n getTypeIndex defs (IndexedTypeUse (Index n) Nothing) = return n -- imports synImportToStruct :: [TypeDef] -> Import -> S.Import synImportToStruct defs (Import _ mod name (ImportFunc _ typeUse)) = case getTypeIndex defs typeUse of Just idx -> S.Import mod name $ S.ImportFunc idx Nothing -> error $ "cannot find type index for function import: " ++ show typeUse synImportToStruct _ (Import _ mod name (ImportTable _ tableType)) = S.Import mod name $ S.ImportTable tableType synImportToStruct _ (Import _ mod name (ImportMemory _ limit)) = S.Import mod name $ S.ImportMemory limit synImportToStruct _ (Import _ mod name (ImportGlobal _ globalType)) = S.Import mod name $ S.ImportGlobal globalType extractImport :: [Import] -> ModuleField -> [Import] extractImport imports (MFImport imp) = imp : imports extractImport imports _ = imports unwrapLabel ctx labelIdx = case getLabelIdx ctx labelIdx of Just i -> Right i Nothing -> Left "unknown label" -- functions synInstrToStruct :: FunCtx -> Instruction -> Either String (S.Instruction Natural) synInstrToStruct _ (PlainInstr Unreachable) = return S.Unreachable synInstrToStruct _ (PlainInstr Nop) = return S.Nop synInstrToStruct ctx (PlainInstr (Br labelIdx)) = S.Br <$> unwrapLabel ctx labelIdx synInstrToStruct ctx (PlainInstr (BrIf labelIdx)) = S.BrIf <$> unwrapLabel ctx labelIdx synInstrToStruct ctx (PlainInstr (BrTable lbls lbl)) = do labels <- mapM (unwrapLabel ctx) lbls S.BrTable labels <$> unwrapLabel ctx lbl synInstrToStruct _ (PlainInstr Return) = return S.Return synInstrToStruct FunCtx { ctxMod } (PlainInstr (Call funIdx)) = case getFuncIndex ctxMod funIdx of Just idx -> return $ S.Call idx Nothing -> Left "unknown function" synInstrToStruct FunCtx { ctxMod = Module { types } } (PlainInstr (CallIndirect typeUse)) = case getTypeIndex types typeUse of Just idx -> return $ S.CallIndirect idx Nothing -> Left "unknown type" synInstrToStruct _ (PlainInstr Drop) = return $ S.Drop synInstrToStruct _ (PlainInstr Select) = return $ S.Select synInstrToStruct ctx (PlainInstr (GetLocal localIdx)) = case getLocalIndex ctx localIdx of Just idx -> return $ S.GetLocal idx Nothing -> Left "unknown local" synInstrToStruct ctx (PlainInstr (SetLocal localIdx)) = case getLocalIndex ctx localIdx of Just idx -> return $ S.SetLocal idx Nothing -> Left "unknown local" synInstrToStruct ctx (PlainInstr (TeeLocal localIdx)) = case getLocalIndex ctx localIdx of Just idx -> return $ S.TeeLocal idx Nothing -> Left "unknown local" synInstrToStruct FunCtx { ctxMod } (PlainInstr (GetGlobal globalIdx)) = case getGlobalIndex ctxMod globalIdx of Just idx -> return $ S.GetGlobal idx Nothing -> Left "unknown global" synInstrToStruct FunCtx { ctxMod } (PlainInstr (SetGlobal globalIdx)) = case getGlobalIndex ctxMod globalIdx of Just idx -> return $ S.SetGlobal idx Nothing -> Left "unknown global" synInstrToStruct _ (PlainInstr (I32Load memArg)) = return $ S.I32Load memArg synInstrToStruct _ (PlainInstr (I64Load memArg)) = return $ S.I64Load memArg synInstrToStruct _ (PlainInstr (F32Load memArg)) = return $ S.F32Load memArg synInstrToStruct _ (PlainInstr (F64Load memArg)) = return $ S.F64Load memArg synInstrToStruct _ (PlainInstr (I32Load8S memArg)) = return $ S.I32Load8S memArg synInstrToStruct _ (PlainInstr (I32Load8U memArg)) = return $ S.I32Load8U memArg synInstrToStruct _ (PlainInstr (I32Load16S memArg)) = return $ S.I32Load16S memArg synInstrToStruct _ (PlainInstr (I32Load16U memArg)) = return $ S.I32Load16U memArg synInstrToStruct _ (PlainInstr (I64Load8S memArg)) = return $ S.I64Load8S memArg synInstrToStruct _ (PlainInstr (I64Load8U memArg)) = return $ S.I64Load8U memArg synInstrToStruct _ (PlainInstr (I64Load16S memArg)) = return $ S.I64Load16S memArg synInstrToStruct _ (PlainInstr (I64Load16U memArg)) = return $ S.I64Load16U memArg synInstrToStruct _ (PlainInstr (I64Load32S memArg)) = return $ S.I64Load32S memArg synInstrToStruct _ (PlainInstr (I64Load32U memArg)) = return $ S.I64Load32U memArg synInstrToStruct _ (PlainInstr (I32Store memArg)) = return $ S.I32Store memArg synInstrToStruct _ (PlainInstr (I64Store memArg)) = return $ S.I64Store memArg synInstrToStruct _ (PlainInstr (F32Store memArg)) = return $ S.F32Store memArg synInstrToStruct _ (PlainInstr (F64Store memArg)) = return $ S.F64Store memArg synInstrToStruct _ (PlainInstr (I32Store8 memArg)) = return $ S.I32Store8 memArg synInstrToStruct _ (PlainInstr (I32Store16 memArg)) = return $ S.I32Store16 memArg synInstrToStruct _ (PlainInstr (I64Store8 memArg)) = return $ S.I64Store8 memArg synInstrToStruct _ (PlainInstr (I64Store16 memArg)) = return $ S.I64Store16 memArg synInstrToStruct _ (PlainInstr (I64Store32 memArg)) = return $ S.I64Store32 memArg synInstrToStruct _ (PlainInstr CurrentMemory) = return $ S.CurrentMemory synInstrToStruct _ (PlainInstr GrowMemory) = return $ S.GrowMemory synInstrToStruct _ (PlainInstr (I32Const val)) = return $ S.I32Const $ integerToWord32 val synInstrToStruct _ (PlainInstr (I64Const val)) = return $ S.I64Const $ integerToWord64 val synInstrToStruct _ (PlainInstr (F32Const val)) = return $ S.F32Const val synInstrToStruct _ (PlainInstr (F64Const val)) = return $ S.F64Const val synInstrToStruct _ (PlainInstr (IUnOp sz op)) = return $ S.IUnOp sz op synInstrToStruct _ (PlainInstr (IBinOp sz op)) = return $ S.IBinOp sz op synInstrToStruct _ (PlainInstr I32Eqz) = return $ S.I32Eqz synInstrToStruct _ (PlainInstr I64Eqz) = return $ S.I64Eqz synInstrToStruct _ (PlainInstr (IRelOp sz op)) = return $ S.IRelOp sz op synInstrToStruct _ (PlainInstr (FUnOp sz op)) = return $ S.FUnOp sz op synInstrToStruct _ (PlainInstr (FBinOp sz op)) = return $ S.FBinOp sz op synInstrToStruct _ (PlainInstr (FRelOp sz op)) = return $ S.FRelOp sz op synInstrToStruct _ (PlainInstr I32WrapI64) = return $ S.I32WrapI64 synInstrToStruct _ (PlainInstr (ITruncFU sz sz')) = return $ S.ITruncFU sz sz' synInstrToStruct _ (PlainInstr (ITruncFS sz sz')) = return $ S.ITruncFS sz sz' synInstrToStruct _ (PlainInstr I64ExtendSI32) = return $ S.I64ExtendSI32 synInstrToStruct _ (PlainInstr I64ExtendUI32) = return $ S.I64ExtendUI32 synInstrToStruct _ (PlainInstr (FConvertIU sz sz')) = return $ S.FConvertIU sz sz' synInstrToStruct _ (PlainInstr (FConvertIS sz sz')) = return $ S.FConvertIS sz sz' synInstrToStruct _ (PlainInstr F32DemoteF64) = return $ S.F32DemoteF64 synInstrToStruct _ (PlainInstr F64PromoteF32) = return $ S.F64PromoteF32 synInstrToStruct _ (PlainInstr (IReinterpretF sz)) = return $ S.IReinterpretF sz synInstrToStruct _ (PlainInstr (FReinterpretI sz)) = return $ S.FReinterpretI sz synInstrToStruct ctx BlockInstr {label, resultType, body} = let ctx' = ctx { ctxLabels = label : ctxLabels ctx } in S.Block resultType <$> mapM (synInstrToStruct ctx') body synInstrToStruct ctx LoopInstr {label, resultType, body} = let ctx' = ctx { ctxLabels = label : ctxLabels ctx } in S.Loop resultType <$> mapM (synInstrToStruct ctx') body synInstrToStruct ctx IfInstr {label, resultType, trueBranch, falseBranch} = do let ctx' = ctx { ctxLabels = label : ctxLabels ctx } trueBranch' <- mapM (synInstrToStruct ctx') trueBranch falseBranch' <- mapM (synInstrToStruct ctx') falseBranch return $ S.If resultType trueBranch' falseBranch' synFunctionToStruct :: Module -> Function -> Either String S.Function synFunctionToStruct mod Function { funcType, locals, body } = do typeIdx <- ( case getTypeIndex (types mod) funcType of Just idx -> Right idx Nothing -> Left "Type was not found or type signature doesn't match with type" ) -- we have to use local func params declaration, -- coz it can contain own names for them let params = case funcType of IndexedTypeUse _ (Just FuncType { params }) -> params AnonimousTypeUse FuncType { params } -> params _ -> if fromIntegral typeIdx < length (types mod) then let TypeDef _ FuncType { params } = types mod !! fromIntegral typeIdx in params else [] let ctx = FunCtx mod [] locals params instructions <- mapM (synInstrToStruct ctx) body return S.Function { S.funcType = typeIdx, S.localTypes = map localType locals, S.body = instructions } extractFunction :: [Function] -> ModuleField -> [Function] extractFunction funcs (MFFunc fun) = fun : funcs extractFunction funcs _ = funcs getLabelIdx :: FunCtx -> LabelIndex -> Maybe Natural getLabelIdx FunCtx { ctxLabels } (Named id) = fromIntegral <$> findIndex (\ident -> ident == Just id) ctxLabels getLabelIdx FunCtx { ctxLabels } (Index idx) = Just idx getLocalIndex :: FunCtx -> LabelIndex -> Maybe Natural getLocalIndex FunCtx {ctxParams, ctxLocals} (Named id) = case findIndex (\(ParamType ident _) -> ident == Just id) ctxParams of Just idx -> return $ fromIntegral idx Nothing -> let isIdent (LocalType ident _) = ident == Just id in fromIntegral . (+ length ctxParams) <$> findIndex isIdent ctxLocals getLocalIndex FunCtx {ctxParams, ctxLocals} (Index idx) = Just idx isFuncImport :: Import -> Bool isFuncImport Import { desc = ImportFunc _ _ } = True isFuncImport _ = False getFuncIndex :: Module -> FuncIndex -> Maybe Natural getFuncIndex Module { imports, functions } (Named id) = let funImports = filter isFuncImport imports in case findIndex (\(Import { desc = ImportFunc ident _ }) -> ident == Just id) funImports of Just idx -> return $ fromIntegral idx Nothing -> let isIdent (Function { ident }) = ident == Just id in fromIntegral . (+ length funImports) <$> findIndex isIdent functions getFuncIndex Module { imports, functions } (Index idx) = Just idx -- tables synTableToStruct :: Table -> S.Table synTableToStruct (Table _ _ tableType) = S.Table tableType extractTable :: [Table] -> ModuleField -> [Table] extractTable tables (MFTable table) = table : tables extractTable tables _ = tables isTableImport :: Import -> Bool isTableImport Import { desc = ImportTable _ _ } = True isTableImport _ = False getTableIndex :: Module -> TableIndex -> Maybe Natural getTableIndex Module { imports, tables } (Named id) = let tableImports = filter isTableImport imports in case findIndex (\(Import { desc = ImportTable ident _ }) -> ident == Just id) tableImports of Just idx -> return $ fromIntegral idx Nothing -> let isIdent (Table _ (Just id) _) = True in fromIntegral . (+ length tableImports) <$> findIndex isIdent tables getTableIndex Module { imports, tables } (Index idx) = Just idx -- memory synMemoryToStruct :: Memory -> S.Memory synMemoryToStruct (Memory _ _ limits) = S.Memory limits extractMemory :: [Memory] -> ModuleField -> [Memory] extractMemory mems (MFMem mem) = mem : mems extractMemory mems _ = mems isMemImport :: Import -> Bool isMemImport Import { desc = ImportMemory _ _ } = True isMemImport _ = False getMemIndex :: Module -> MemoryIndex -> Maybe Natural getMemIndex Module { imports, mems } (Named id) = let memImports = filter isMemImport imports in case findIndex (\(Import { desc = ImportMemory ident _ }) -> ident == Just id) memImports of Just idx -> return $ fromIntegral idx Nothing -> let isIdent (Memory _ (Just id) _) = True in fromIntegral . (+ length memImports) <$> findIndex isIdent mems getMemIndex Module { imports, mems } (Index idx) = Just idx -- global synGlobalToStruct :: Module -> Global -> Either String S.Global synGlobalToStruct mod Global { globalType, initializer } = let ctx = FunCtx mod [] [] [] in S.Global globalType <$> mapM (synInstrToStruct ctx) initializer extractGlobal :: [Global] -> ModuleField -> [Global] extractGlobal globals (MFGlobal global) = global : globals extractGlobal globals _ = globals isGlobalImport :: Import -> Bool isGlobalImport Import { desc = ImportGlobal _ _ } = True isGlobalImport _ = False getGlobalIndex :: Module -> GlobalIndex -> Maybe Natural getGlobalIndex Module { imports, globals } (Named id) = let globalImports = filter isGlobalImport imports in case findIndex (\(Import { desc = ImportGlobal ident _ }) -> ident == Just id) globalImports of Just idx -> return $ fromIntegral idx Nothing -> let isIdent (Global { ident }) = ident == Just id in fromIntegral . (+ length globalImports) <$> findIndex isIdent globals getGlobalIndex Module { imports, globals } (Index idx) = Just idx -- elem segment synElemToStruct :: Module -> ElemSegment -> Either String S.ElemSegment synElemToStruct mod ElemSegment { tableIndex, offset, funcIndexes } = let ctx = FunCtx mod [] [] [] in let offsetInstrs = mapM (synInstrToStruct ctx) offset in let idx = fromJust $ getTableIndex mod tableIndex in let indexes = map (fromJust . getFuncIndex mod) funcIndexes in S.ElemSegment idx <$> offsetInstrs <*> return indexes extractElemSegment :: [ElemSegment] -> ModuleField -> [ElemSegment] extractElemSegment elems (MFElem elem) = elem : elems extractElemSegment elems _ = elems -- data segment synDataToStruct :: Module -> DataSegment -> Either String S.DataSegment synDataToStruct mod DataSegment { memIndex, offset, datastring } = let ctx = FunCtx mod [] [] [] in let offsetInstrs = mapM (synInstrToStruct ctx) offset in let idx = fromJust $ getMemIndex mod memIndex in S.DataSegment idx <$> offsetInstrs <*> return datastring extractDataSegment :: [DataSegment] -> ModuleField -> [DataSegment] extractDataSegment datas (MFData dataSegment) = dataSegment : datas extractDataSegment datas _ = datas -- start synStartToStruct :: Module -> StartFunction -> S.StartFunction synStartToStruct mod (StartFunction funIdx) = S.StartFunction $ fromJust $ getFuncIndex mod funIdx extractStart :: [ModuleField] -> Maybe StartFunction extractStart = foldl' extractStart' Nothing extractStart' :: Maybe StartFunction -> ModuleField -> Maybe StartFunction extractStart' _ (MFStart start) = Just start extractStart' start _ = start -- exports extractExports :: Module -> [ModuleField] -> [ModuleField] extractExports mod mf = let initial = (funcImportLength, globImportLength, memImportLength, tableImportLength, []) in let (_, _, _, _, result) = foldl' extractExport initial mf in reverse result where funcImportLength = fromIntegral $ length $ filter isFuncImport $ imports mod globImportLength = fromIntegral $ length $ filter isGlobalImport $ imports mod memImportLength = fromIntegral $ length $ filter isMemImport $ imports mod tableImportLength = fromIntegral $ length $ filter isTableImport $ imports mod extractExport (fidx, gidx, midx, tidx, mf) (MFFunc fun@Function{ exportFuncAs }) = let exports = map (\name -> MFExport $ Export name $ ExportFunc $ Index fidx) exportFuncAs in (fidx + 1, gidx, midx, tidx, [MFFunc fun] ++ exports ++ mf) extractExport (fidx, gidx, midx, tidx, mf) (MFGlobal glob@Global{ exportGlobalAs }) = let exports = map (\name -> MFExport $ Export name $ ExportGlobal $ Index gidx) exportGlobalAs in (fidx, gidx + 1, midx, tidx, [MFGlobal glob] ++ exports ++ mf) extractExport (fidx, gidx, midx, tidx, mf) (MFMem (Memory exps i l)) = let exports = map (\name -> MFExport $ Export name $ ExportMemory $ Index midx) exps in (fidx, gidx, midx + 1, tidx, [MFMem (Memory exps i l)] ++ exports ++ mf) extractExport (fidx, gidx, midx, tidx, mf) (MFTable (Table exps i t)) = let exports = map (\name -> MFExport $ Export name $ ExportTable $ Index tidx) exps in (fidx, gidx, midx, tidx + 1, [MFTable (Table exps i t)] ++ exports ++ mf) extractExport (fidx, gidx, midx, tidx, mf) f = (fidx, gidx, midx, tidx, f:mf) synExportsToStruct :: Module -> [ModuleField] -> [S.Export] synExportsToStruct mod (MFExport Export { name, desc = ExportFunc idx } : rest) = let exp = S.Export name $ S.ExportFunc $ fromJust $ getFuncIndex mod idx in exp : synExportsToStruct mod rest synExportsToStruct mod (MFExport Export { name, desc = ExportTable idx } : rest) = let exp = S.Export name $ S.ExportTable $ fromJust $ getTableIndex mod idx in exp : synExportsToStruct mod rest synExportsToStruct mod (MFExport Export { name, desc = ExportMemory idx } : rest) = let exp = S.Export name $ S.ExportMemory $ fromJust $ getMemIndex mod idx in exp : synExportsToStruct mod rest synExportsToStruct mod (MFExport Export { name, desc = ExportGlobal idx } : rest) = let exp = S.Export name $ S.ExportGlobal $ fromJust $ getGlobalIndex mod idx in exp : synExportsToStruct mod rest synExportsToStruct mod (_ : rest) = synExportsToStruct mod rest synExportsToStruct _ [] = [] {-# LINE 1 "templates/GenericTemplate.hs" #-} -- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp -- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex. #if __GLASGOW_HASKELL__ > 706 #define LT(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# m)) :: Bool) #define GTE(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.>=# m)) :: Bool) #define EQ(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.==# m)) :: Bool) #else #define LT(n,m) (n Happy_GHC_Exts.<# m) #define GTE(n,m) (n Happy_GHC_Exts.>=# m) #define EQ(n,m) (n Happy_GHC_Exts.==# m) #endif data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList infixr 9 `HappyStk` data HappyStk a = HappyStk a (HappyStk a) ----------------------------------------------------------------------------- -- starting the parse happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll ----------------------------------------------------------------------------- -- Accepting the parse -- If the current token is 0#, it means we've just accepted a partial -- parse (a %partial parser). We must ignore the saved token on the top of -- the stack in this case. happyAccept 0# tk st sts (_ `HappyStk` ans `HappyStk` _) = happyReturn1 ans happyAccept j tk st sts (HappyStk ans _) = (happyTcHack j (happyTcHack st)) (happyReturn1 ans) ----------------------------------------------------------------------------- -- Arrays only: do the next action happyDoAction i tk st = {- nothing -} case action of 0# -> {- nothing -} happyFail (happyExpListPerState ((Happy_GHC_Exts.I# (st)) :: Int)) i tk st -1# -> {- nothing -} happyAccept i tk st n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -} (happyReduceArr Happy_Data_Array.! rule) i tk st where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#)))))) n -> {- nothing -} happyShift new_state i tk st where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) where off = happyAdjustOffset (indexShortOffAddr happyActOffsets st) off_i = (off Happy_GHC_Exts.+# i) check = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#)) then EQ(indexShortOffAddr happyCheck off_i, i) else False action | check = indexShortOffAddr happyTable off_i | otherwise = indexShortOffAddr happyDefActions st indexShortOffAddr (HappyA# arr) off = Happy_GHC_Exts.narrow16Int# i where i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low) high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#))) low = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off')) off' = off Happy_GHC_Exts.*# 2# {-# INLINE happyLt #-} happyLt x y = LT(x,y) readArrayBit arr bit = Bits.testBit (Happy_GHC_Exts.I# (indexShortOffAddr arr ((unbox_int bit) `Happy_GHC_Exts.iShiftRA#` 4#))) (bit `mod` 16) where unbox_int (Happy_GHC_Exts.I# x) = x data HappyAddr = HappyA# Happy_GHC_Exts.Addr# ----------------------------------------------------------------------------- -- HappyState data type (not arrays) ----------------------------------------------------------------------------- -- Shifting a token happyShift new_state 0# tk st sts stk@(x `HappyStk` _) = let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in -- trace "shifting the error token" $ happyDoAction i tk new_state (HappyCons (st) (sts)) (stk) happyShift new_state i tk st sts stk = happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk) -- happyReduce is specialised for the common cases. happySpecReduce_0 i fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happySpecReduce_0 nt fn j tk st@((action)) sts stk = happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk) happySpecReduce_1 i fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk') = let r = fn v1 in happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk')) happySpecReduce_2 i fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk') = let r = fn v1 v2 in happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk')) happySpecReduce_3 i fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk') = let r = fn v1 v2 v3 in happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk')) happyReduce k i fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happyReduce k nt fn j tk st sts stk = case happyDrop (k Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) sts of sts1@((HappyCons (st1@(action)) (_))) -> let r = fn stk in -- it doesn't hurt to always seq here... happyDoSeq r (happyGoto nt j tk st1 sts1 r) happyMonadReduce k nt fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happyMonadReduce k nt fn j tk st sts stk = case happyDrop k (HappyCons (st) (sts)) of sts1@((HappyCons (st1@(action)) (_))) -> let drop_stk = happyDropStk k stk in happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk)) happyMonad2Reduce k nt fn 0# tk st sts stk = happyFail [] 0# tk st sts stk happyMonad2Reduce k nt fn j tk st sts stk = case happyDrop k (HappyCons (st) (sts)) of sts1@((HappyCons (st1@(action)) (_))) -> let drop_stk = happyDropStk k stk off = happyAdjustOffset (indexShortOffAddr happyGotoOffsets st1) off_i = (off Happy_GHC_Exts.+# nt) new_state = indexShortOffAddr happyTable off_i in happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk)) happyDrop 0# l = l happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t happyDropStk 0# l = l happyDropStk n (x `HappyStk` xs) = happyDropStk (n Happy_GHC_Exts.-# (1#::Happy_GHC_Exts.Int#)) xs ----------------------------------------------------------------------------- -- Moving to a new state after a reduction happyGoto nt j tk st = {- nothing -} happyDoAction j tk new_state where off = happyAdjustOffset (indexShortOffAddr happyGotoOffsets st) off_i = (off Happy_GHC_Exts.+# nt) new_state = indexShortOffAddr happyTable off_i ----------------------------------------------------------------------------- -- Error recovery (0# is the error token) -- parse error if we are in recovery and we fail again happyFail explist 0# tk old_st _ stk@(x `HappyStk` _) = let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in -- trace "failing" $ happyError_ explist i tk {- We don't need state discarding for our restricted implementation of "error". In fact, it can cause some bogus parses, so I've disabled it for now --SDM -- discard a state happyFail 0# tk old_st (HappyCons ((action)) (sts)) (saved_tok `HappyStk` _ `HappyStk` stk) = -- trace ("discarding state, depth " ++ show (length stk)) $ happyDoAction 0# tk action sts ((saved_tok`HappyStk`stk)) -} -- Enter error recovery: generate an error token, -- save the old token and carry on. happyFail explist i tk (action) sts stk = -- trace "entering error recovery" $ happyDoAction 0# tk action sts ( (Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk) -- Internal happy errors: notHappyAtAll :: a notHappyAtAll = error "Internal Happy error\n" ----------------------------------------------------------------------------- -- Hack to get the typechecker to accept our action functions happyTcHack :: Happy_GHC_Exts.Int# -> a -> a happyTcHack x y = y {-# INLINE happyTcHack #-} ----------------------------------------------------------------------------- -- Seq-ing. If the --strict flag is given, then Happy emits -- happySeq = happyDoSeq -- otherwise it emits -- happySeq = happyDontSeq happyDoSeq, happyDontSeq :: a -> b -> b happyDoSeq a b = a `seq` b happyDontSeq a b = b ----------------------------------------------------------------------------- -- Don't inline any functions from the template. GHC has a nasty habit -- of deciding to inline happyGoto everywhere, which increases the size of -- the generated parser quite a bit. {-# NOINLINE happyDoAction #-} {-# NOINLINE happyTable #-} {-# NOINLINE happyCheck #-} {-# NOINLINE happyActOffsets #-} {-# NOINLINE happyGotoOffsets #-} {-# NOINLINE happyDefActions #-} {-# NOINLINE happyShift #-} {-# NOINLINE happySpecReduce_0 #-} {-# NOINLINE happySpecReduce_1 #-} {-# NOINLINE happySpecReduce_2 #-} {-# NOINLINE happySpecReduce_3 #-} {-# NOINLINE happyReduce #-} {-# NOINLINE happyMonadReduce #-} {-# NOINLINE happyGoto #-} {-# NOINLINE happyFail #-} -- end of Happy Template.