{-# OPTIONS_GHC -w #-}
{-# OPTIONS -fglasgow-exts -cpp #-}
{-# LANGUAGE TupleSections #-}

{-| The parser is generated by Happy (<http://www.haskell.org/happy>).
 -
 - Ideally, ranges should be as precise as possible, to get messages that
 - emphasize precisely the faulting term(s) upon error.
 -
 - However, interactive highlighting is only applied at the end of each
 - mutual block, keywords are only highlighted once (see
 - `TypeChecking.Rules.Decl'). So if the ranges of two declarations
 - interleave, one must ensure that keyword ranges are not included in
 - the intersection. (Otherwise they are uncolored by the interactive
 - highlighting.)
 -
 -}
module Agda.Syntax.Parser.Parser (
      moduleParser
    , moduleNameParser
    , exprParser
    , exprWhereParser
    , tokensParser
    , tests
    ) where

import Control.Monad

import Data.Char
import Data.Functor
import Data.List
import Data.Maybe
import Data.Monoid
import qualified Data.Traversable as T

import Debug.Trace

import Agda.Syntax.Position hiding (tests)
import Agda.Syntax.Parser.Monad
import Agda.Syntax.Parser.Lexer
import Agda.Syntax.Parser.Tokens
import Agda.Syntax.Concrete as C
import Agda.Syntax.Concrete.Pretty ()
import Agda.Syntax.Common
import Agda.Syntax.Fixity
import Agda.Syntax.Notation
import Agda.Syntax.Literal

import Agda.Utils.Either hiding (tests)
import Agda.Utils.Hash
import Agda.Utils.List (spanJust)
import Agda.Utils.Monad
import Agda.Utils.Pretty
import Agda.Utils.QuickCheck
import Agda.Utils.Singleton
import Agda.Utils.TestHelpers
import Agda.Utils.Tuple

import Agda.Utils.Impossible
#include "undefined.h"
import qualified Data.Array as Happy_Data_Array
import qualified GHC.Exts as Happy_GHC_Exts
import Control.Applicative(Applicative(..))

-- parser produced by Happy Version 1.19.4

newtype HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83 = HappyAbsSyn HappyAny
#if __GLASGOW_HASKELL__ >= 607
type HappyAny = Happy_GHC_Exts.Any
#else
type HappyAny = forall a . a
#endif
happyIn9 :: ([Token]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn9 #-}
happyOut9 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Token])
happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut9 #-}
happyIn10 :: ([Token]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn10 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn10 #-}
happyOut10 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Token])
happyOut10 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut10 #-}
happyIn11 :: (Token) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn11 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn11 #-}
happyOut11 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Token)
happyOut11 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut11 #-}
happyIn12 :: (([Pragma], [Declaration])) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn12 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn12 #-}
happyOut12 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (([Pragma], [Declaration]))
happyOut12 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut12 #-}
happyIn13 :: t13 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn13 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn13 #-}
happyOut13 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t13
happyOut13 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut13 #-}
happyIn14 :: t14 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn14 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn14 #-}
happyOut14 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t14
happyOut14 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut14 #-}
happyIn15 :: t15 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn15 #-}
happyOut15 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t15
happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut15 #-}
happyIn16 :: (()) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn16 #-}
happyOut16 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (())
happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut16 #-}
happyIn17 :: (Integer) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn17 #-}
happyOut17 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Integer)
happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut17 #-}
happyIn18 :: (Name) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn18 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn18 #-}
happyOut18 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Name)
happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut18 #-}
happyIn19 :: ([Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn19 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn19 #-}
happyOut19 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Name])
happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut19 #-}
happyIn20 :: (Range) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn20 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn20 #-}
happyOut20 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Range)
happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut20 #-}
happyIn21 :: (Arg Name) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn21 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn21 #-}
happyOut21 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Arg Name)
happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut21 #-}
happyIn22 :: ([Arg Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn22 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn22 #-}
happyOut22 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Arg Name])
happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut22 #-}
happyIn23 :: ([Arg Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn23 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn23 #-}
happyOut23 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Arg Name])
happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut23 #-}
happyIn24 :: (QName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn24 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn24 #-}
happyOut24 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (QName)
happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut24 #-}
happyIn25 :: (QName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn25 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn25 #-}
happyOut25 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (QName)
happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut25 #-}
happyIn26 :: (Name) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn26 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn26 #-}
happyOut26 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Name)
happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut26 #-}
happyIn27 :: ([Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn27 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn27 #-}
happyOut27 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Name])
happyOut27 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut27 #-}
happyIn28 :: ([Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn28 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn28 #-}
happyOut28 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Name])
happyOut28 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut28 #-}
happyIn29 :: (Either [Name] [Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn29 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn29 #-}
happyOut29 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Either [Name] [Expr])
happyOut29 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut29 #-}
happyIn30 :: ([WithHiding Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn30 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn30 #-}
happyOut30 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([WithHiding Name])
happyOut30 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut30 #-}
happyIn31 :: ([String]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn31 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn31 #-}
happyOut31 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([String])
happyOut31 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut31 #-}
happyIn32 :: (String) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn32 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn32 #-}
happyOut32 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (String)
happyOut32 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut32 #-}
happyIn33 :: ([(Interval, String)]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn33 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn33 #-}
happyOut33 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([(Interval, String)])
happyOut33 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut33 #-}
happyIn34 :: (Name) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn34 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn34 #-}
happyOut34 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Name)
happyOut34 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut34 #-}
happyIn35 :: (QName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn35 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn35 #-}
happyOut35 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (QName)
happyOut35 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut35 #-}
happyIn36 :: (Expr) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn36 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn36 #-}
happyOut36 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Expr)
happyOut36 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut36 #-}
happyIn37 :: t37 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn37 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn37 #-}
happyOut37 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t37
happyOut37 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut37 #-}
happyIn38 :: ([Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn38 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn38 #-}
happyOut38 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Expr])
happyOut38 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut38 #-}
happyIn39 :: ([Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn39 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn39 #-}
happyOut39 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Expr])
happyOut39 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut39 #-}
happyIn40 :: t40 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn40 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn40 #-}
happyOut40 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t40
happyOut40 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut40 #-}
happyIn41 :: (Expr) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn41 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn41 #-}
happyOut41 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Expr)
happyOut41 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut41 #-}
happyIn42 :: ([Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn42 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn42 #-}
happyOut42 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Expr])
happyOut42 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut42 #-}
happyIn43 :: t43 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn43 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn43 #-}
happyOut43 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t43
happyOut43 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut43 #-}
happyIn44 :: t44 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn44 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn44 #-}
happyOut44 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t44
happyOut44 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut44 #-}
happyIn45 :: t45 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn45 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn45 #-}
happyOut45 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t45
happyOut45 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut45 #-}
happyIn46 :: (RecordAssignments) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn46 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn46 #-}
happyOut46 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (RecordAssignments)
happyOut46 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut46 #-}
happyIn47 :: (RecordAssignments) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn47 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn47 #-}
happyOut47 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (RecordAssignments)
happyOut47 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut47 #-}
happyIn48 :: (RecordAssignment) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn48 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn48 #-}
happyOut48 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (RecordAssignment)
happyOut48 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut48 #-}
happyIn49 :: (ModuleAssignment) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn49 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn49 #-}
happyOut49 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (ModuleAssignment)
happyOut49 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut49 #-}
happyIn50 :: ([FieldAssignment]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn50 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn50 #-}
happyOut50 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([FieldAssignment])
happyOut50 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut50 #-}
happyIn51 :: ([FieldAssignment]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn51 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn51 #-}
happyOut51 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([FieldAssignment])
happyOut51 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut51 #-}
happyIn52 :: (FieldAssignment) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn52 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn52 #-}
happyOut52 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (FieldAssignment)
happyOut52 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut52 #-}
happyIn53 :: t53 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn53 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn53 #-}
happyOut53 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t53
happyOut53 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut53 #-}
happyIn54 :: t54 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn54 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn54 #-}
happyOut54 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t54
happyOut54 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut54 #-}
happyIn55 :: ([TypedBindings]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn55 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn55 #-}
happyOut55 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([TypedBindings])
happyOut55 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut55 #-}
happyIn56 :: (TypedBindings) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn56 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn56 #-}
happyOut56 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (TypedBindings)
happyOut56 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut56 #-}
happyIn57 :: (TypedBindings) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn57 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn57 #-}
happyOut57 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (TypedBindings)
happyOut57 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut57 #-}
happyIn58 :: (TypedBindings) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn58 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn58 #-}
happyOut58 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (TypedBindings)
happyOut58 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut58 #-}
happyIn59 :: ([LamBinding]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn59 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn59 #-}
happyOut59 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([LamBinding])
happyOut59 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut59 #-}
happyIn60 :: (Either ([LamBinding], Hiding) [Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn60 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn60 #-}
happyOut60 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Either ([LamBinding], Hiding) [Expr])
happyOut60 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut60 #-}
happyIn61 :: ([Either Hiding LamBinding]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn61 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn61 #-}
happyOut61 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Either Hiding LamBinding])
happyOut61 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut61 #-}
happyIn62 :: (Either [Either Hiding LamBinding] [Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn62 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn62 #-}
happyOut62 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Either [Either Hiding LamBinding] [Expr])
happyOut62 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut62 #-}
happyIn63 :: ((LHS,RHS,WhereClause,Bool)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn63 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn63 #-}
happyOut63 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ((LHS,RHS,WhereClause,Bool))
happyOut63 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut63 #-}
happyIn64 :: ((LHS,RHS,WhereClause,Bool)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn64 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn64 #-}
happyOut64 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ((LHS,RHS,WhereClause,Bool))
happyOut64 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut64 #-}
happyIn65 :: ((LHS,RHS,WhereClause,Bool)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn65 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn65 #-}
happyOut65 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ((LHS,RHS,WhereClause,Bool))
happyOut65 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut65 #-}
happyIn66 :: ([(LHS,RHS,WhereClause,Bool)]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn66 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn66 #-}
happyOut66 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([(LHS,RHS,WhereClause,Bool)])
happyOut66 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut66 #-}
happyIn67 :: ([LamBinding]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn67 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn67 #-}
happyOut67 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([LamBinding])
happyOut67 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut67 #-}
happyIn68 :: ([LamBinding]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn68 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn68 #-}
happyOut68 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([LamBinding])
happyOut68 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut68 #-}
happyIn69 :: ([LamBinding]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn69 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn69 #-}
happyOut69 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([LamBinding])
happyOut69 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut69 #-}
happyIn70 :: ([LamBinding]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn70 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn70 #-}
happyOut70 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([LamBinding])
happyOut70 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut70 #-}
happyIn71 :: (Either [LamBinding] [Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn71 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn71 #-}
happyOut71 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Either [LamBinding] [Expr])
happyOut71 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut71 #-}
happyIn72 :: (ImportDirective) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn72 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn72 #-}
happyOut72 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (ImportDirective)
happyOut72 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut72 #-}
happyIn73 :: ([ImportDirective]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn73 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn73 #-}
happyOut73 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([ImportDirective])
happyOut73 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut73 #-}
happyIn74 :: (ImportDirective) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn74 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn74 #-}
happyOut74 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (ImportDirective)
happyOut74 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut74 #-}
happyIn75 :: ((Using, Range)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn75 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn75 #-}
happyOut75 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ((Using, Range))
happyOut75 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut75 #-}
happyIn76 :: (([ImportedName], Range)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn76 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn76 #-}
happyOut76 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (([ImportedName], Range))
happyOut76 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut76 #-}
happyIn77 :: (([Renaming] , Range)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn77 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn77 #-}
happyOut77 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (([Renaming] , Range))
happyOut77 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut77 #-}
happyIn78 :: ([Renaming]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn78 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn78 #-}
happyOut78 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Renaming])
happyOut78 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut78 #-}
happyIn79 :: (Renaming) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn79 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn79 #-}
happyOut79 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Renaming)
happyOut79 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut79 #-}
happyIn80 :: (ImportedName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn80 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn80 #-}
happyOut80 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (ImportedName)
happyOut80 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut80 #-}
happyIn81 :: (ImportedName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn81 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn81 #-}
happyOut81 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (ImportedName)
happyOut81 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut81 #-}
happyIn82 :: ([ImportedName]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn82 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn82 #-}
happyOut82 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([ImportedName])
happyOut82 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut82 #-}
happyIn83 :: t83 -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn83 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn83 #-}
happyOut83 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> t83
happyOut83 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut83 #-}
happyIn84 :: (LHS) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn84 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn84 #-}
happyOut84 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (LHS)
happyOut84 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut84 #-}
happyIn85 :: ([Pattern]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn85 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn85 #-}
happyOut85 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Pattern])
happyOut85 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut85 #-}
happyIn86 :: ([Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn86 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn86 #-}
happyOut86 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Expr])
happyOut86 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut86 #-}
happyIn87 :: ([Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn87 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn87 #-}
happyOut87 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Expr])
happyOut87 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut87 #-}
happyIn88 :: (WhereClause) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn88 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn88 #-}
happyOut88 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (WhereClause)
happyOut88 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut88 #-}
happyIn89 :: (ExprWhere) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn89 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn89 #-}
happyOut89 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (ExprWhere)
happyOut89 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut89 #-}
happyIn90 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn90 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn90 #-}
happyOut90 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut90 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut90 #-}
happyIn91 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn91 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn91 #-}
happyOut91 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut91 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut91 #-}
happyIn92 :: ([Arg Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn92 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn92 #-}
happyOut92 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Arg Declaration])
happyOut92 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut92 #-}
happyIn93 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn93 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn93 #-}
happyOut93 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut93 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut93 #-}
happyIn94 :: (RHSOrTypeSigs) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn94 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn94 #-}
happyOut94 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (RHSOrTypeSigs)
happyOut94 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut94 #-}
happyIn95 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn95 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn95 #-}
happyOut95 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut95 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut95 #-}
happyIn96 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn96 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn96 #-}
happyOut96 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut96 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut96 #-}
happyIn97 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn97 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn97 #-}
happyOut97 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut97 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut97 #-}
happyIn98 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn98 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn98 #-}
happyOut98 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut98 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut98 #-}
happyIn99 :: ((Name, IsInstance)) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn99 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn99 #-}
happyOut99 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ((Name, IsInstance))
happyOut99 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut99 #-}
happyIn100 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn100 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn100 #-}
happyOut100 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut100 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut100 #-}
happyIn101 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn101 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn101 #-}
happyOut101 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut101 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut101 #-}
happyIn102 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn102 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn102 #-}
happyOut102 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut102 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut102 #-}
happyIn103 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn103 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn103 #-}
happyOut103 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut103 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut103 #-}
happyIn104 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn104 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn104 #-}
happyOut104 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut104 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut104 #-}
happyIn105 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn105 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn105 #-}
happyOut105 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut105 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut105 #-}
happyIn106 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn106 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn106 #-}
happyOut106 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut106 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut106 #-}
happyIn107 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn107 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn107 #-}
happyOut107 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut107 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut107 #-}
happyIn108 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn108 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn108 #-}
happyOut108 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut108 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut108 #-}
happyIn109 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn109 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn109 #-}
happyOut109 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut109 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut109 #-}
happyIn110 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn110 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn110 #-}
happyOut110 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut110 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut110 #-}
happyIn111 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn111 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn111 #-}
happyOut111 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut111 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut111 #-}
happyIn112 :: ([Arg Name]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn112 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn112 #-}
happyOut112 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Arg Name])
happyOut112 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut112 #-}
happyIn113 :: ([RString]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn113 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn113 #-}
happyOut113 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([RString])
happyOut113 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut113 #-}
happyIn114 :: ([NamedArg HoleName]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn114 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn114 #-}
happyOut114 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([NamedArg HoleName])
happyOut114 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut114 #-}
happyIn115 :: (NamedArg HoleName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn115 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn115 #-}
happyOut115 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (NamedArg HoleName)
happyOut115 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut115 #-}
happyIn116 :: (HoleName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn116 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn116 #-}
happyOut116 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (HoleName)
happyOut116 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut116 #-}
happyIn117 :: (HoleName) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn117 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn117 #-}
happyOut117 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (HoleName)
happyOut117 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut117 #-}
happyIn118 :: (RString) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn118 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn118 #-}
happyOut118 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (RString)
happyOut118 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut118 #-}
happyIn119 :: (Maybe Range) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn119 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn119 #-}
happyOut119 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Maybe Range)
happyOut119 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut119 #-}
happyIn120 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn120 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn120 #-}
happyOut120 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut120 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut120 #-}
happyIn121 :: ([Expr]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn121 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn121 #-}
happyOut121 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Expr])
happyOut121 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut121 #-}
happyIn122 :: ([TypedBindings] -> Parser ModuleApplication) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn122 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn122 #-}
happyOut122 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([TypedBindings] -> Parser ModuleApplication)
happyOut122 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut122 #-}
happyIn123 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn123 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn123 #-}
happyOut123 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut123 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut123 #-}
happyIn124 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn124 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn124 #-}
happyOut124 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut124 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut124 #-}
happyIn125 :: (Name) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn125 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn125 #-}
happyOut125 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Name)
happyOut125 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut125 #-}
happyIn126 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn126 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn126 #-}
happyOut126 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut126 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut126 #-}
happyIn127 :: (Declaration) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn127 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn127 #-}
happyOut127 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Declaration)
happyOut127 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut127 #-}
happyIn128 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn128 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn128 #-}
happyOut128 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut128 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut128 #-}
happyIn129 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn129 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn129 #-}
happyOut129 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut129 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut129 #-}
happyIn130 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn130 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn130 #-}
happyOut130 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut130 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut130 #-}
happyIn131 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn131 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn131 #-}
happyOut131 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut131 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut131 #-}
happyIn132 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn132 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn132 #-}
happyOut132 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut132 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut132 #-}
happyIn133 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn133 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn133 #-}
happyOut133 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut133 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut133 #-}
happyIn134 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn134 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn134 #-}
happyOut134 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut134 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut134 #-}
happyIn135 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn135 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn135 #-}
happyOut135 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut135 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut135 #-}
happyIn136 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn136 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn136 #-}
happyOut136 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut136 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut136 #-}
happyIn137 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn137 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn137 #-}
happyOut137 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut137 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut137 #-}
happyIn138 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn138 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn138 #-}
happyOut138 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut138 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut138 #-}
happyIn139 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn139 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn139 #-}
happyOut139 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut139 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut139 #-}
happyIn140 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn140 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn140 #-}
happyOut140 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut140 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut140 #-}
happyIn141 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn141 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn141 #-}
happyOut141 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut141 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut141 #-}
happyIn142 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn142 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn142 #-}
happyOut142 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut142 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut142 #-}
happyIn143 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn143 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn143 #-}
happyOut143 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut143 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut143 #-}
happyIn144 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn144 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn144 #-}
happyOut144 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut144 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut144 #-}
happyIn145 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn145 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn145 #-}
happyOut145 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut145 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut145 #-}
happyIn146 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn146 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn146 #-}
happyOut146 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut146 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut146 #-}
happyIn147 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn147 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn147 #-}
happyOut147 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut147 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut147 #-}
happyIn148 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn148 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn148 #-}
happyOut148 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut148 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut148 #-}
happyIn149 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn149 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn149 #-}
happyOut149 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut149 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut149 #-}
happyIn150 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn150 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn150 #-}
happyOut150 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut150 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut150 #-}
happyIn151 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn151 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn151 #-}
happyOut151 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut151 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut151 #-}
happyIn152 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn152 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn152 #-}
happyOut152 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut152 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut152 #-}
happyIn153 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn153 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn153 #-}
happyOut153 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut153 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut153 #-}
happyIn154 :: (Pragma) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn154 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn154 #-}
happyOut154 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Pragma)
happyOut154 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut154 #-}
happyIn155 :: ([TypeSignature]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn155 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn155 #-}
happyOut155 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([TypeSignature])
happyOut155 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut155 #-}
happyIn156 :: ([TypeSignature]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn156 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn156 #-}
happyOut156 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([TypeSignature])
happyOut156 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut156 #-}
happyIn157 :: ([Arg TypeSignature]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn157 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn157 #-}
happyOut157 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Arg TypeSignature])
happyOut157 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut157 #-}
happyIn158 :: ([Arg TypeSignature]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn158 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn158 #-}
happyOut158 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Arg TypeSignature])
happyOut158 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut158 #-}
happyIn159 :: (((Maybe (Ranged Induction), Maybe Bool, Maybe (Name, IsInstance)), [Declaration])) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn159 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn159 #-}
happyOut159 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (((Maybe (Ranged Induction), Maybe Bool, Maybe (Name, IsInstance)), [Declaration]))
happyOut159 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut159 #-}
happyIn160 :: ([RecordDirective]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn160 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn160 #-}
happyOut160 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([RecordDirective])
happyOut160 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut160 #-}
happyIn161 :: (RecordDirective) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn161 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn161 #-}
happyOut161 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (RecordDirective)
happyOut161 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut161 #-}
happyIn162 :: (Ranged Bool) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn162 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn162 #-}
happyOut162 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Ranged Bool)
happyOut162 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut162 #-}
happyIn163 :: (Ranged Induction) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn163 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn163 #-}
happyOut163 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Ranged Induction)
happyOut163 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut163 #-}
happyIn164 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn164 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn164 #-}
happyOut164 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut164 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut164 #-}
happyIn165 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn165 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn165 #-}
happyOut165 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut165 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut165 #-}
happyIn166 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn166 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn166 #-}
happyOut166 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut166 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut166 #-}
happyIn167 :: ([Declaration]) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyIn167 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn167 #-}
happyOut167 :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> ([Declaration])
happyOut167 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut167 #-}
happyInTok :: (Token) -> (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83)
happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyInTok #-}
happyOutTok :: (HappyAbsSyn t13 t14 t15 t37 t40 t43 t44 t45 t53 t54 t83) -> (Token)
happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOutTok #-}


happyActOffsets :: HappyAddr
happyActOffsets = HappyA# "\x00\x00\x5c\x0b\x5c\x0b\x34\x07\xef\x04\x11\x0b\x00\x00\xbe\x04\x37\x07\x00\x00\x65\x07\x00\x00\x00\x00\x00\x00\x00\x00\x31\x07\x00\x00\x00\x00\x65\x09\xff\x04\x25\x07\xd0\x09\x2c\x07\x00\x00\x00\x00\x00\x00\x23\x07\x00\x00\xfb\x0c\x00\x00\xe4\x0c\x00\x00\x00\x00\x2a\x07\xe4\x0c\x00\x00\x00\x00\x92\x09\x46\x09\x4a\x07\xf9\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1b\x07\x1b\x07\x58\x04\x87\x00\x2e\x07\x5a\x01\xf2\x0a\x28\x07\x00\x00\x1b\x02\x14\x07\xf2\x03\x9b\x0c\x2b\x07\xdd\x06\xf9\x08\x14\x07\x14\x07\x26\x07\x00\x00\x1d\x07\x8a\x01\x1a\x07\x00\x00\x00\x00\xde\x01\xde\x01\x00\x00\x18\x07\x1e\x07\x19\x07\x65\x00\x17\x07\x5c\x07\x08\x07\x06\x07\xe3\x04\x00\x00\x00\x00\xda\x08\xdd\x06\x8d\x08\x7b\x0b\x7b\x0b\x7b\x0b\x00\x00\x1a\x03\xa7\x0a\x7b\x0b\x7b\x0b\x00\x00\x00\x00\x88\x0a\x7b\x0b\x88\x0a\x00\x00\x4f\x01\x05\x07\xe7\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\x03\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\x02\x07\xfc\x06\xfc\x06\xf0\x06\xeb\x06\xeb\x06\xeb\x06\xea\x06\xea\x06\xdd\xff\xea\x06\x2f\x00\xe2\x06\xe8\x06\xe6\x06\xe1\x06\x84\x0c\xdb\x06\x8f\x00\xdb\x06\xee\x11\x00\x00\x00\x00\x4e\x08\x88\x0a\x00\x00\xe7\x06\x00\x00\x26\x09\xe1\x07\xd0\x03\x29\x03\x00\x00\x6e\x08\x20\x08\x01\x08\x12\x07\x3b\x0c\xe5\x06\x3b\x0c\xd7\x06\xe3\x04\x22\x07\x21\x07\x52\x06\xba\x08\x88\x0a\xd8\x06\xba\x08\x00\x00\x7b\x0b\x7b\x0b\x87\x00\x88\x0a\x88\x0a\x00\x00\x00\x00\xfa\x06\x7b\x0b\x3b\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\x88\x0a\x00\x00\x00\x00\x00\x00\xca\x06\x00\x00\x7b\x0b\xe1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x88\x0a\x88\x0a\xd4\x06\x3b\x0c\xc6\x06\x00\x00\xd1\x06\x00\x00\x00\x00\xbc\x06\x7b\x0b\xc5\x06\xe4\x06\x26\x01\xc3\x06\x00\x00\xe7\xff\x02\x01\x7b\x0b\xc1\x06\xde\x06\xb9\x06\x00\x00\xb4\x06\x00\x00\x7b\x0b\x7b\x0b\x7b\x0b\x00\x00\x7b\x0b\x7b\x0b\x00\x08\x9a\x06\x00\x08\xb6\x07\x97\x07\x3b\x0a\x00\x00\x00\x00\x98\x06\xe8\xff\xa7\x06\xa0\x06\xa0\x06\xa0\x06\xa0\x06\xa0\x06\xa0\x06\xa0\x06\xa0\x06\xa0\x06\x9e\x06\x9c\x06\x9b\x06\x95\x06\x91\x06\x93\x06\x90\x06\x8d\x06\x8e\x06\x8b\x06\x89\x06\x85\x06\x7f\x06\x7f\x06\x80\x06\x7e\x06\x8a\x06\x87\x06\x1c\x0a\xf7\x01\xe0\x05\x00\x00\x00\x00\x76\x06\x00\x00\xc3\x05\x24\x0c\x76\x06\x00\x00\x46\x04\x46\x04\x00\x00\x00\x00\x00\x00\xf2\x00\x00\x00\xf2\x00\xf2\x00\x00\x00\x66\x01\x46\x04\x46\x04\x00\x00\x00\x00\x00\x00\x52\x06\x00\x00\x00\x00\x00\x00\x00\x00\xf3\x03\xa9\x06\xa6\x06\x00\x00\x00\x00\x00\x00\x7b\x0b\x7b\x0b\x75\x06\xde\x01\x78\x06\x72\x06\xde\x01\x6f\x06\x61\x00\x00\x00\xe3\x04\x00\x00\x00\x00\x1c\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1c\x0a\x00\x00\x00\x00\xdb\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x67\x06\x67\x06\x00\x00\x00\x00\x00\x00\x00\x00\x46\x04\xea\xff\x46\x04\xe4\xff\x00\x00\x17\x03\x6c\x06\x00\x00\x68\x00\x5d\x06\xcc\x00\xa8\x01\xd6\xff\xd6\xff\xf2\x00\x00\x00\x00\x00\x00\x00\x8c\x06\xdc\xff\x46\x04\xdb\x0b\x35\x01\xbe\x06\x00\x00\x63\x06\x61\x06\x00\x00\x68\x00\xe0\xff\x7b\x0b\x75\x01\x00\x00\x00\x00\x00\x00\x5b\x06\xaf\xff\xaf\xff\x00\x00\x00\x00\x1c\x0a\x1c\x0a\x00\x00\x00\x00\x4d\x06\x00\x00\x49\x06\x47\x06\x48\x06\x00\x00\x00\x00\x00\x00\x46\x06\x44\x06\x00\x00\x41\x06\x00\x00\x40\x06\x3f\x06\x3a\x06\x3b\x06\x37\x06\x34\x06\x34\x06\x34\x06\x32\x06\x30\x06\x30\x06\x29\x06\x26\x06\x11\x06\x00\x00\x03\x06\x03\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf3\x00\xe1\x01\x9d\x00\xe1\x01\x00\x00\x0a\x06\xd1\x09\x00\x00\xd1\x09\xb2\x09\x00\x00\x00\x00\x00\x00\x0e\x06\x00\x06\x00\x00\x0d\x06\xe3\x04\x00\x00\x35\x01\xb2\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x01\x00\x00\x00\x00\x00\x00\x01\x06\x00\x00\xfa\x05\xf4\x05\x00\x00\xec\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb2\x09\x00\x00\x00\x00\x00\x00\x00\x00\xe9\x05\xe8\x05\xe4\x05\xdf\x05\xdf\x05\xdc\x05\xdb\x05\xd5\x05\x00\x00\xca\x05\xc9\x05\xc7\x05\x00\x00\x00\x00\x86\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x05\xd6\x05\xec\x00\x8c\x05\xd2\x05\xb5\xff\x00\x00\xbe\x05\xa0\x00\xc0\x05\xb2\x09\x00\x00\xb6\x05\xb2\x09\xb2\x09\xe5\x00\x00\x00\x00\x00\xb2\x05\x96\x05\xe3\x04\x96\x05\x00\x00\xd6\xff\xad\x05\x97\x05\xe5\x00\x00\x00\x97\x05\x97\x05\x97\x05\x97\x05\x00\x00\x00\x00\x66\x01\xb2\x09\x00\x00\x93\x05\xb2\x09\x00\x00\x93\x05\xb2\x09\x00\x00\x00\x00\x00\x00\x35\x01\x00\x00\xb8\x05\x00\x00\xb4\x05\x00\x00\x00\x00\x00\x00\x90\x05\xe5\x00\x89\x05\xe5\x00\x17\x03\x17\x03\x00\x00\x00\x00\xc4\x0b\x35\x01\x00\x00\xe3\x04\x35\x01\x00\x00\x00\x00\x00\x00\xaf\x05\x00\x00\x23\x05\x80\x05\x00\x00\x8b\x05\x8a\x05\xaf\xff\x00\x00\x85\x05\x84\x05\xaf\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x73\x05\x71\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\xf7\xff\x01\x00\x00\x00\x00\x00\x81\x05\x79\x05\x00\x00\x6c\x05\x6c\x05\x75\x05\x7e\x05\x91\x05\x00\x00\x00\x00\x69\x05\x00\x00\x00\x00\x5b\x05\x00\x00\x65\x05\x65\x05\x5c\x05\x60\x05\x60\x05\x00\x00\x00\x00\x68\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x52\x05\x00\x00\x00\x00\x56\x05\x00\x00\x4e\x05\x00\x00\x35\x01\x00\x00\x00\x00\x71\x06\x00\x00\x00\x00\x17\x03\x17\x03\x17\x03\x17\x03\x4d\x05\x4d\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe5\x00\x00\x00\x00\x00\xed\x05\x00\x00\x00\x00\x00\x00\x88\x05\x4c\x05\x2f\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x05\x20\x05\x6e\x05\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x1d\x05\x00\x00\x1f\x05\x00\x00\x00\x00\x00\x00"#

happyGotoOffsets :: HappyAddr
happyGotoOffsets = HappyA# "\xb4\x04\xd0\x11\xb9\x02\x7d\x05\xb6\x02\x42\x02\x7a\x05\x77\x05\x00\x00\x00\x00\x2a\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x65\x06\x21\x05\x00\x00\x18\x01\xd7\x04\x00\x00\x00\x00\x00\x00\x66\x05\x00\x00\x37\x01\x00\x00\x3c\x03\x00\x00\x00\x00\x27\x05\x7e\x03\x00\x00\x00\x00\x39\x03\xb4\x11\xdc\x0e\x98\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x1e\x05\x00\x00\x00\x00\x7c\x11\x00\x00\x00\x00\x7f\x04\x00\x00\x00\x00\x7e\x03\xc1\x03\x95\x0d\xd9\x0d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x05\x5f\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xce\x04\xa5\x01\x00\x00\x00\x00\x46\x0d\x6d\x0d\xb7\x0d\x76\x04\xc0\x0e\xb9\x0e\x00\x00\x00\x00\xbe\x01\xa1\x0e\x9a\x0e\x00\x00\x00\x00\x60\x11\xf7\x11\x44\x11\x00\x00\xf9\xff\x00\x04\x62\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x63\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x04\x54\x05\x53\x05\xbf\x04\x37\x05\x26\x05\xaa\x04\x91\x04\x21\x04\x22\x00\x1e\x04\xa5\x01\xa7\x04\x1c\x04\x19\x04\x0b\x04\xb2\x00\x9b\x04\x7a\x04\x71\x04\x00\x00\x00\x00\x00\x00\x5b\x07\x28\x11\x00\x00\x00\x00\x00\x00\xdf\x06\x00\x00\x60\x00\x38\x00\x00\x00\xbe\x01\x1e\x0e\x8c\x00\x54\x04\xda\x02\x00\x00\x4b\x02\x00\x00\x30\x02\x00\x00\x00\x00\x38\x03\x1f\x07\x0c\x11\x00\x00\xb8\x06\x00\x00\x82\x0e\x7b\x0e\x4f\x04\xf0\x10\xd4\x10\x00\x00\x00\x00\x3c\x04\xec\x11\x6c\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\xb8\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x07\x69\x04\x00\x00\x00\x00\x00\x00\x00\x00\x68\x04\x9c\x10\x80\x10\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x01\xd5\x02\x18\x04\x11\x04\x00\x00\x00\x00\x00\x00\x2b\x04\x14\x04\xc8\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x04\x63\x0e\x5c\x0e\x00\x00\x44\x0e\x3d\x0e\x82\x06\x00\x00\x18\x06\xbe\x01\x10\x06\x25\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x04\x38\x04\x2e\x04\x29\x04\x22\x04\x0e\x04\x0c\x04\x08\x04\x05\x04\xf7\x03\x00\x00\x00\x00\x00\x00\x00\x00\xee\x03\xc2\x03\xe5\x03\x00\x00\x00\x00\x00\x00\xb8\x03\xd7\x03\xb9\x03\x00\x00\x52\x04\x00\x00\x00\x00\x64\x10\x1d\x04\xba\x05\x00\x00\x00\x00\x04\x00\x00\x00\x9b\x01\xaf\x00\xa3\x03\x00\x00\x55\x05\x25\x04\x00\x00\x00\x00\x00\x00\x67\x02\x00\x00\xc0\x01\x33\x01\x00\x00\xfb\xff\x9c\x03\x40\x03\x00\x00\x00\x00\x00\x00\xaf\x02\x00\x00\x00\x00\x00\x00\x00\x00\xfc\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa6\x05\x41\x05\x00\x00\x94\x03\x00\x00\x00\x00\x87\x03\x00\x00\x00\x00\x00\x00\x6f\x01\x00\x00\x00\x00\x48\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x10\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x03\xa6\x03\x00\x00\x00\x00\x00\x00\x00\x00\xb3\x02\x00\x00\xb0\x02\x00\x00\x00\x00\x31\x04\x00\x00\x00\x00\x27\x04\xf2\x02\x00\x00\x78\x03\x13\x03\x8e\x02\xb7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2d\x02\xa8\x00\x8b\x08\xdc\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x10\x04\x00\x00\xfb\x0d\xe2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x03\x60\x03\x00\x00\x00\x00\x10\x10\xf4\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x69\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x62\x03\x00\x00\x63\x03\x5e\x03\x53\x03\x3d\x03\x2f\x03\xeb\x02\xb1\x02\x00\x00\x00\x00\xaa\x02\x00\x00\xa3\x02\x79\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x75\x02\x00\x00\x68\x02\x00\x00\x00\x00\x15\x01\x00\x00\x06\x00\xd8\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x03\x00\x00\x15\x07\xbc\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x02\x3d\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\xd4\x01\x00\x00\x00\x00\xc4\x01\x00\x00\x57\x00\x00\x00\xa6\x01\x84\x0f\x00\x00\xce\x00\x68\x0f\x4c\x0f\x23\x02\x00\x00\x00\x00\x00\x00\x0d\x03\x2b\x00\x88\x02\x00\x00\x02\x02\x00\x00\xfe\x01\xdc\x01\x00\x00\x9a\x03\x58\x03\x3a\x03\xe1\x02\x00\x00\x00\x00\x3c\x00\x30\x0f\x00\x00\x45\x02\x14\x0f\x00\x00\x2e\x02\xf8\x0e\x00\x00\x00\x00\x00\x00\x7c\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd8\x01\x00\x00\xd0\x01\x17\x04\xf0\x03\x00\x00\x00\x00\x42\x00\x17\x05\x00\x00\x27\x00\x4d\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x01\x72\x01\x00\x00\x00\x00\x00\x00\x4e\x02\x00\x00\x00\x00\x00\x00\x25\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\x31\x01\xbf\x01\x13\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xb9\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x01\x42\x01\x00\x00\x34\x01\xf6\x00\x00\x00\x00\x00\xe7\x01\x00\x00\x00\x00\x00\x00\x53\x01\x00\x00\x6e\x01\x00\x00\x00\x00\x8b\x00\x00\x00\x84\x00\x00\x00\xd7\x02\x00\x00\x00\x00\xdc\x0e\x00\x00\x00\x00\xc6\x03\x7c\x03\x44\x03\xf6\x02\x39\x01\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xeb\x00\x00\x00\x00\x00\x26\x02\x00\x00\x00\x00\x00\x00\x9a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe9\x00\x5e\x00\xa3\x01\x00\x00\x00\x00\x00\x00\x00\x00\x7a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1c\x00\x0a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

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

happyCheck :: HappyAddr
happyCheck = HappyA# "\xff\xff\x05\x00\x09\x00\x54\x00\x09\x00\x09\x00\x51\x00\x0c\x00\x2c\x00\x0e\x00\x13\x00\x0f\x00\x2c\x00\x09\x00\x0a\x00\x09\x00\x2c\x00\x62\x00\x00\x00\x09\x00\x13\x00\x0f\x00\x2c\x00\x62\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x05\x00\x09\x00\x4d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x50\x00\x45\x00\x51\x00\x4f\x00\x09\x00\x0f\x00\x10\x00\x4f\x00\x09\x00\x4e\x00\x0f\x00\x10\x00\x62\x00\x4f\x00\x0f\x00\x10\x00\x36\x00\x37\x00\x38\x00\x62\x00\x63\x00\x09\x00\x13\x00\x2a\x00\x2b\x00\x09\x00\x5f\x00\x4b\x00\x0c\x00\x11\x00\x0e\x00\x09\x00\x64\x00\x51\x00\x53\x00\x58\x00\x54\x00\x0f\x00\x56\x00\x57\x00\x58\x00\x59\x00\x52\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\x62\x00\x22\x00\x23\x00\x24\x00\x09\x00\x00\x00\x09\x00\x6e\x00\x6f\x00\x0b\x00\x74\x00\x72\x00\x73\x00\x5e\x00\x11\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\x09\x00\x53\x00\x95\x00\x62\x00\x63\x00\x8d\x00\x0f\x00\x09\x00\x74\x00\x93\x00\x71\x00\x9d\x00\x13\x00\x0f\x00\x71\x00\x9b\x00\x9c\x00\x13\x00\x14\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x70\x00\x2c\x00\x09\x00\x50\x00\x4e\x00\x0f\x00\x09\x00\x58\x00\x0f\x00\x09\x00\x30\x00\x58\x00\x0f\x00\x68\x00\x09\x00\x0f\x00\x36\x00\x37\x00\x6d\x00\x39\x00\x5e\x00\x5f\x00\x11\x00\x12\x00\x22\x00\x23\x00\x24\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x22\x00\x23\x00\x24\x00\x09\x00\x23\x00\x51\x00\x09\x00\x0a\x00\x54\x00\x0f\x00\x56\x00\x57\x00\x58\x00\x59\x00\x50\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\x4f\x00\x22\x00\x23\x00\x24\x00\x50\x00\x62\x00\x09\x00\x6e\x00\x6f\x00\x55\x00\x0b\x00\x72\x00\x73\x00\x5c\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\x09\x00\x70\x00\x8d\x00\x96\x00\x70\x00\x09\x00\x0f\x00\x09\x00\x70\x00\x52\x00\x09\x00\x9d\x00\x9e\x00\x0f\x00\x59\x00\x9b\x00\x5b\x00\x09\x00\x11\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x70\x00\x09\x00\x51\x00\x09\x00\x5a\x00\x09\x00\x5c\x00\x4f\x00\x51\x00\x11\x00\x12\x00\x0f\x00\x2f\x00\x29\x00\x2a\x00\x2b\x00\x36\x00\x37\x00\x38\x00\x62\x00\x5c\x00\x4e\x00\x1c\x00\x3a\x00\x3b\x00\x62\x00\x3d\x00\x3e\x00\x22\x00\x05\x00\x4b\x00\x23\x00\x48\x00\x49\x00\x4a\x00\x5c\x00\x51\x00\x2b\x00\x5f\x00\x54\x00\x6d\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\x4f\x00\x10\x00\x09\x00\x09\x00\x48\x00\x49\x00\x4a\x00\x6e\x00\x6f\x00\x0f\x00\x10\x00\x72\x00\x73\x00\x5c\x00\x09\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\x51\x00\x6d\x00\x8d\x00\x09\x00\x09\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x0f\x00\x07\x00\x9d\x00\x11\x00\x53\x00\x09\x00\x6d\x00\x56\x00\x62\x00\x4c\x00\x4d\x00\x0f\x00\x10\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x59\x00\x07\x00\x5b\x00\x48\x00\x6d\x00\x4a\x00\x50\x00\x07\x00\x09\x00\x62\x00\x09\x00\x2f\x00\x09\x00\x57\x00\x0f\x00\x59\x00\x34\x00\x5b\x00\x11\x00\x12\x00\x15\x00\x9b\x00\x9c\x00\x09\x00\x62\x00\x3d\x00\x3e\x00\x50\x00\x0b\x00\x1e\x00\x1f\x00\x20\x00\x6d\x00\x22\x00\x23\x00\x24\x00\x0b\x00\x5a\x00\x4b\x00\x5c\x00\x0b\x00\x45\x00\x46\x00\x47\x00\x51\x00\x05\x00\x06\x00\x54\x00\x31\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\x59\x00\x67\x00\x5b\x00\x45\x00\x46\x00\x47\x00\x09\x00\x6e\x00\x6f\x00\x62\x00\x09\x00\x72\x00\x73\x00\x0c\x00\x0d\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\x6e\x00\x6f\x00\x0b\x00\x09\x00\x4f\x00\x6d\x00\x98\x00\x99\x00\x9a\x00\x0f\x00\x09\x00\x9d\x00\x5a\x00\x09\x00\x5c\x00\x5a\x00\x96\x00\x5c\x00\x11\x00\x0f\x00\x10\x00\x6d\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x6a\x00\x6b\x00\x57\x00\x6d\x00\x59\x00\x0f\x00\x5b\x00\x16\x00\x09\x00\x25\x00\x26\x00\x27\x00\x28\x00\x62\x00\x0f\x00\x2b\x00\x2f\x00\x16\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4c\x00\x4d\x00\x3c\x00\x3d\x00\x3e\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x4b\x00\x57\x00\x0b\x00\x59\x00\x09\x00\x5b\x00\x51\x00\x11\x00\x12\x00\x54\x00\x0f\x00\x56\x00\x57\x00\x58\x00\x59\x00\x0b\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\x4b\x00\x22\x00\x23\x00\x24\x00\x6c\x00\x6d\x00\x1a\x00\x6e\x00\x6f\x00\x54\x00\x09\x00\x72\x00\x73\x00\x0c\x00\x0d\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\x09\x00\x09\x00\x6c\x00\x6d\x00\x09\x00\x1a\x00\x0f\x00\x09\x00\x16\x00\x11\x00\x09\x00\x9d\x00\x11\x00\x0f\x00\x10\x00\x16\x00\x0f\x00\x9b\x00\x9c\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x2f\x00\x9b\x00\x9c\x00\x2f\x00\x09\x00\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x0f\x00\x09\x00\x0a\x00\x3c\x00\x3d\x00\x3e\x00\x3c\x00\x3d\x00\x3e\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x51\x00\x16\x00\x0c\x00\x54\x00\x0e\x00\x56\x00\x57\x00\x58\x00\x59\x00\x50\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\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x09\x00\x6e\x00\x6f\x00\x0c\x00\x0d\x00\x72\x00\x73\x00\x9b\x00\x9c\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\x09\x00\x09\x00\x09\x00\x0a\x00\x09\x00\x17\x00\x0f\x00\x09\x00\x09\x00\x11\x00\x0f\x00\x9d\x00\x09\x00\x0f\x00\x10\x00\x0c\x00\x11\x00\x0e\x00\x16\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\x0a\x00\x4c\x00\x4d\x00\x26\x00\x27\x00\x28\x00\x2f\x00\x16\x00\x2b\x00\x32\x00\x33\x00\x34\x00\x35\x00\x2f\x00\x59\x00\x57\x00\x5b\x00\x59\x00\x16\x00\x5b\x00\x3d\x00\x3e\x00\x16\x00\x62\x00\x51\x00\x18\x00\x3c\x00\x3d\x00\x3e\x00\x16\x00\x57\x00\x09\x00\x59\x00\x4b\x00\x5b\x00\x09\x00\x94\x00\x09\x00\x0c\x00\x51\x00\x0e\x00\x62\x00\x54\x00\x0f\x00\x56\x00\x57\x00\x58\x00\x59\x00\x0b\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\x0b\x00\x22\x00\x23\x00\x24\x00\x09\x00\x0a\x00\x09\x00\x6e\x00\x6f\x00\x9b\x00\x9c\x00\x72\x00\x73\x00\x09\x00\x11\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\x09\x00\x2f\x00\x6c\x00\x6d\x00\x16\x00\x09\x00\x0f\x00\x09\x00\x0c\x00\x1a\x00\x0e\x00\x9d\x00\x15\x00\x0f\x00\x3c\x00\x3d\x00\x3e\x00\x19\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x1a\x00\x31\x00\x00\x00\x01\x00\x02\x00\x6c\x00\x6d\x00\x05\x00\x09\x00\x07\x00\x08\x00\x0c\x00\x0a\x00\x0e\x00\x1a\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x1a\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x18\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x05\x00\x06\x00\x24\x00\x25\x00\x26\x00\x06\x00\x28\x00\x29\x00\x2a\x00\x09\x00\x1a\x00\x09\x00\x51\x00\x1a\x00\x0c\x00\x0f\x00\x0e\x00\x1a\x00\x57\x00\x1a\x00\x59\x00\x15\x00\x5b\x00\x05\x00\x06\x00\x09\x00\x6e\x00\x6f\x00\x06\x00\x62\x00\x1e\x00\x1f\x00\x20\x00\x11\x00\x22\x00\x23\x00\x24\x00\x09\x00\x48\x00\x1a\x00\x0c\x00\x4b\x00\x0e\x00\x4d\x00\x9b\x00\x9c\x00\x1a\x00\x51\x00\x52\x00\x31\x00\x54\x00\x1a\x00\x57\x00\x57\x00\x59\x00\x59\x00\x5b\x00\x5b\x00\x9b\x00\x9c\x00\x5e\x00\x1a\x00\x60\x00\x2f\x00\x62\x00\x63\x00\x1a\x00\x65\x00\x01\x00\x02\x00\x09\x00\x0a\x00\x05\x00\x4d\x00\x07\x00\x08\x00\x3c\x00\x3d\x00\x3e\x00\x4c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x05\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x0b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x09\x00\x0a\x00\x24\x00\x25\x00\x26\x00\x09\x00\x28\x00\x29\x00\x2a\x00\x09\x00\x0a\x00\x0f\x00\x69\x00\x6a\x00\x6b\x00\x4d\x00\x6d\x00\x15\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x4c\x00\x4d\x00\x1e\x00\x1f\x00\x20\x00\x51\x00\x22\x00\x23\x00\x24\x00\x9b\x00\x9c\x00\x57\x00\x4f\x00\x59\x00\x48\x00\x5b\x00\x4e\x00\x4b\x00\x09\x00\x4d\x00\x9b\x00\x31\x00\x62\x00\x51\x00\x52\x00\x92\x00\x54\x00\x2e\x00\x2f\x00\x57\x00\x09\x00\x59\x00\x08\x00\x5b\x00\x00\x00\x01\x00\x5e\x00\x9b\x00\x60\x00\x9b\x00\x62\x00\x63\x00\x9b\x00\x65\x00\x66\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\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\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x9b\x00\x0a\x00\x08\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\x08\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x62\x00\x63\x00\x24\x00\x25\x00\x26\x00\x09\x00\x28\x00\x29\x00\x2a\x00\x4f\x00\x50\x00\x0f\x00\x62\x00\x63\x00\x94\x00\x13\x00\x14\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x09\x00\x09\x00\x09\x00\x1e\x00\x1f\x00\x20\x00\x9b\x00\x22\x00\x23\x00\x24\x00\x11\x00\x04\x00\x06\x00\x9b\x00\x0b\x00\x48\x00\x0b\x00\x4f\x00\x4b\x00\x09\x00\x4d\x00\x30\x00\x9b\x00\x4c\x00\x51\x00\x52\x00\x55\x00\x54\x00\x4e\x00\x02\x00\x57\x00\x01\x00\x59\x00\x5e\x00\x5b\x00\x62\x00\x03\x00\x13\x00\x62\x00\x60\x00\x2f\x00\x62\x00\x63\x00\x58\x00\x65\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x3c\x00\x3d\x00\x3e\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\x58\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x5d\x00\x5d\x00\x24\x00\x25\x00\x26\x00\x09\x00\x28\x00\x29\x00\x2a\x00\x5d\x00\x62\x00\x0f\x00\x5a\x00\x5c\x00\x27\x00\x13\x00\x14\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x58\x00\x62\x00\x09\x00\x1e\x00\x1f\x00\x20\x00\x62\x00\x22\x00\x23\x00\x24\x00\x11\x00\x4e\x00\x58\x00\x62\x00\x4e\x00\x48\x00\x58\x00\x61\x00\x4b\x00\x61\x00\x4d\x00\x30\x00\x53\x00\x53\x00\x51\x00\x52\x00\x2c\x00\x54\x00\x53\x00\x53\x00\x57\x00\x2c\x00\x59\x00\x62\x00\x5b\x00\x2c\x00\x5c\x00\x5a\x00\x61\x00\x60\x00\x2f\x00\x62\x00\x63\x00\x5c\x00\x65\x00\x01\x00\x02\x00\x5d\x00\x04\x00\x05\x00\x5d\x00\x07\x00\x08\x00\x3c\x00\x3d\x00\x3e\x00\x62\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x50\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x5c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x4c\x00\x4d\x00\x24\x00\x25\x00\x26\x00\x51\x00\x28\x00\x29\x00\x2a\x00\x62\x00\x09\x00\x57\x00\x0b\x00\x59\x00\x5d\x00\x5b\x00\x0f\x00\x62\x00\x09\x00\x50\x00\x13\x00\x14\x00\x62\x00\x50\x00\x5c\x00\x61\x00\x11\x00\x61\x00\x61\x00\x4c\x00\x4d\x00\x1e\x00\x1f\x00\x20\x00\x51\x00\x22\x00\x23\x00\x24\x00\x48\x00\x61\x00\x57\x00\x4b\x00\x59\x00\x4d\x00\x5b\x00\x61\x00\x61\x00\x51\x00\x52\x00\x30\x00\x54\x00\x62\x00\x64\x00\x57\x00\x61\x00\x59\x00\x2f\x00\x5b\x00\x61\x00\x61\x00\x57\x00\x34\x00\x60\x00\x62\x00\x62\x00\x63\x00\x57\x00\x65\x00\x01\x00\x02\x00\x3d\x00\x3e\x00\x05\x00\x57\x00\x07\x00\x08\x00\x4e\x00\x5c\x00\x53\x00\x50\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x64\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x09\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x0f\x00\x64\x00\x24\x00\x25\x00\x26\x00\x08\x00\x28\x00\x29\x00\x2a\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x11\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x64\x00\x09\x00\x1b\x00\x64\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x11\x00\x64\x00\x24\x00\x64\x00\x26\x00\x64\x00\x28\x00\x48\x00\x64\x00\x61\x00\x4b\x00\x64\x00\x4d\x00\x61\x00\x61\x00\x61\x00\x51\x00\x52\x00\x61\x00\x54\x00\x61\x00\x61\x00\x57\x00\x61\x00\x59\x00\x64\x00\x5b\x00\x61\x00\x54\x00\x4f\x00\x2f\x00\x60\x00\x50\x00\x62\x00\x63\x00\x34\x00\x65\x00\x2c\x00\x48\x00\x5d\x00\x4f\x00\x4b\x00\x4c\x00\x4d\x00\x3d\x00\x3e\x00\x09\x00\x51\x00\x52\x00\x5d\x00\x54\x00\x08\x00\x58\x00\x57\x00\x11\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5c\x00\x11\x00\x58\x00\x5c\x00\x2c\x00\x62\x00\x63\x00\x2c\x00\x65\x00\x50\x00\x62\x00\x1b\x00\x50\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x62\x00\x61\x00\x24\x00\x64\x00\x26\x00\x08\x00\x28\x00\x2f\x00\x09\x00\x64\x00\x61\x00\x53\x00\x61\x00\x53\x00\x11\x00\x61\x00\x11\x00\x64\x00\x61\x00\x3b\x00\x64\x00\x3d\x00\x3e\x00\x64\x00\x1b\x00\x64\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x64\x00\x64\x00\x24\x00\x64\x00\x26\x00\x64\x00\x28\x00\x48\x00\x53\x00\x61\x00\x4b\x00\x4c\x00\x4d\x00\x53\x00\x2f\x00\x2f\x00\x51\x00\x52\x00\x2d\x00\x54\x00\x34\x00\x53\x00\x57\x00\x53\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x56\x00\x3d\x00\x3e\x00\x62\x00\x4e\x00\x62\x00\x63\x00\x5c\x00\x65\x00\x50\x00\x48\x00\x5c\x00\x2d\x00\x09\x00\x4c\x00\x4d\x00\x53\x00\x0b\x00\x0b\x00\x51\x00\x52\x00\x11\x00\x54\x00\x5b\x00\x08\x00\x57\x00\x23\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x53\x00\x56\x00\x11\x00\x62\x00\x5d\x00\x62\x00\x63\x00\x16\x00\x65\x00\x5d\x00\x62\x00\x5d\x00\x1b\x00\x5d\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x5d\x00\x2f\x00\x24\x00\x65\x00\x26\x00\x08\x00\x28\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x3b\x00\x11\x00\x3d\x00\x3e\x00\x62\x00\x5d\x00\x58\x00\x5e\x00\x5d\x00\x5d\x00\x09\x00\x1b\x00\x0a\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x11\x00\x4f\x00\x24\x00\x58\x00\x26\x00\x58\x00\x28\x00\x48\x00\x5c\x00\x4f\x00\x5c\x00\x4c\x00\x4d\x00\x5c\x00\x66\x00\x53\x00\x51\x00\x52\x00\x50\x00\x54\x00\x56\x00\x66\x00\x57\x00\x58\x00\x59\x00\x62\x00\x5b\x00\x56\x00\x23\x00\x5d\x00\x2f\x00\x66\x00\x55\x00\x62\x00\x63\x00\x34\x00\x65\x00\x5d\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\x3d\x00\x3e\x00\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\x08\x00\xff\xff\x57\x00\xff\xff\x59\x00\x5a\x00\x5b\x00\x5c\x00\xff\xff\x11\x00\xff\xff\xff\xff\x09\x00\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x0f\x00\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x5a\x00\x5b\x00\x5c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\x08\x00\x54\x00\xff\xff\xff\xff\x57\x00\x58\x00\x59\x00\xff\xff\x5b\x00\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\x11\x00\x51\x00\xff\xff\x53\x00\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x1b\x00\x5b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x62\x00\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\x4c\x00\x4d\x00\x4d\x00\xff\xff\xff\xff\x51\x00\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\x57\x00\x57\x00\x59\x00\x59\x00\x5b\x00\x5b\x00\x5c\x00\xff\xff\xff\xff\xff\xff\x60\x00\x62\x00\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\x08\x00\x57\x00\xff\xff\x59\x00\x5a\x00\x5b\x00\x5c\x00\xff\xff\xff\xff\x11\x00\xff\xff\xff\xff\x62\x00\x63\x00\x16\x00\x65\x00\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\x11\x00\x51\x00\xff\xff\x53\x00\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x1b\x00\x5b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x62\x00\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\x58\x00\x59\x00\xff\xff\x5b\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\x08\x00\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\x5c\x00\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\x11\x00\x51\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x1b\x00\x5b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x62\x00\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\x58\x00\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\x08\x00\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\x5c\x00\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\x11\x00\x51\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x1b\x00\x5b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x62\x00\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\x58\x00\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\x53\x00\x54\x00\x08\x00\x56\x00\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\x11\x00\x51\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x1b\x00\x5b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\x62\x00\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\x4c\x00\x4d\x00\x4d\x00\xff\xff\xff\xff\x51\x00\x51\x00\x52\x00\x08\x00\x54\x00\xff\xff\x57\x00\x57\x00\x59\x00\x59\x00\x5b\x00\x5b\x00\x11\x00\xff\xff\xff\xff\xff\xff\x60\x00\x62\x00\x62\x00\x63\x00\xff\xff\x65\x00\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\x08\x00\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\x5c\x00\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\x08\x00\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\x4b\x00\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\x08\x00\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\x08\x00\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\xff\xff\x28\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x54\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\x1b\x00\x65\x00\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\x62\x00\x63\x00\x4d\x00\x65\x00\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\x1b\x00\x65\x00\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\x62\x00\x63\x00\x4d\x00\x65\x00\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\x1b\x00\x65\x00\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\x62\x00\x63\x00\x4d\x00\x65\x00\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x62\x00\x63\x00\x1b\x00\x65\x00\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\xff\xff\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\xff\xff\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\xff\xff\x5b\x00\xff\xff\xff\xff\xff\xff\x48\x00\xff\xff\xff\xff\x62\x00\x63\x00\x4d\x00\x65\x00\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\x09\x00\xff\xff\xff\xff\x57\x00\xff\xff\x59\x00\x0f\x00\x5b\x00\xff\xff\xff\xff\xff\xff\xff\xff\x15\x00\xff\xff\x62\x00\x63\x00\xff\xff\x65\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x09\x00\x31\x00\x0b\x00\xff\xff\xff\xff\xff\xff\x0f\x00\xff\xff\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x09\x00\xff\xff\x0b\x00\xff\xff\xff\xff\xff\xff\x0f\x00\xff\xff\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x09\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x0f\x00\xff\xff\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x09\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x0f\x00\xff\xff\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x09\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x0f\x00\xff\xff\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\x2a\x00\x2b\x00\x09\x00\xff\xff\x0b\x00\xff\xff\x30\x00\xff\xff\x0f\x00\x09\x00\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\x0f\x00\xff\xff\xff\xff\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x09\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\x0f\x00\x09\x00\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\x0f\x00\xff\xff\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x09\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\x0f\x00\x09\x00\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\x0f\x00\xff\xff\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x09\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\x0f\x00\x09\x00\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\x0f\x00\xff\xff\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x09\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\x0f\x00\x09\x00\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\x0f\x00\xff\xff\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\x09\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\x0f\x00\x09\x00\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\x0f\x00\xff\xff\x30\x00\xff\xff\x13\x00\x14\x00\xff\xff\xff\xff\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x1e\x00\x1f\x00\x20\x00\xff\xff\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\x0b\x00\xff\xff\x30\x00\xff\xff\x0f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0f\x00\xff\xff\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\xd9\x01\xb4\x01\x7d\x02\xe1\x01\x08\x00\xc6\x02\xe2\x01\x8e\x02\xe3\x01\xe8\x02\x09\x00\x84\x02\x90\x01\xf7\x01\x08\x00\xa0\x02\x04\x02\xdb\x01\x35\x03\xe3\x02\x09\x00\xa3\x02\x04\x02\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x36\x03\x39\x02\x94\x02\x56\x02\x0d\x00\x0e\x00\x5c\x01\x10\x00\x11\x00\x12\x00\x2c\x00\x8f\x02\x26\x02\xa1\x01\x85\x02\x2c\x00\x2d\x00\x9e\x01\xa1\x02\x2c\x00\xb0\x01\x2d\x00\xb7\x02\x2a\x00\xa4\x02\x2d\x00\xb7\x02\x57\x02\x58\x02\x59\x02\x2a\x00\x2b\x00\xb1\x00\x9d\x01\xd9\x02\x3c\x02\xe1\x01\xb1\x01\x13\x00\xe2\x01\x66\x01\xe3\x01\x08\x00\x27\x02\x68\x00\xe4\x01\xe9\x02\x69\x00\x09\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\xf8\x01\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x2a\x00\x10\x00\x11\x00\xf2\x01\x2d\x03\xdb\x01\xb1\x00\x4f\x00\x7a\x00\x4f\x01\xb5\x01\x7b\x00\x7c\x00\xdc\x01\x6a\x01\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\x08\x00\xae\x02\xe5\x01\x2a\x00\x2b\x00\x60\x01\x09\x00\x08\x00\x9f\x01\xf9\x01\x02\x03\x4d\x01\x67\x00\x09\x00\xb8\x02\xb1\x01\x0e\x03\x40\x00\x45\x01\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x5b\x01\x0d\x00\x0e\x00\x5c\x01\x10\x00\x11\x00\x12\x00\x08\x00\x04\x03\x68\x00\x08\x00\x5a\xff\xb0\x01\x09\x00\x08\x00\xd1\x01\x09\x00\x08\x00\x44\x00\x5a\xff\x09\x00\xc2\x02\xb1\x00\x09\x00\x5d\x01\x5e\x01\xc3\x02\x5f\x01\xdc\x01\xb1\x01\xeb\x01\x90\x02\x10\x00\x11\x00\xf2\x01\x10\x00\x11\x00\xf2\x01\x13\x00\x10\x00\x11\x00\xf2\x01\x08\x00\x95\x01\x68\x00\x90\x01\xf7\x01\x69\x00\x09\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x94\x01\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\xcd\x01\x10\x00\x11\x00\xf2\x01\x41\x02\x2a\x00\x2e\x03\x4f\x00\x7a\x00\xd8\x00\x34\x03\x7b\x00\x7c\x00\x5e\x02\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\x08\x00\x8b\x02\x60\x01\x16\x03\xa7\x02\xde\x02\x09\x00\x08\x00\xf3\x01\xbe\x02\xb1\x00\x9a\x00\x9b\x00\x09\x00\x99\x02\xa2\x01\x9a\x02\x39\x02\xb2\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x56\x02\x0d\x00\x0e\x00\x5c\x01\x10\x00\x11\x00\x12\x00\xde\x02\x3f\x02\xb1\x00\xca\x02\x4f\x02\x4a\x00\x08\x00\x4b\x00\xcd\x01\xbd\x00\xeb\x01\xec\x01\x09\x00\xc9\x00\x3a\x02\x3b\x02\x3c\x02\x57\x02\x58\x02\x5a\x02\x04\x02\x60\x02\xb0\x01\x50\x02\xca\x00\xcb\x00\x2a\x00\xcc\x00\xcd\x00\x51\x02\x19\x03\x13\x00\xc4\x00\xdf\x02\xe0\x02\xe1\x02\x34\x02\x68\x00\x52\x02\xb1\x01\x69\x00\x1c\x03\x6a\x00\x6b\x00\x6c\x00\x6d\x00\xf4\x02\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x69\xff\xe7\x01\x18\x03\x2c\x00\xdf\x02\xe9\x02\xe1\x02\x4f\x00\x7a\x00\x2d\x00\xcf\x01\x7b\x00\x7c\x00\x69\xff\xde\x02\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\xa1\x01\x1d\x03\x60\x01\x08\x00\xb1\x00\xf5\x02\xf6\x02\xf7\x02\xf8\x02\x09\x00\xe3\x02\xf9\x02\xb2\x00\x63\x00\x2c\x00\x1f\x03\x64\x00\x2a\x00\xe8\x01\xe9\x01\x2d\x00\x9b\x01\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\xea\x01\x23\x03\xeb\x01\xdf\x02\x20\x03\x2b\x03\x82\x02\xe3\x02\x08\x00\x2a\x00\xb1\x00\x6d\x01\x27\x03\x01\x02\x09\x00\x02\x02\xf5\x01\x03\x02\xeb\x01\xed\x01\x4b\x00\xb1\x01\x0f\x03\x28\x03\x04\x02\x6f\x01\xcd\x00\x5a\xff\x08\x03\x64\x01\x0d\x00\x0e\x00\xf3\x02\x10\x00\x11\x00\x47\x01\x0a\x03\x5a\xff\x13\x00\x5a\xff\xb3\x02\x2c\x03\xe5\x02\xe6\x02\x68\x00\x1a\x03\x1b\x03\x69\x00\x4e\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\xf4\x02\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x97\x02\xf6\x01\x98\x02\xe4\x02\xe5\x02\xe6\x02\x95\x02\x4f\x00\x7a\x00\x2a\x00\xe1\x01\x7b\x00\x7c\x00\x91\x02\xb5\x02\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\x4f\x00\x50\x00\xbb\x02\x08\x00\xcd\x01\xc4\x02\x31\x03\xf7\x02\xf8\x02\x09\x00\xb1\x00\x32\x03\x4a\x00\x50\x01\x4b\x00\x4a\x00\xc0\x02\x4b\x00\xb2\x00\x2d\x00\x51\x01\xc8\x02\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x08\x00\x80\x02\xfe\x01\x01\x02\xff\x01\x02\x02\x09\x00\x03\x02\xd3\x02\x08\x00\x52\x01\x53\x01\x54\x01\x55\x01\x04\x02\x09\x00\x56\x01\xdd\x01\xd4\x02\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x3a\x00\x5d\x00\x8c\x02\xdf\x01\xcd\x00\xd4\x00\x10\x00\x11\x00\xc3\x00\xb1\x00\x13\x00\x5e\x00\x5c\x02\x5f\x00\x08\x00\x60\x00\x68\x00\xeb\x01\xee\x01\x69\x00\x09\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x5e\x02\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x13\x00\x10\x00\x11\x00\x3e\x01\xec\x02\xed\x02\x60\x02\x4f\x00\x7a\x00\x14\x00\xe1\x01\x7b\x00\x7c\x00\x91\x02\x92\x02\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\x08\x00\xb1\x00\xf0\x02\xed\x02\xb1\x00\x61\x02\x09\x00\x2c\x00\x62\x02\xb2\x00\x08\x00\x4d\x01\xb2\x00\x2d\x00\x2e\x00\x65\x02\x09\x00\xb1\x01\xaa\x02\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x31\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\xdd\x01\xb1\x01\xac\x02\xdd\x01\x08\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x09\x00\x90\x01\xaf\x02\xa1\x02\xdf\x01\xcd\x00\xa4\x02\xdf\x01\xcd\x00\x38\x02\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x59\x01\x10\x00\x11\x00\xc3\x00\xe1\x01\x68\x00\x66\x02\xe2\x01\x69\x00\x10\x03\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x38\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x15\x03\x49\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\xe1\x01\x4f\x00\x7a\x00\x91\x02\x94\x02\x7b\x00\x7c\x00\xb1\x01\xb6\x02\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\x08\x00\xb1\x00\x90\x01\xb0\x02\x08\x00\x67\x02\x09\x00\x50\x01\xb1\x00\xb2\x00\x09\x00\xdc\x01\xe1\x01\x2d\x00\x51\x01\xe2\x01\xb2\x00\x11\x03\x69\x02\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\xc2\x00\x10\x00\x11\x00\xc3\x00\x90\x01\xb1\x02\xe8\x01\xe9\x01\x52\x02\x54\x01\x55\x01\xb3\x00\x6a\x02\x56\x01\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xdd\x01\xea\x01\x68\x01\xeb\x01\xba\x01\x6b\x02\xbb\x01\xb8\x00\xb9\x00\x6e\x02\x2a\x00\xbd\x00\x6c\x02\xde\x01\xdf\x01\xcd\x00\x74\x02\x68\x01\x95\x02\x69\x01\x13\x00\x6a\x01\xe1\x01\x9a\x02\x08\x00\xe2\x01\x68\x00\x12\x03\x2a\x00\x69\x00\x09\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\xd2\x01\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\xd5\x01\x10\x00\x11\x00\x54\x00\x90\x01\xb2\x02\xb1\x00\x4f\x00\x7a\x00\xb1\x01\xb9\x02\x7b\x00\x7c\x00\xf1\x01\xb2\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\x08\x00\xdd\x01\x7a\x02\x7b\x02\x0c\x02\xe1\x01\x09\x00\x08\x00\xe2\x01\x09\x02\x13\x03\x4d\x01\x4b\x00\x09\x00\xe0\x01\xdf\x01\xcd\x00\x12\x02\x4c\x00\x32\x00\x0b\x00\x4d\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x30\x02\x0d\x00\x0e\x00\x31\x02\x10\x00\x11\x00\x12\x00\x34\x00\x35\x00\x36\x00\x37\x00\x0b\x02\x4e\x00\xdb\x01\x9d\x00\x9e\x00\x7d\x02\x7e\x02\x9f\x00\xe1\x01\xa0\x00\x16\x00\xe2\x01\x80\xfe\x06\x03\x11\x02\xa1\x00\xa2\x00\xa3\x00\xa4\x00\x17\x00\xa5\x00\xa6\x00\xa7\x00\x14\x02\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\x18\x00\x19\x02\x19\x00\x1a\x00\x1b\x00\x1c\x00\xad\x00\x85\x02\x86\x02\x1e\x00\xae\x00\x1f\x00\x32\x02\x20\x00\xaf\x00\xb0\x00\x08\x00\x1b\x02\xe1\x01\xbd\x00\x1c\x02\xe2\x01\x09\x00\x07\x03\x1d\x02\x59\x00\x1e\x02\x6c\x01\x4b\x00\x6d\x01\x9b\x02\x9c\x02\xb1\x00\x4f\x00\x50\x00\x34\x02\x2a\x00\x64\x01\x0d\x00\x0e\x00\xb2\x00\x10\x00\x11\x00\x47\x01\xe1\x01\x21\x00\x1f\x02\xe2\x01\x22\x00\x9e\x02\x23\x00\xb1\x01\xa5\x02\x20\x02\x24\x00\x25\x00\xc0\x01\x26\x00\x21\x02\x59\x00\x27\x00\x5a\x00\x28\x00\x5b\x00\x29\x00\xb1\x01\xa6\x02\xdc\x01\x22\x02\xb1\x00\xdd\x01\x2a\x00\x2b\x00\x23\x02\x2c\x00\x9d\x00\x9e\x00\x90\x01\x07\x02\x9f\x00\x36\x02\xa0\x00\x16\x00\xef\x01\xdf\x01\xcd\x00\x37\x02\xa1\x00\xa2\x00\xa3\x00\xa4\x00\x17\x00\xa5\x00\xa6\x00\xa7\x00\x43\x02\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\x18\x00\x44\x02\x19\x00\x1a\x00\x1b\x00\x1c\x00\xad\x00\x90\x01\x91\x01\x1e\x00\xae\x00\x1f\x00\x08\x00\x20\x00\xaf\x00\xb0\x00\x90\x01\x92\x01\x09\x00\xfc\x01\xfd\x01\xfe\x01\x40\x01\xff\x01\x4b\x00\x01\x03\x49\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\xbb\x00\xbc\x00\x64\x01\x0d\x00\x0e\x00\xbd\x00\x10\x00\x11\x00\x47\x01\xb1\x01\xb2\x01\x5e\x00\x44\x01\xcf\x00\x21\x00\xd0\x00\x5a\x01\x22\x00\x94\x01\x23\x00\x96\x01\xbd\x01\x2a\x00\x24\x00\x25\x00\x97\x01\x26\x00\x5b\x00\x37\x00\x27\x00\x9a\x01\x28\x00\xa3\x01\x29\x00\x3f\x00\x07\x00\x24\xfe\x99\x01\xb1\x00\x9d\x01\x2a\x00\x2b\x00\xa1\x01\x2c\x00\x24\xfe\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\x03\x01\x04\x01\x05\x01\x06\x01\x07\x01\x08\x01\x09\x01\x0a\x01\x0b\x01\x0c\x01\x0d\x01\x0e\x01\x0f\x01\x10\x01\x11\x01\x12\x01\x13\x01\x14\x01\x15\x01\x16\x01\x17\x01\x18\x01\x19\x01\x1a\x01\x1b\x01\x1c\x01\x1d\x01\x1e\x01\x1f\x01\x20\x01\x21\x01\x22\x01\x23\x01\x24\x01\x25\x01\x26\x01\x27\x01\x28\x01\x29\x01\x2a\x01\x2b\x01\x2c\x01\x2d\x01\x2e\x01\x2f\x01\x30\x01\x31\x01\x32\x01\x33\x01\x34\x01\x35\x01\x36\x01\x37\x01\x38\x01\x39\x01\x3a\x01\x3b\x01\x3c\x01\x3d\x01\x3e\x01\x9d\x00\x9e\x00\xfb\x02\xfc\x02\x9f\x00\xfd\x02\xa0\x00\x16\x00\xa2\x01\x80\xfe\xa5\x01\xfe\x02\xa1\x00\xa2\x00\xa3\x00\xff\x02\x17\x00\xa5\x00\xa6\x00\xa7\x00\x00\x03\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\x18\x00\xa6\x01\x19\x00\x1a\x00\x1b\x00\x1c\x00\xad\x00\x2a\x00\x2b\x00\x1e\x00\xae\x00\x1f\x00\x08\x00\x20\x00\xaf\x00\xb0\x00\xd2\x00\xd3\x00\x09\x00\x2a\x00\x2b\x00\xa7\x01\x40\x00\x41\x00\x03\x03\x49\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\xa9\x01\xaa\x01\xb1\x00\x46\x01\x0d\x00\x0e\x00\xab\x01\x10\x00\x11\x00\x47\x01\xb2\x00\xac\x01\xae\x01\xc1\x01\xc8\x01\x21\x00\xc9\x01\x65\x00\x22\x00\xc6\x00\x23\x00\xbe\x01\xc7\x00\xc0\x00\x24\x00\x25\x00\xd0\x00\x26\x00\xd5\x00\xd8\x00\x27\x00\x07\x00\x28\x00\x38\x03\x29\x00\x2a\x00\x2f\x00\xe8\x02\x2a\x00\xb1\x00\xdd\x01\x2a\x00\x2b\x00\x30\x03\x2c\x00\x9d\x00\x9e\x00\xfb\x02\xfc\x02\x9f\x00\xfd\x02\xa0\x00\x16\x00\xf0\x01\xdf\x01\xcd\x00\xfe\x02\xa1\x00\xa2\x00\xa3\x00\xff\x02\x17\x00\xa5\x00\xa6\x00\xa7\x00\x00\x03\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\x18\x00\x31\x03\x19\x00\x1a\x00\x1b\x00\x1c\x00\xad\x00\xb4\x01\xc2\x02\x1e\x00\xae\x00\x1f\x00\x08\x00\x20\x00\xaf\x00\xb0\x00\x18\x03\x2a\x00\x09\x00\x1f\x03\x22\x03\x25\x03\x40\x00\x41\x00\xa8\x02\x49\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\x23\x03\x04\x02\xb1\x00\x46\x01\x0d\x00\x0e\x00\x04\x02\x10\x00\x11\x00\x47\x01\xb2\x00\x26\x03\x27\x03\x2a\x00\x2b\x03\x21\x00\x2a\x03\xeb\x02\x22\x00\xec\x02\x23\x00\xbf\x01\xef\x02\xf0\x02\x24\x00\x25\x00\x01\x03\x26\x00\xf2\x02\xf3\x02\x27\x00\x0d\x03\x28\x00\x04\x02\x29\x00\x0e\x03\x0a\x03\xc8\x02\xcd\x02\xb1\x00\xdd\x01\x2a\x00\x2b\x00\x0c\x03\x2c\x00\x9d\x00\x9e\x00\xb4\x01\x34\x03\x9f\x00\xb4\x01\xa0\x00\x16\x00\xfa\x01\xdf\x01\xcd\x00\x2a\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\x17\x00\xa5\x00\xa6\x00\xa7\x00\xbb\x02\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\x18\x00\xb5\x02\x19\x00\x1a\x00\x1b\x00\x1c\x00\xad\x00\xbb\x00\xbc\x00\x1e\x00\xae\x00\x1f\x00\xbd\x00\x20\x00\xaf\x00\xb0\x00\x2a\x00\x08\x00\x71\x01\x28\x02\x72\x01\xc2\x02\x73\x01\x09\x00\x04\x02\xb1\x00\xc7\x02\x48\x01\x41\x00\x2a\x00\xcb\x02\xcc\x02\xce\x02\xb2\x00\xcf\x02\xd0\x02\xbb\x00\xbc\x00\x46\x01\x0d\x00\x0e\x00\xbd\x00\x10\x00\x11\x00\x47\x01\x21\x00\xd1\x02\x5e\x00\x22\x00\xcf\x00\x23\x00\xfc\x01\xd2\x02\xd3\x02\x24\x00\x25\x00\x48\x00\x26\x00\x2a\x00\x0e\x02\x27\x00\xd6\x02\x28\x00\x6d\x01\x29\x00\xd7\x02\xd8\x02\xdb\x02\x2a\x02\xb1\x00\x2a\x00\x2a\x00\x2b\x00\xdc\x02\x2c\x00\x9d\x00\x9e\x00\x6f\x01\xcd\x00\x9f\x00\xdd\x02\xa0\x00\x16\x00\x54\x02\x55\x02\x5c\x02\x41\x02\xa1\x00\xa2\x00\xa3\x00\xa4\x00\x17\x00\xa5\x00\xa6\x00\xa7\x00\x0b\x02\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\x18\x00\x08\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\xad\x00\x09\x00\x0e\x02\x1e\x00\xae\x00\x1f\x00\x16\x00\x20\x00\xaf\x00\xb0\x00\xdd\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\x17\x00\xd3\x00\x0d\x00\x0e\x00\xd4\x00\x10\x00\x11\x00\x12\x00\x64\x02\xb1\x00\x18\x00\x65\x02\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\xb2\x00\x0e\x02\x1e\x00\x69\x02\x1f\x00\x0e\x02\x20\x00\x21\x00\x1b\x02\x6e\x02\x22\x00\x0e\x02\x23\x00\x70\x02\x71\x02\x72\x02\x24\x00\x25\x00\x73\x02\x26\x00\x74\x02\x76\x02\x27\x00\x77\x02\x28\x00\x0e\x02\x29\x00\x78\x02\x80\x02\x88\x02\x6d\x01\xb1\x00\x89\x02\x2a\x00\x2b\x00\x2b\x02\x2c\x00\x90\x02\x21\x00\xa9\x01\x9e\x02\x15\x03\x3a\x00\x3b\x00\x6f\x01\xcd\x00\xb1\x00\x24\x00\x25\x00\xb4\x01\x26\x00\x16\x00\xd2\x01\x3c\x00\xb2\x00\x3d\x00\x4a\x00\x3e\x00\x4b\x00\xd4\x01\x17\x00\xd5\x01\xd7\x01\xd8\x01\x2a\x00\x2b\x00\xd9\x01\x2c\x00\x06\x02\x2a\x00\x18\x00\x07\x02\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x2a\x00\x09\x02\x1e\x00\x0b\x02\x1f\x00\x16\x00\x20\x00\xc9\x00\xb1\x00\x0e\x02\x0f\x02\x14\xff\x10\x02\x15\xff\x17\x00\x11\x02\xb2\x00\x0b\x02\x16\x02\x49\x01\x14\x02\xcc\x00\xcd\x00\x0b\x02\x18\x00\x17\x02\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x18\x02\x19\x02\x1e\x00\x1b\x02\x1f\x00\x0b\x02\x20\x00\x21\x00\x11\xff\x25\x02\x8a\x02\x3a\x00\x3b\x00\x0f\xff\x78\x01\x6d\x01\x24\x00\x25\x00\x42\x01\x26\x00\x6e\x01\x10\xff\x3c\x00\x36\x02\x3d\x00\x4a\x00\x3e\x00\x4b\x00\xc2\x00\x6f\x01\xcd\x00\x2a\x00\x3e\x02\x2a\x00\x2b\x00\x3f\x02\x2c\x00\x41\x02\x21\x00\x46\x02\x42\x01\xb1\x00\x3a\x00\x3b\x00\x4b\x01\x4f\x01\x50\x01\x24\x00\x25\x00\xb2\x00\x26\x00\x58\x01\x16\x00\x3c\x00\xd7\x00\x3d\x00\x4a\x00\x3e\x00\x4b\x00\x74\x01\x59\x01\x52\x00\x2a\x00\xc9\x00\x2a\x00\x2b\x00\x53\x00\x2c\x00\x99\x01\x2a\x00\xc9\x00\x18\x00\xc9\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\xa9\x01\xc9\x00\x1e\x00\xa5\x01\x1f\x00\x16\x00\x20\x00\x48\x02\x49\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\x4c\x01\x17\x00\xcc\x00\xcd\x00\x2a\x00\xc9\x00\xc3\x01\xae\x01\xb4\x01\xc9\x00\xb1\x00\x18\x00\xc4\x01\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\xb2\x00\xc7\x01\x1e\x00\xc5\x01\x1f\x00\xc6\x01\x20\x00\x21\x00\xc8\x01\xcd\x01\xcb\x01\x3a\x00\x3b\x00\xcc\x01\xff\xff\x61\x00\x24\x00\x25\x00\x65\x00\x26\x00\xc2\x00\xff\xff\x3c\x00\x54\x00\x3d\x00\x2a\x00\x3e\x00\x64\x00\xd7\x00\xc9\x00\x6d\x01\xff\xff\xd8\x00\x2a\x00\x2b\x00\x75\x01\x2c\x00\x31\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x6f\x01\xcd\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x16\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x4a\x00\x3e\x00\x4b\x00\x00\x00\x17\x00\x00\x00\x00\x00\x08\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x09\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\xd3\x00\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x4a\x00\x29\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x16\x00\x26\x00\x00\x00\x00\x00\x27\x00\x2a\x02\x28\x00\x00\x00\x29\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\xf6\xfe\xf6\xfe\x00\x00\x00\x00\x17\x00\xf6\xfe\x00\x00\xf6\xfe\x00\x00\x00\x00\x00\x00\xf6\xfe\x00\x00\xf6\xfe\x18\x00\xf6\xfe\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\xf6\xfe\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\xbb\x00\xbc\x00\x23\x00\x00\x00\x00\x00\xbd\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x71\x01\x27\x00\x72\x01\x28\x00\x73\x01\x29\x00\x62\x01\x00\x00\x00\x00\x00\x00\x63\x01\x2a\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x16\x00\x27\x00\x00\x00\x28\x00\x4a\x00\x29\x00\x4b\x00\x00\x00\x00\x00\x52\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x53\x00\x2c\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\xbb\x00\xbc\x00\x00\x00\x00\x00\x17\x00\xbd\x00\x00\x00\x12\xff\x00\x00\x00\x00\x00\x00\x71\x01\x00\x00\x72\x01\x18\x00\x73\x01\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x2a\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x27\x00\x66\x01\x28\x00\x00\x00\x29\x00\x8a\x02\x49\x02\x4a\x02\x4b\x02\x4c\x02\x4d\x02\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x16\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x46\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\xbb\x00\xbc\x00\x00\x00\x00\x00\x17\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x00\x00\x00\xcf\x00\x18\x00\xd0\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x2a\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x54\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x16\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x46\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\xbb\x00\xbc\x00\x00\x00\x00\x00\x17\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x01\x00\x00\x72\x01\x18\x00\x73\x01\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x2a\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x54\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x4d\xff\x26\x00\x16\x00\x4d\xff\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\xbb\x00\xbc\x00\x00\x00\x00\x00\x17\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x00\x00\x00\xbf\x00\x18\x00\xc0\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x2a\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\xbb\x00\xbc\x00\x23\x00\x00\x00\x00\x00\xbd\x00\x24\x00\x25\x00\x16\x00\x26\x00\x00\x00\x5e\x00\x27\x00\xcf\x00\x28\x00\xd0\x00\x29\x00\x17\x00\x00\x00\x00\x00\x00\x00\x63\x01\x2a\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x16\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x28\x02\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x16\x00\x26\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x22\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x16\x00\x26\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x16\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x1f\x00\x00\x00\x20\x00\x21\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x26\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x18\x00\x2c\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x18\x00\x00\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\x06\x03\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x21\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x23\x00\x2c\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x18\x00\x2c\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x18\x00\x00\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\xf5\x01\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x21\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x23\x00\x2c\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x18\x00\x2c\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x18\x00\x00\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x21\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x23\x00\x2c\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x57\x00\x00\x00\x58\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x18\x00\x2c\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x18\x00\x00\x00\x19\x00\x1a\x00\x00\x00\x1c\x00\x1d\x00\x00\x00\x00\x00\x1e\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\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x21\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x23\x00\x2c\x00\x00\x00\x00\x00\x24\x00\x25\x00\x00\x00\x08\x00\x00\x00\x00\x00\x27\x00\x00\x00\x28\x00\x09\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x2a\x00\x2b\x00\x00\x00\x2c\x00\x4c\x00\x32\x00\x0b\x00\x4d\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x00\x35\x00\x36\x00\x37\x00\x08\x00\xc0\x01\x46\x00\x00\x00\x00\x00\x00\x00\x09\x00\x00\x00\x00\x00\x00\x00\x40\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x00\x32\x00\x0b\x00\x43\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x00\x35\x00\x36\x00\x37\x00\xbf\x01\x08\x00\x00\x00\x46\x00\x00\x00\x00\x00\x00\x00\x09\x00\x00\x00\x00\x00\x00\x00\x40\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x00\x32\x00\x0b\x00\x43\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x34\x00\x35\x00\x36\x00\x37\x00\x48\x00\x09\x00\x00\x00\x00\x00\x00\x00\x40\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x32\x00\x0b\x00\x43\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x34\x00\x35\x00\x36\x00\x37\x00\xbe\x01\x09\x00\x00\x00\x00\x00\x00\x00\x40\x00\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x32\x00\x0b\x00\x43\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x82\x02\x34\x00\x35\x00\x36\x00\x37\x00\x44\x00\x09\x00\x00\x00\x00\x00\x00\x00\x40\x00\x45\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x02\x3b\x02\x3c\x02\x08\x00\x00\x00\x63\x01\x00\x00\x44\x00\x00\x00\x09\x00\x08\x00\x00\x00\x00\x00\x48\x01\x41\x00\x00\x00\x09\x00\x00\x00\x00\x00\x00\x00\x40\x00\x45\x01\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x46\x01\x0d\x00\x0e\x00\x08\x00\x10\x00\x11\x00\x47\x01\x00\x00\x00\x00\x09\x00\x08\x00\x48\x00\x00\x00\x2c\x02\x41\x00\x00\x00\x09\x00\x00\x00\x44\x00\x00\x00\x2d\x02\x41\x00\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x46\x01\x0d\x00\x0e\x00\x08\x00\x10\x00\x11\x00\x47\x01\x00\x00\x00\x00\x09\x00\x08\x00\xbb\x01\x00\x00\x2e\x02\x41\x00\x00\x00\x09\x00\x00\x00\xbc\x01\x00\x00\x2f\x02\x41\x00\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x46\x01\x0d\x00\x0e\x00\x08\x00\x10\x00\x11\x00\x47\x01\x00\x00\x00\x00\x09\x00\x08\x00\xbe\x01\x00\x00\x40\x00\x45\x01\x00\x00\x09\x00\x00\x00\xbf\x01\x00\x00\x48\x01\x41\x00\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x46\x01\x0d\x00\x0e\x00\x08\x00\x10\x00\x11\x00\x47\x01\x00\x00\x00\x00\x09\x00\x08\x00\x44\x00\x00\x00\x40\x00\x41\x00\x00\x00\x09\x00\x00\x00\x48\x00\x00\x00\x40\x00\x41\x00\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x46\x01\x0d\x00\x0e\x00\x08\x00\x10\x00\x11\x00\x47\x01\x00\x00\x00\x00\x09\x00\x08\x00\x44\x00\x00\x00\x40\x00\x41\x00\x00\x00\x09\x00\x00\x00\x48\x00\x00\x00\x40\x00\x41\x00\x00\x00\x00\x00\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x46\x01\x0d\x00\x0e\x00\x00\x00\x10\x00\x11\x00\x47\x01\x08\x00\x00\x00\x46\x00\x00\x00\xbb\x01\x00\x00\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbc\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xad\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbc\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd8\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x79\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xce\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x02\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4b\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x74\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x01\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x33\x00\x10\x00\x11\x00\x12\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x34\x00\x35\x00\x36\x00\x37\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x00\x00\x00\x3f\x01\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x00\x00\x00\x00\x00\x00\xb7\x01\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x77\x01\x78\x01\x79\x01\x7a\x01\x7b\x01\x7c\x01\x7d\x01\x7e\x01\x7f\x01\x80\x01\x81\x01\x82\x01\x83\x01\x84\x01\x85\x01\x86\x01\x87\x01\x88\x01\x89\x01\x8a\x01\x8b\x01\x8c\x01\x8d\x01\x8e\x01\x8f\x01\x90\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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 (6, 476) [
	(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),
	(426 , happyReduce_426),
	(427 , happyReduce_427),
	(428 , happyReduce_428),
	(429 , happyReduce_429),
	(430 , happyReduce_430),
	(431 , happyReduce_431),
	(432 , happyReduce_432),
	(433 , happyReduce_433),
	(434 , happyReduce_434),
	(435 , happyReduce_435),
	(436 , happyReduce_436),
	(437 , happyReduce_437),
	(438 , happyReduce_438),
	(439 , happyReduce_439),
	(440 , happyReduce_440),
	(441 , happyReduce_441),
	(442 , happyReduce_442),
	(443 , happyReduce_443),
	(444 , happyReduce_444),
	(445 , happyReduce_445),
	(446 , happyReduce_446),
	(447 , happyReduce_447),
	(448 , happyReduce_448),
	(449 , happyReduce_449),
	(450 , happyReduce_450),
	(451 , happyReduce_451),
	(452 , happyReduce_452),
	(453 , happyReduce_453),
	(454 , happyReduce_454),
	(455 , happyReduce_455),
	(456 , happyReduce_456),
	(457 , happyReduce_457),
	(458 , happyReduce_458),
	(459 , happyReduce_459),
	(460 , happyReduce_460),
	(461 , happyReduce_461),
	(462 , happyReduce_462),
	(463 , happyReduce_463),
	(464 , happyReduce_464),
	(465 , happyReduce_465),
	(466 , happyReduce_466),
	(467 , happyReduce_467),
	(468 , happyReduce_468),
	(469 , happyReduce_469),
	(470 , happyReduce_470),
	(471 , happyReduce_471),
	(472 , happyReduce_472),
	(473 , happyReduce_473),
	(474 , happyReduce_474),
	(475 , happyReduce_475),
	(476 , happyReduce_476)
	]

happy_n_terms = 103 :: Int
happy_n_nonterms = 159 :: Int

happyReduce_6 = happySpecReduce_1  0# happyReduction_6
happyReduction_6 happy_x_1
	 =  case happyOut10 happy_x_1 of { happy_var_1 -> 
	happyIn9
		 (reverse happy_var_1
	)}

happyReduce_7 = happySpecReduce_2  1# happyReduction_7
happyReduction_7 happy_x_2
	happy_x_1
	 =  case happyOut10 happy_x_1 of { happy_var_1 -> 
	case happyOut11 happy_x_2 of { happy_var_2 -> 
	happyIn10
		 (happy_var_2 : happy_var_1
	)}}

happyReduce_8 = happySpecReduce_0  1# happyReduction_8
happyReduction_8  =  happyIn10
		 ([]
	)

happyReduce_9 = happySpecReduce_1  2# happyReduction_9
happyReduction_9 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwAbstract happy_var_1) -> 
	happyIn11
		 (TokKeyword KwAbstract happy_var_1
	)}

happyReduce_10 = happySpecReduce_1  2# happyReduction_10
happyReduction_10 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCoData happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCoData happy_var_1
	)}

happyReduce_11 = happySpecReduce_1  2# happyReduction_11
happyReduction_11 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCoInductive happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCoInductive happy_var_1
	)}

happyReduce_12 = happySpecReduce_1  2# happyReduction_12
happyReduction_12 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwConstructor happy_var_1) -> 
	happyIn11
		 (TokKeyword KwConstructor happy_var_1
	)}

happyReduce_13 = happySpecReduce_1  2# happyReduction_13
happyReduction_13 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwData happy_var_1) -> 
	happyIn11
		 (TokKeyword KwData happy_var_1
	)}

happyReduce_14 = happySpecReduce_1  2# happyReduction_14
happyReduction_14 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwEta happy_var_1) -> 
	happyIn11
		 (TokKeyword KwEta happy_var_1
	)}

happyReduce_15 = happySpecReduce_1  2# happyReduction_15
happyReduction_15 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwField happy_var_1) -> 
	happyIn11
		 (TokKeyword KwField happy_var_1
	)}

happyReduce_16 = happySpecReduce_1  2# happyReduction_16
happyReduction_16 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwForall happy_var_1) -> 
	happyIn11
		 (TokKeyword KwForall happy_var_1
	)}

happyReduce_17 = happySpecReduce_1  2# happyReduction_17
happyReduction_17 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwHiding happy_var_1) -> 
	happyIn11
		 (TokKeyword KwHiding happy_var_1
	)}

happyReduce_18 = happySpecReduce_1  2# happyReduction_18
happyReduction_18 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwImport happy_var_1) -> 
	happyIn11
		 (TokKeyword KwImport happy_var_1
	)}

happyReduce_19 = happySpecReduce_1  2# happyReduction_19
happyReduction_19 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwIn happy_var_1) -> 
	happyIn11
		 (TokKeyword KwIn happy_var_1
	)}

happyReduce_20 = happySpecReduce_1  2# happyReduction_20
happyReduction_20 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInductive happy_var_1) -> 
	happyIn11
		 (TokKeyword KwInductive happy_var_1
	)}

happyReduce_21 = happySpecReduce_1  2# happyReduction_21
happyReduction_21 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInfix happy_var_1) -> 
	happyIn11
		 (TokKeyword KwInfix happy_var_1
	)}

happyReduce_22 = happySpecReduce_1  2# happyReduction_22
happyReduction_22 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInfixL happy_var_1) -> 
	happyIn11
		 (TokKeyword KwInfixL happy_var_1
	)}

happyReduce_23 = happySpecReduce_1  2# happyReduction_23
happyReduction_23 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInfixR happy_var_1) -> 
	happyIn11
		 (TokKeyword KwInfixR happy_var_1
	)}

happyReduce_24 = happySpecReduce_1  2# happyReduction_24
happyReduction_24 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInstance happy_var_1) -> 
	happyIn11
		 (TokKeyword KwInstance happy_var_1
	)}

happyReduce_25 = happySpecReduce_1  2# happyReduction_25
happyReduction_25 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwLet happy_var_1) -> 
	happyIn11
		 (TokKeyword KwLet happy_var_1
	)}

happyReduce_26 = happySpecReduce_1  2# happyReduction_26
happyReduction_26 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwMacro happy_var_1) -> 
	happyIn11
		 (TokKeyword KwMacro happy_var_1
	)}

happyReduce_27 = happySpecReduce_1  2# happyReduction_27
happyReduction_27 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwModule happy_var_1) -> 
	happyIn11
		 (TokKeyword KwModule happy_var_1
	)}

happyReduce_28 = happySpecReduce_1  2# happyReduction_28
happyReduction_28 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwMutual happy_var_1) -> 
	happyIn11
		 (TokKeyword KwMutual happy_var_1
	)}

happyReduce_29 = happySpecReduce_1  2# happyReduction_29
happyReduction_29 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwNoEta happy_var_1) -> 
	happyIn11
		 (TokKeyword KwNoEta happy_var_1
	)}

happyReduce_30 = happySpecReduce_1  2# happyReduction_30
happyReduction_30 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwOpen happy_var_1) -> 
	happyIn11
		 (TokKeyword KwOpen happy_var_1
	)}

happyReduce_31 = happySpecReduce_1  2# happyReduction_31
happyReduction_31 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPatternSyn happy_var_1) -> 
	happyIn11
		 (TokKeyword KwPatternSyn happy_var_1
	)}

happyReduce_32 = happySpecReduce_1  2# happyReduction_32
happyReduction_32 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPostulate happy_var_1) -> 
	happyIn11
		 (TokKeyword KwPostulate happy_var_1
	)}

happyReduce_33 = happySpecReduce_1  2# happyReduction_33
happyReduction_33 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPrimitive happy_var_1) -> 
	happyIn11
		 (TokKeyword KwPrimitive happy_var_1
	)}

happyReduce_34 = happySpecReduce_1  2# happyReduction_34
happyReduction_34 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPrivate happy_var_1) -> 
	happyIn11
		 (TokKeyword KwPrivate happy_var_1
	)}

happyReduce_35 = happySpecReduce_1  2# happyReduction_35
happyReduction_35 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwProp happy_var_1) -> 
	happyIn11
		 (TokKeyword KwProp happy_var_1
	)}

happyReduce_36 = happySpecReduce_1  2# happyReduction_36
happyReduction_36 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPublic happy_var_1) -> 
	happyIn11
		 (TokKeyword KwPublic happy_var_1
	)}

happyReduce_37 = happySpecReduce_1  2# happyReduction_37
happyReduction_37 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuote happy_var_1) -> 
	happyIn11
		 (TokKeyword KwQuote happy_var_1
	)}

happyReduce_38 = happySpecReduce_1  2# happyReduction_38
happyReduction_38 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuoteContext happy_var_1) -> 
	happyIn11
		 (TokKeyword KwQuoteContext happy_var_1
	)}

happyReduce_39 = happySpecReduce_1  2# happyReduction_39
happyReduction_39 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuoteGoal happy_var_1) -> 
	happyIn11
		 (TokKeyword KwQuoteGoal happy_var_1
	)}

happyReduce_40 = happySpecReduce_1  2# happyReduction_40
happyReduction_40 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuoteTerm happy_var_1) -> 
	happyIn11
		 (TokKeyword KwQuoteTerm happy_var_1
	)}

happyReduce_41 = happySpecReduce_1  2# happyReduction_41
happyReduction_41 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwRecord happy_var_1) -> 
	happyIn11
		 (TokKeyword KwRecord happy_var_1
	)}

happyReduce_42 = happySpecReduce_1  2# happyReduction_42
happyReduction_42 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwRenaming happy_var_1) -> 
	happyIn11
		 (TokKeyword KwRenaming happy_var_1
	)}

happyReduce_43 = happySpecReduce_1  2# happyReduction_43
happyReduction_43 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwRewrite happy_var_1) -> 
	happyIn11
		 (TokKeyword KwRewrite happy_var_1
	)}

happyReduce_44 = happySpecReduce_1  2# happyReduction_44
happyReduction_44 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwSet happy_var_1) -> 
	happyIn11
		 (TokKeyword KwSet happy_var_1
	)}

happyReduce_45 = happySpecReduce_1  2# happyReduction_45
happyReduction_45 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwSyntax happy_var_1) -> 
	happyIn11
		 (TokKeyword KwSyntax happy_var_1
	)}

happyReduce_46 = happySpecReduce_1  2# happyReduction_46
happyReduction_46 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwTactic happy_var_1) -> 
	happyIn11
		 (TokKeyword KwTactic happy_var_1
	)}

happyReduce_47 = happySpecReduce_1  2# happyReduction_47
happyReduction_47 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwTo happy_var_1) -> 
	happyIn11
		 (TokKeyword KwTo happy_var_1
	)}

happyReduce_48 = happySpecReduce_1  2# happyReduction_48
happyReduction_48 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwUnquote happy_var_1) -> 
	happyIn11
		 (TokKeyword KwUnquote happy_var_1
	)}

happyReduce_49 = happySpecReduce_1  2# happyReduction_49
happyReduction_49 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwUnquoteDecl happy_var_1) -> 
	happyIn11
		 (TokKeyword KwUnquoteDecl happy_var_1
	)}

happyReduce_50 = happySpecReduce_1  2# happyReduction_50
happyReduction_50 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwUnquoteDef happy_var_1) -> 
	happyIn11
		 (TokKeyword KwUnquoteDef happy_var_1
	)}

happyReduce_51 = happySpecReduce_1  2# happyReduction_51
happyReduction_51 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwUsing happy_var_1) -> 
	happyIn11
		 (TokKeyword KwUsing happy_var_1
	)}

happyReduce_52 = happySpecReduce_1  2# happyReduction_52
happyReduction_52 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwWhere happy_var_1) -> 
	happyIn11
		 (TokKeyword KwWhere happy_var_1
	)}

happyReduce_53 = happySpecReduce_1  2# happyReduction_53
happyReduction_53 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwWith happy_var_1) -> 
	happyIn11
		 (TokKeyword KwWith happy_var_1
	)}

happyReduce_54 = happySpecReduce_1  2# happyReduction_54
happyReduction_54 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwBUILTIN happy_var_1) -> 
	happyIn11
		 (TokKeyword KwBUILTIN happy_var_1
	)}

happyReduce_55 = happySpecReduce_1  2# happyReduction_55
happyReduction_55 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCATCHALL happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCATCHALL happy_var_1
	)}

happyReduce_56 = happySpecReduce_1  2# happyReduction_56
happyReduction_56 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED happy_var_1
	)}

happyReduce_57 = happySpecReduce_1  2# happyReduction_57
happyReduction_57 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_DATA happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_DATA happy_var_1
	)}

happyReduce_58 = happySpecReduce_1  2# happyReduction_58
happyReduction_58 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_DATA_UHC happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_DATA_UHC happy_var_1
	)}

happyReduce_59 = happySpecReduce_1  2# happyReduction_59
happyReduction_59 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_DECLARE_DATA happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_DECLARE_DATA happy_var_1
	)}

happyReduce_60 = happySpecReduce_1  2# happyReduction_60
happyReduction_60 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_EPIC happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_EPIC happy_var_1
	)}

happyReduce_61 = happySpecReduce_1  2# happyReduction_61
happyReduction_61 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_EXPORT happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_EXPORT happy_var_1
	)}

happyReduce_62 = happySpecReduce_1  2# happyReduction_62
happyReduction_62 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_JS happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_JS happy_var_1
	)}

happyReduce_63 = happySpecReduce_1  2# happyReduction_63
happyReduction_63 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_TYPE happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_TYPE happy_var_1
	)}

happyReduce_64 = happySpecReduce_1  2# happyReduction_64
happyReduction_64 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCOMPILED_UHC happy_var_1) -> 
	happyIn11
		 (TokKeyword KwCOMPILED_UHC happy_var_1
	)}

happyReduce_65 = happySpecReduce_1  2# happyReduction_65
happyReduction_65 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwHASKELL happy_var_1) -> 
	happyIn11
		 (TokKeyword KwHASKELL happy_var_1
	)}

happyReduce_66 = happySpecReduce_1  2# happyReduction_66
happyReduction_66 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwDISPLAY happy_var_1) -> 
	happyIn11
		 (TokKeyword KwDISPLAY happy_var_1
	)}

happyReduce_67 = happySpecReduce_1  2# happyReduction_67
happyReduction_67 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwIMPORT happy_var_1) -> 
	happyIn11
		 (TokKeyword KwIMPORT happy_var_1
	)}

happyReduce_68 = happySpecReduce_1  2# happyReduction_68
happyReduction_68 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwIMPORT_UHC happy_var_1) -> 
	happyIn11
		 (TokKeyword KwIMPORT_UHC happy_var_1
	)}

happyReduce_69 = happySpecReduce_1  2# happyReduction_69
happyReduction_69 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwIMPOSSIBLE happy_var_1) -> 
	happyIn11
		 (TokKeyword KwIMPOSSIBLE happy_var_1
	)}

happyReduce_70 = happySpecReduce_1  2# happyReduction_70
happyReduction_70 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwINLINE happy_var_1) -> 
	happyIn11
		 (TokKeyword KwINLINE happy_var_1
	)}

happyReduce_71 = happySpecReduce_1  2# happyReduction_71
happyReduction_71 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwMEASURE happy_var_1) -> 
	happyIn11
		 (TokKeyword KwMEASURE happy_var_1
	)}

happyReduce_72 = happySpecReduce_1  2# happyReduction_72
happyReduction_72 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwNO_SMASHING happy_var_1) -> 
	happyIn11
		 (TokKeyword KwNO_SMASHING happy_var_1
	)}

happyReduce_73 = happySpecReduce_1  2# happyReduction_73
happyReduction_73 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwNO_TERMINATION_CHECK happy_var_1) -> 
	happyIn11
		 (TokKeyword KwNO_TERMINATION_CHECK happy_var_1
	)}

happyReduce_74 = happySpecReduce_1  2# happyReduction_74
happyReduction_74 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwNO_POSITIVITY_CHECK happy_var_1) -> 
	happyIn11
		 (TokKeyword KwNO_POSITIVITY_CHECK happy_var_1
	)}

happyReduce_75 = happySpecReduce_1  2# happyReduction_75
happyReduction_75 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwNON_TERMINATING happy_var_1) -> 
	happyIn11
		 (TokKeyword KwNON_TERMINATING happy_var_1
	)}

happyReduce_76 = happySpecReduce_1  2# happyReduction_76
happyReduction_76 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwOPTIONS happy_var_1) -> 
	happyIn11
		 (TokKeyword KwOPTIONS happy_var_1
	)}

happyReduce_77 = happySpecReduce_1  2# happyReduction_77
happyReduction_77 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwREWRITE happy_var_1) -> 
	happyIn11
		 (TokKeyword KwREWRITE happy_var_1
	)}

happyReduce_78 = happySpecReduce_1  2# happyReduction_78
happyReduction_78 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwSTATIC happy_var_1) -> 
	happyIn11
		 (TokKeyword KwSTATIC happy_var_1
	)}

happyReduce_79 = happySpecReduce_1  2# happyReduction_79
happyReduction_79 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwTERMINATING happy_var_1) -> 
	happyIn11
		 (TokKeyword KwTERMINATING happy_var_1
	)}

happyReduce_80 = happySpecReduce_1  2# happyReduction_80
happyReduction_80 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSetN happy_var_1) -> 
	happyIn11
		 (TokSetN happy_var_1
	)}

happyReduce_81 = happySpecReduce_1  2# happyReduction_81
happyReduction_81 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokTeX happy_var_1) -> 
	happyIn11
		 (TokTeX happy_var_1
	)}

happyReduce_82 = happySpecReduce_1  2# happyReduction_82
happyReduction_82 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokComment happy_var_1) -> 
	happyIn11
		 (TokComment happy_var_1
	)}

happyReduce_83 = happySpecReduce_1  2# happyReduction_83
happyReduction_83 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymEllipsis happy_var_1) -> 
	happyIn11
		 (TokSymbol SymEllipsis happy_var_1
	)}

happyReduce_84 = happySpecReduce_1  2# happyReduction_84
happyReduction_84 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDotDot happy_var_1) -> 
	happyIn11
		 (TokSymbol SymDotDot happy_var_1
	)}

happyReduce_85 = happySpecReduce_1  2# happyReduction_85
happyReduction_85 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDot happy_var_1) -> 
	happyIn11
		 (TokSymbol SymDot happy_var_1
	)}

happyReduce_86 = happySpecReduce_1  2# happyReduction_86
happyReduction_86 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymSemi happy_var_1) -> 
	happyIn11
		 (TokSymbol SymSemi happy_var_1
	)}

happyReduce_87 = happySpecReduce_1  2# happyReduction_87
happyReduction_87 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymColon happy_var_1) -> 
	happyIn11
		 (TokSymbol SymColon happy_var_1
	)}

happyReduce_88 = happySpecReduce_1  2# happyReduction_88
happyReduction_88 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymEqual happy_var_1) -> 
	happyIn11
		 (TokSymbol SymEqual happy_var_1
	)}

happyReduce_89 = happySpecReduce_1  2# happyReduction_89
happyReduction_89 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymUnderscore happy_var_1) -> 
	happyIn11
		 (TokSymbol SymUnderscore happy_var_1
	)}

happyReduce_90 = happySpecReduce_1  2# happyReduction_90
happyReduction_90 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymQuestionMark happy_var_1) -> 
	happyIn11
		 (TokSymbol SymQuestionMark happy_var_1
	)}

happyReduce_91 = happySpecReduce_1  2# happyReduction_91
happyReduction_91 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymArrow happy_var_1) -> 
	happyIn11
		 (TokSymbol SymArrow happy_var_1
	)}

happyReduce_92 = happySpecReduce_1  2# happyReduction_92
happyReduction_92 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymLambda happy_var_1) -> 
	happyIn11
		 (TokSymbol SymLambda happy_var_1
	)}

happyReduce_93 = happySpecReduce_1  2# happyReduction_93
happyReduction_93 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymAs happy_var_1) -> 
	happyIn11
		 (TokSymbol SymAs happy_var_1
	)}

happyReduce_94 = happySpecReduce_1  2# happyReduction_94
happyReduction_94 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymBar happy_var_1) -> 
	happyIn11
		 (TokSymbol SymBar happy_var_1
	)}

happyReduce_95 = happySpecReduce_1  2# happyReduction_95
happyReduction_95 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenParen happy_var_1) -> 
	happyIn11
		 (TokSymbol SymOpenParen happy_var_1
	)}

happyReduce_96 = happySpecReduce_1  2# happyReduction_96
happyReduction_96 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymCloseParen happy_var_1) -> 
	happyIn11
		 (TokSymbol SymCloseParen happy_var_1
	)}

happyReduce_97 = happySpecReduce_1  2# happyReduction_97
happyReduction_97 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDoubleOpenBrace happy_var_1) -> 
	happyIn11
		 (TokSymbol SymDoubleOpenBrace happy_var_1
	)}

happyReduce_98 = happySpecReduce_1  2# happyReduction_98
happyReduction_98 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDoubleCloseBrace happy_var_1) -> 
	happyIn11
		 (TokSymbol SymDoubleCloseBrace happy_var_1
	)}

happyReduce_99 = happySpecReduce_1  2# happyReduction_99
happyReduction_99 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenBrace happy_var_1) -> 
	happyIn11
		 (TokSymbol SymOpenBrace happy_var_1
	)}

happyReduce_100 = happySpecReduce_1  2# happyReduction_100
happyReduction_100 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymCloseBrace happy_var_1) -> 
	happyIn11
		 (TokSymbol SymCloseBrace happy_var_1
	)}

happyReduce_101 = happySpecReduce_1  2# happyReduction_101
happyReduction_101 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenVirtualBrace happy_var_1) -> 
	happyIn11
		 (TokSymbol SymOpenVirtualBrace happy_var_1
	)}

happyReduce_102 = happySpecReduce_1  2# happyReduction_102
happyReduction_102 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymCloseVirtualBrace happy_var_1) -> 
	happyIn11
		 (TokSymbol SymCloseVirtualBrace happy_var_1
	)}

happyReduce_103 = happySpecReduce_1  2# happyReduction_103
happyReduction_103 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymVirtualSemi happy_var_1) -> 
	happyIn11
		 (TokSymbol SymVirtualSemi happy_var_1
	)}

happyReduce_104 = happySpecReduce_1  2# happyReduction_104
happyReduction_104 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	happyIn11
		 (TokSymbol SymOpenPragma happy_var_1
	)}

happyReduce_105 = happySpecReduce_1  2# happyReduction_105
happyReduction_105 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymClosePragma happy_var_1) -> 
	happyIn11
		 (TokSymbol SymClosePragma happy_var_1
	)}

happyReduce_106 = happySpecReduce_1  2# happyReduction_106
happyReduction_106 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokId happy_var_1) -> 
	happyIn11
		 (TokId happy_var_1
	)}

happyReduce_107 = happySpecReduce_1  2# happyReduction_107
happyReduction_107 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokQId happy_var_1) -> 
	happyIn11
		 (TokQId happy_var_1
	)}

happyReduce_108 = happySpecReduce_1  2# happyReduction_108
happyReduction_108 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokString happy_var_1) -> 
	happyIn11
		 (TokString happy_var_1
	)}

happyReduce_109 = happySpecReduce_1  2# happyReduction_109
happyReduction_109 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokLiteral happy_var_1) -> 
	happyIn11
		 (TokLiteral happy_var_1
	)}

happyReduce_110 = happySpecReduce_3  3# happyReduction_110
happyReduction_110 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut126 happy_x_2 of { happy_var_2 -> 
	happyIn12
		 (takeOptionsPragmas happy_var_2
	)}

happyReduce_111 = happySpecReduce_0  4# happyReduction_111
happyReduction_111  =  happyIn13
		 (()
	)

happyReduce_112 = happySpecReduce_1  4# happyReduction_112
happyReduction_112 happy_x_1
	 =  happyIn13
		 (()
	)

happyReduce_113 = happySpecReduce_1  5# happyReduction_113
happyReduction_113 happy_x_1
	 =  happyIn14
		 (()
	)

happyReduce_114 = happyMonadReduce 1# 5# happyReduction_114
happyReduction_114 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (( popContext)
	) (\r -> happyReturn (happyIn14 r))

happyReduce_115 = happySpecReduce_1  6# happyReduction_115
happyReduction_115 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymSemi happy_var_1) -> 
	happyIn15
		 (happy_var_1
	)}

happyReduce_116 = happySpecReduce_1  6# happyReduction_116
happyReduction_116 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymVirtualSemi happy_var_1) -> 
	happyIn15
		 (happy_var_1
	)}

happyReduce_117 = happyMonadReduce 0# 7# happyReduction_117
happyReduction_117 (happyRest) tk
	 = happyThen (( pushLexState imp_dir)
	) (\r -> happyReturn (happyIn16 r))

happyReduce_118 = happyMonadReduce 1# 8# happyReduction_118
happyReduction_118 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokLiteral happy_var_1) -> 
	( case happy_var_1 of {
                     LitNat _ i -> return i;
                     _          -> fail $ "Expected integer"
                   })}
	) (\r -> happyReturn (happyIn17 r))

happyReduce_119 = happyMonadReduce 1# 9# happyReduction_119
happyReduction_119 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokId happy_var_1) -> 
	( mkName happy_var_1)}
	) (\r -> happyReturn (happyIn18 r))

happyReduce_120 = happySpecReduce_2  10# happyReduction_120
happyReduction_120 happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	case happyOut19 happy_x_2 of { happy_var_2 -> 
	happyIn19
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_121 = happySpecReduce_1  10# happyReduction_121
happyReduction_121 happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	happyIn19
		 ([happy_var_1]
	)}

happyReduce_122 = happySpecReduce_1  11# happyReduction_122
happyReduction_122 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDoubleCloseBrace happy_var_1) -> 
	happyIn20
		 (getRange happy_var_1
	)}

happyReduce_123 = happyMonadReduce 2# 11# happyReduction_123
happyReduction_123 (happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokSymbol SymCloseBrace happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymCloseBrace happy_var_2) -> 
	(
      if posPos (fromJust (rEnd' (getRange happy_var_2))) -
         posPos (fromJust (rStart' (getRange happy_var_1))) > 2
      then parseErrorAt (fromJust (rStart' (getRange happy_var_2)))
         "Expecting '}}', found separated '}'s."
      else return $ getRange (happy_var_1, happy_var_2))}}
	) (\r -> happyReturn (happyIn20 r))

happyReduce_124 = happySpecReduce_2  12# happyReduction_124
happyReduction_124 happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_2 of { happy_var_2 -> 
	happyIn21
		 (setRelevance Irrelevant $ defaultArg happy_var_2
	)}

happyReduce_125 = happySpecReduce_1  12# happyReduction_125
happyReduction_125 happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	happyIn21
		 (defaultArg happy_var_1
	)}

happyReduce_126 = happySpecReduce_2  13# happyReduction_126
happyReduction_126 happy_x_2
	happy_x_1
	 =  case happyOut21 happy_x_1 of { happy_var_1 -> 
	case happyOut22 happy_x_2 of { happy_var_2 -> 
	happyIn22
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_127 = happySpecReduce_1  13# happyReduction_127
happyReduction_127 happy_x_1
	 =  case happyOut21 happy_x_1 of { happy_var_1 -> 
	happyIn22
		 ([happy_var_1]
	)}

happyReduce_128 = happySpecReduce_2  14# happyReduction_128
happyReduction_128 happy_x_2
	happy_x_1
	 =  case happyOut21 happy_x_1 of { happy_var_1 -> 
	case happyOut23 happy_x_2 of { happy_var_2 -> 
	happyIn23
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_129 = happySpecReduce_1  14# happyReduction_129
happyReduction_129 happy_x_1
	 =  case happyOut21 happy_x_1 of { happy_var_1 -> 
	happyIn23
		 ([happy_var_1]
	)}

happyReduce_130 = happyReduce 4# 14# happyReduction_130
happyReduction_130 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut22 happy_x_2 of { happy_var_2 -> 
	case happyOut23 happy_x_4 of { happy_var_4 -> 
	happyIn23
		 (map makeInstance happy_var_2 ++ happy_var_4
	) `HappyStk` happyRest}}

happyReduce_131 = happySpecReduce_3  14# happyReduction_131
happyReduction_131 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut22 happy_x_2 of { happy_var_2 -> 
	happyIn23
		 (map makeInstance happy_var_2
	)}

happyReduce_132 = happyReduce 4# 14# happyReduction_132
happyReduction_132 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut22 happy_x_2 of { happy_var_2 -> 
	case happyOut23 happy_x_4 of { happy_var_4 -> 
	happyIn23
		 (map hide happy_var_2 ++ happy_var_4
	) `HappyStk` happyRest}}

happyReduce_133 = happySpecReduce_3  14# happyReduction_133
happyReduction_133 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut22 happy_x_2 of { happy_var_2 -> 
	happyIn23
		 (map hide happy_var_2
	)}

happyReduce_134 = happyReduce 5# 14# happyReduction_134
happyReduction_134 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	case happyOut23 happy_x_5 of { happy_var_5 -> 
	happyIn23
		 (map (hide . setRelevance Irrelevant . defaultArg) happy_var_3 ++ happy_var_5
	) `HappyStk` happyRest}}

happyReduce_135 = happyReduce 4# 14# happyReduction_135
happyReduction_135 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	happyIn23
		 (map (hide . setRelevance Irrelevant . defaultArg) happy_var_3
	) `HappyStk` happyRest}

happyReduce_136 = happyReduce 5# 14# happyReduction_136
happyReduction_136 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	case happyOut23 happy_x_5 of { happy_var_5 -> 
	happyIn23
		 (map (makeInstance . setRelevance Irrelevant . defaultArg) happy_var_3 ++ happy_var_5
	) `HappyStk` happyRest}}

happyReduce_137 = happyReduce 4# 14# happyReduction_137
happyReduction_137 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	happyIn23
		 (map (makeInstance . setRelevance Irrelevant . defaultArg) happy_var_3
	) `HappyStk` happyRest}

happyReduce_138 = happyReduce 5# 14# happyReduction_138
happyReduction_138 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	case happyOut23 happy_x_5 of { happy_var_5 -> 
	happyIn23
		 (map (hide . setRelevance NonStrict . defaultArg) happy_var_3 ++ happy_var_5
	) `HappyStk` happyRest}}

happyReduce_139 = happyReduce 4# 14# happyReduction_139
happyReduction_139 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	happyIn23
		 (map (hide . setRelevance NonStrict . defaultArg) happy_var_3
	) `HappyStk` happyRest}

happyReduce_140 = happyReduce 5# 14# happyReduction_140
happyReduction_140 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	case happyOut23 happy_x_5 of { happy_var_5 -> 
	happyIn23
		 (map (makeInstance . setRelevance NonStrict . defaultArg) happy_var_3 ++ happy_var_5
	) `HappyStk` happyRest}}

happyReduce_141 = happyReduce 4# 14# happyReduction_141
happyReduction_141 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut19 happy_x_3 of { happy_var_3 -> 
	happyIn23
		 (map (makeInstance . setRelevance NonStrict . defaultArg) happy_var_3
	) `HappyStk` happyRest}

happyReduce_142 = happyMonadReduce 1# 15# happyReduction_142
happyReduction_142 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokQId happy_var_1) -> 
	( mkQName happy_var_1)}
	) (\r -> happyReturn (happyIn24 r))

happyReduce_143 = happySpecReduce_1  15# happyReduction_143
happyReduction_143 happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	happyIn24
		 (QName happy_var_1
	)}

happyReduce_144 = happySpecReduce_1  16# happyReduction_144
happyReduction_144 happy_x_1
	 =  case happyOut24 happy_x_1 of { happy_var_1 -> 
	happyIn25
		 (happy_var_1
	)}

happyReduce_145 = happySpecReduce_1  17# happyReduction_145
happyReduction_145 happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	happyIn26
		 (happy_var_1
	)}

happyReduce_146 = happySpecReduce_1  17# happyReduction_146
happyReduction_146 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymUnderscore happy_var_1) -> 
	happyIn26
		 (Name (getRange happy_var_1) [Hole]
	)}

happyReduce_147 = happySpecReduce_2  18# happyReduction_147
happyReduction_147 happy_x_2
	happy_x_1
	 =  case happyOut26 happy_x_1 of { happy_var_1 -> 
	case happyOut27 happy_x_2 of { happy_var_2 -> 
	happyIn27
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_148 = happySpecReduce_1  18# happyReduction_148
happyReduction_148 happy_x_1
	 =  case happyOut26 happy_x_1 of { happy_var_1 -> 
	happyIn27
		 ([happy_var_1]
	)}

happyReduce_149 = happySpecReduce_1  19# happyReduction_149
happyReduction_149 happy_x_1
	 =  case happyOut29 happy_x_1 of { happy_var_1 -> 
	happyIn28
		 (case happy_var_1 of
      Left ns -> ns
      Right _ -> fail $ "expected sequence of bound identifiers, not absurd pattern"
	)}

happyReduce_150 = happyMonadReduce 1# 20# happyReduction_150
happyReduction_150 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut39 happy_x_1 of { happy_var_1 -> 
	(
    let getName :: Expr -> Maybe Name
        getName (Ident (QName x)) = Just x
        getName (Underscore r _)  = Just (Name r [Hole])
        getName _                 = Nothing

        isAbsurd :: Expr -> Bool
        isAbsurd (Absurd _)                  = True
        isAbsurd (HiddenArg _ (Named _ e))   = isAbsurd e
        isAbsurd (InstanceArg _ (Named _ e)) = isAbsurd e
        isAbsurd (Paren _ expr)              = isAbsurd expr
        isAbsurd (RawApp _ exprs)            = any isAbsurd exprs
        isAbsurd _                           = False
    in
    if any isAbsurd happy_var_1 then return $ Right happy_var_1 else
    case mapM getName happy_var_1 of
        Just good -> return $ Left good
        Nothing   -> fail $ "expected sequence of bound identifiers")}
	) (\r -> happyReturn (happyIn29 r))

happyReduce_151 = happyMonadReduce 1# 21# happyReduction_151
happyReduction_151 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut39 happy_x_1 of { happy_var_1 -> 
	(
    let -- interpret an expression as name
        getName :: Expr -> Maybe Name
        getName (Ident (QName x)) = Just x
        getName (Underscore r _)  = Just (Name r [Hole])
        getName _                 = Nothing

        getNames :: Expr -> Maybe [Name]
        getNames (RawApp _ es) = mapM getName es
        getNames e             = singleton `fmap` getName e

        -- interpret an expression as name or list of hidden names
        getName1 :: Expr -> Maybe [WithHiding Name]
        getName1 (Ident (QName x)) = Just [WithHiding NotHidden x]
        getName1 (Underscore r _)  = Just [WithHiding NotHidden $ Name r [Hole]]
        getName1 (HiddenArg _ (Named Nothing e))
                                   = map (WithHiding Hidden) `fmap` getNames e
        getName1 _                 = Nothing

    in
    case mapM getName1 happy_var_1 of
        Just good -> return $ concat good
        Nothing   -> fail $ "expected sequence of possibly hidden bound identifiers")}
	) (\r -> happyReturn (happyIn30 r))

happyReduce_152 = happySpecReduce_0  22# happyReduction_152
happyReduction_152  =  happyIn31
		 ([]
	)

happyReduce_153 = happySpecReduce_2  22# happyReduction_153
happyReduction_153 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokString happy_var_1) -> 
	case happyOut31 happy_x_2 of { happy_var_2 -> 
	happyIn31
		 (snd happy_var_1 : happy_var_2
	)}}

happyReduce_154 = happySpecReduce_1  23# happyReduction_154
happyReduction_154 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokString happy_var_1) -> 
	happyIn32
		 (snd happy_var_1
	)}

happyReduce_155 = happySpecReduce_0  24# happyReduction_155
happyReduction_155  =  happyIn33
		 ([]
	)

happyReduce_156 = happySpecReduce_2  24# happyReduction_156
happyReduction_156 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokString happy_var_1) -> 
	case happyOut33 happy_x_2 of { happy_var_2 -> 
	happyIn33
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_157 = happyMonadReduce 1# 25# happyReduction_157
happyReduction_157 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokString happy_var_1) -> 
	( mkName happy_var_1)}
	) (\r -> happyReturn (happyIn34 r))

happyReduce_158 = happyMonadReduce 1# 26# happyReduction_158
happyReduction_158 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokString happy_var_1) -> 
	( fmap QName (mkName happy_var_1))}
	) (\r -> happyReturn (happyIn35 r))

happyReduce_159 = happySpecReduce_2  27# happyReduction_159
happyReduction_159 happy_x_2
	happy_x_1
	 =  case happyOut53 happy_x_1 of { happy_var_1 -> 
	case happyOut36 happy_x_2 of { happy_var_2 -> 
	happyIn36
		 (Pi happy_var_1 happy_var_2
	)}}

happyReduce_160 = happySpecReduce_3  27# happyReduction_160
happyReduction_160 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut42 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymArrow happy_var_2) -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn36
		 (Fun (getRange (happy_var_1,happy_var_2,happy_var_3))
                                              (RawApp (getRange happy_var_1) happy_var_1)
                                              happy_var_3
	)}}}

happyReduce_161 = happySpecReduce_3  27# happyReduction_161
happyReduction_161 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut37 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymEqual happy_var_2) -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn36
		 (Equal (getRange (happy_var_1, happy_var_2, happy_var_3)) happy_var_1 happy_var_3
	)}}}

happyReduce_162 = happySpecReduce_1  27# happyReduction_162
happyReduction_162 happy_x_1
	 =  case happyOut37 happy_x_1 of { happy_var_1 -> 
	happyIn36
		 (happy_var_1
	)}

happyReduce_163 = happyMonadReduce 1# 28# happyReduction_163
happyReduction_163 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut38 happy_x_1 of { happy_var_1 -> 
	( case happy_var_1 of
                      { [e]    -> return e
                      ; e : es -> return $ WithApp (fuseRange e es) e es
                      ; []     -> fail "impossible: empty with expressions"
                      })}
	) (\r -> happyReturn (happyIn37 r))

happyReduce_164 = happySpecReduce_3  29# happyReduction_164
happyReduction_164 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut42 happy_x_1 of { happy_var_1 -> 
	case happyOut38 happy_x_3 of { happy_var_3 -> 
	happyIn38
		 (RawApp (getRange happy_var_1) happy_var_1 :  happy_var_3
	)}}

happyReduce_165 = happySpecReduce_1  29# happyReduction_165
happyReduction_165 happy_x_1
	 =  case happyOut39 happy_x_1 of { happy_var_1 -> 
	happyIn38
		 ([RawApp (getRange happy_var_1) happy_var_1]
	)}

happyReduce_166 = happySpecReduce_1  30# happyReduction_166
happyReduction_166 happy_x_1
	 =  case happyOut40 happy_x_1 of { happy_var_1 -> 
	happyIn39
		 ([happy_var_1]
	)}

happyReduce_167 = happySpecReduce_2  30# happyReduction_167
happyReduction_167 happy_x_2
	happy_x_1
	 =  case happyOut45 happy_x_1 of { happy_var_1 -> 
	case happyOut39 happy_x_2 of { happy_var_2 -> 
	happyIn39
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_168 = happySpecReduce_3  31# happyReduction_168
happyReduction_168 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymLambda happy_var_1) -> 
	case happyOut59 happy_x_2 of { happy_var_2 -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn40
		 (Lam (getRange (happy_var_1,happy_var_2,happy_var_3)) happy_var_2 happy_var_3
	)}}}

happyReduce_169 = happySpecReduce_1  31# happyReduction_169
happyReduction_169 happy_x_1
	 =  case happyOut41 happy_x_1 of { happy_var_1 -> 
	happyIn40
		 (happy_var_1
	)}

happyReduce_170 = happySpecReduce_3  31# happyReduction_170
happyReduction_170 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut67 happy_x_2 of { happy_var_2 -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn40
		 (forallPi happy_var_2 happy_var_3
	)}}

happyReduce_171 = happyReduce 4# 31# happyReduction_171
happyReduction_171 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwLet happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokKeyword KwIn happy_var_3) -> 
	case happyOut36 happy_x_4 of { happy_var_4 -> 
	happyIn40
		 (Let (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_2 happy_var_4
	) `HappyStk` happyRest}}}}

happyReduce_172 = happySpecReduce_1  31# happyReduction_172
happyReduction_172 happy_x_1
	 =  case happyOut45 happy_x_1 of { happy_var_1 -> 
	happyIn40
		 (happy_var_1
	)}

happyReduce_173 = happyReduce 4# 31# happyReduction_173
happyReduction_173 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwQuoteGoal happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokKeyword KwIn happy_var_3) -> 
	case happyOut36 happy_x_4 of { happy_var_4 -> 
	happyIn40
		 (QuoteGoal (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_2 happy_var_4
	) `HappyStk` happyRest}}}}

happyReduce_174 = happySpecReduce_2  31# happyReduction_174
happyReduction_174 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwTactic happy_var_1) -> 
	case happyOut42 happy_x_2 of { happy_var_2 -> 
	happyIn40
		 (Tactic (getRange (happy_var_1, happy_var_2)) (RawApp (getRange happy_var_2) happy_var_2) []
	)}}

happyReduce_175 = happyReduce 4# 31# happyReduction_175
happyReduction_175 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwTactic happy_var_1) -> 
	case happyOut42 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymBar happy_var_3) -> 
	case happyOut38 happy_x_4 of { happy_var_4 -> 
	happyIn40
		 (Tactic (getRange (happy_var_1, happy_var_2, happy_var_3, happy_var_4)) (RawApp (getRange happy_var_2) happy_var_2) happy_var_4
	) `HappyStk` happyRest}}}}

happyReduce_176 = happyReduce 4# 32# happyReduction_176
happyReduction_176 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymLambda happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymOpenBrace happy_var_2) -> 
	case happyOut66 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseBrace happy_var_4) -> 
	happyIn41
		 (ExtendedLam (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) (reverse happy_var_3)
	) `HappyStk` happyRest}}}}

happyReduce_177 = happyMonadReduce 2# 32# happyReduction_177
happyReduction_177 (happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokSymbol SymLambda happy_var_1) -> 
	case happyOut60 happy_x_2 of { happy_var_2 -> 
	( case happy_var_2 of
                                       Left (bs, h) -> if null bs then return $ AbsurdLam r h else
                                                       return $ Lam r bs (AbsurdLam r h)
                                                         where r = fuseRange happy_var_1 bs
                                       Right es -> do -- it is of the form @\ { p1 ... () }@
                                                     p <- exprToLHS (RawApp (getRange es) es);
                                                     return $ ExtendedLam (fuseRange happy_var_1 es)
                                                                     [(p [] [], AbsurdRHS, NoWhere, False)])}}
	) (\r -> happyReturn (happyIn41 r))

happyReduce_178 = happySpecReduce_1  33# happyReduction_178
happyReduction_178 happy_x_1
	 =  case happyOut45 happy_x_1 of { happy_var_1 -> 
	happyIn42
		 ([happy_var_1]
	)}

happyReduce_179 = happySpecReduce_2  33# happyReduction_179
happyReduction_179 happy_x_2
	happy_x_1
	 =  case happyOut45 happy_x_1 of { happy_var_1 -> 
	case happyOut42 happy_x_2 of { happy_var_2 -> 
	happyIn42
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_180 = happySpecReduce_3  34# happyReduction_180
happyReduction_180 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenBrace happy_var_1) -> 
	case happyOut36 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymCloseBrace happy_var_3) -> 
	happyIn43
		 (HiddenArg (getRange (happy_var_1,happy_var_2,happy_var_3)) (maybeNamed happy_var_2)
	)}}}

happyReduce_181 = happySpecReduce_2  34# happyReduction_181
happyReduction_181 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenBrace happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymCloseBrace happy_var_2) -> 
	happyIn43
		 (let r = fuseRange happy_var_1 happy_var_2 in HiddenArg r $ unnamed $ Absurd r
	)}}

happyReduce_182 = happySpecReduce_1  35# happyReduction_182
happyReduction_182 happy_x_1
	 =  case happyOut24 happy_x_1 of { happy_var_1 -> 
	happyIn44
		 (Ident happy_var_1
	)}

happyReduce_183 = happySpecReduce_1  35# happyReduction_183
happyReduction_183 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokLiteral happy_var_1) -> 
	happyIn44
		 (Lit happy_var_1
	)}

happyReduce_184 = happySpecReduce_1  35# happyReduction_184
happyReduction_184 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymQuestionMark happy_var_1) -> 
	happyIn44
		 (QuestionMark (getRange happy_var_1) Nothing
	)}

happyReduce_185 = happySpecReduce_1  35# happyReduction_185
happyReduction_185 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymUnderscore happy_var_1) -> 
	happyIn44
		 (Underscore (getRange happy_var_1) Nothing
	)}

happyReduce_186 = happySpecReduce_1  35# happyReduction_186
happyReduction_186 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwProp happy_var_1) -> 
	happyIn44
		 (Prop (getRange happy_var_1)
	)}

happyReduce_187 = happySpecReduce_1  35# happyReduction_187
happyReduction_187 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwSet happy_var_1) -> 
	happyIn44
		 (Set (getRange happy_var_1)
	)}

happyReduce_188 = happySpecReduce_1  35# happyReduction_188
happyReduction_188 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuote happy_var_1) -> 
	happyIn44
		 (Quote (getRange happy_var_1)
	)}

happyReduce_189 = happySpecReduce_1  35# happyReduction_189
happyReduction_189 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuoteTerm happy_var_1) -> 
	happyIn44
		 (QuoteTerm (getRange happy_var_1)
	)}

happyReduce_190 = happySpecReduce_1  35# happyReduction_190
happyReduction_190 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwQuoteContext happy_var_1) -> 
	happyIn44
		 (QuoteContext (getRange happy_var_1)
	)}

happyReduce_191 = happySpecReduce_1  35# happyReduction_191
happyReduction_191 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwUnquote happy_var_1) -> 
	happyIn44
		 (Unquote (getRange happy_var_1)
	)}

happyReduce_192 = happySpecReduce_1  35# happyReduction_192
happyReduction_192 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSetN happy_var_1) -> 
	happyIn44
		 (SetN (getRange (fst happy_var_1)) (snd happy_var_1)
	)}

happyReduce_193 = happySpecReduce_3  35# happyReduction_193
happyReduction_193 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDoubleOpenBrace happy_var_1) -> 
	case happyOut36 happy_x_2 of { happy_var_2 -> 
	case happyOut20 happy_x_3 of { happy_var_3 -> 
	happyIn44
		 (InstanceArg (getRange (happy_var_1,happy_var_2,happy_var_3))
                                                          (maybeNamed happy_var_2)
	)}}}

happyReduce_194 = happySpecReduce_3  35# happyReduction_194
happyReduction_194 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenParen happy_var_1) -> 
	case happyOut36 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymCloseParen happy_var_3) -> 
	happyIn44
		 (Paren (getRange (happy_var_1,happy_var_2,happy_var_3)) happy_var_2
	)}}}

happyReduce_195 = happySpecReduce_2  35# happyReduction_195
happyReduction_195 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenParen happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymCloseParen happy_var_2) -> 
	happyIn44
		 (Absurd (fuseRange happy_var_1 happy_var_2)
	)}}

happyReduce_196 = happySpecReduce_2  35# happyReduction_196
happyReduction_196 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDoubleOpenBrace happy_var_1) -> 
	case happyOut20 happy_x_2 of { happy_var_2 -> 
	happyIn44
		 (let r = fuseRange happy_var_1 happy_var_2 in InstanceArg r $ unnamed $ Absurd r
	)}}

happyReduce_197 = happySpecReduce_3  35# happyReduction_197
happyReduction_197 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymAs happy_var_2) -> 
	case happyOut45 happy_x_3 of { happy_var_3 -> 
	happyIn44
		 (As (getRange (happy_var_1,happy_var_2,happy_var_3)) happy_var_1 happy_var_3
	)}}}

happyReduce_198 = happySpecReduce_2  35# happyReduction_198
happyReduction_198 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDot happy_var_1) -> 
	case happyOut45 happy_x_2 of { happy_var_2 -> 
	happyIn44
		 (Dot (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_199 = happyReduce 4# 35# happyReduction_199
happyReduction_199 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwRecord happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymOpenBrace happy_var_2) -> 
	case happyOut46 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseBrace happy_var_4) -> 
	happyIn44
		 (Rec (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}}

happyReduce_200 = happyReduce 5# 35# happyReduction_200
happyReduction_200 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwRecord happy_var_1) -> 
	case happyOut44 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymOpenBrace happy_var_3) -> 
	case happyOut50 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymCloseBrace happy_var_5) -> 
	happyIn44
		 (RecUpdate (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) happy_var_2 happy_var_4
	) `HappyStk` happyRest}}}}}

happyReduce_201 = happySpecReduce_1  36# happyReduction_201
happyReduction_201 happy_x_1
	 =  case happyOut43 happy_x_1 of { happy_var_1 -> 
	happyIn45
		 (happy_var_1
	)}

happyReduce_202 = happySpecReduce_1  36# happyReduction_202
happyReduction_202 happy_x_1
	 =  case happyOut44 happy_x_1 of { happy_var_1 -> 
	happyIn45
		 (happy_var_1
	)}

happyReduce_203 = happySpecReduce_0  37# happyReduction_203
happyReduction_203  =  happyIn46
		 ([]
	)

happyReduce_204 = happySpecReduce_1  37# happyReduction_204
happyReduction_204 happy_x_1
	 =  case happyOut47 happy_x_1 of { happy_var_1 -> 
	happyIn46
		 (happy_var_1
	)}

happyReduce_205 = happySpecReduce_1  38# happyReduction_205
happyReduction_205 happy_x_1
	 =  case happyOut48 happy_x_1 of { happy_var_1 -> 
	happyIn47
		 ([happy_var_1]
	)}

happyReduce_206 = happySpecReduce_3  38# happyReduction_206
happyReduction_206 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut48 happy_x_1 of { happy_var_1 -> 
	case happyOut47 happy_x_3 of { happy_var_3 -> 
	happyIn47
		 (happy_var_1 : happy_var_3
	)}}

happyReduce_207 = happySpecReduce_1  39# happyReduction_207
happyReduction_207 happy_x_1
	 =  case happyOut52 happy_x_1 of { happy_var_1 -> 
	happyIn48
		 (Left  happy_var_1
	)}

happyReduce_208 = happySpecReduce_1  39# happyReduction_208
happyReduction_208 happy_x_1
	 =  case happyOut49 happy_x_1 of { happy_var_1 -> 
	happyIn48
		 (Right happy_var_1
	)}

happyReduce_209 = happySpecReduce_3  40# happyReduction_209
happyReduction_209 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut25 happy_x_1 of { happy_var_1 -> 
	case happyOut121 happy_x_2 of { happy_var_2 -> 
	case happyOut72 happy_x_3 of { happy_var_3 -> 
	happyIn49
		 (ModuleAssignment happy_var_1 happy_var_2 happy_var_3
	)}}}

happyReduce_210 = happySpecReduce_0  41# happyReduction_210
happyReduction_210  =  happyIn50
		 ([]
	)

happyReduce_211 = happySpecReduce_1  41# happyReduction_211
happyReduction_211 happy_x_1
	 =  case happyOut51 happy_x_1 of { happy_var_1 -> 
	happyIn50
		 (happy_var_1
	)}

happyReduce_212 = happySpecReduce_1  42# happyReduction_212
happyReduction_212 happy_x_1
	 =  case happyOut52 happy_x_1 of { happy_var_1 -> 
	happyIn51
		 ([happy_var_1]
	)}

happyReduce_213 = happySpecReduce_3  42# happyReduction_213
happyReduction_213 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut52 happy_x_1 of { happy_var_1 -> 
	case happyOut51 happy_x_3 of { happy_var_3 -> 
	happyIn51
		 (happy_var_1 : happy_var_3
	)}}

happyReduce_214 = happySpecReduce_3  43# happyReduction_214
happyReduction_214 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn52
		 (FieldAssignment happy_var_1 happy_var_3
	)}}

happyReduce_215 = happySpecReduce_2  44# happyReduction_215
happyReduction_215 happy_x_2
	happy_x_1
	 =  case happyOut54 happy_x_1 of { happy_var_1 -> 
	happyIn53
		 (happy_var_1
	)}

happyReduce_216 = happySpecReduce_1  45# happyReduction_216
happyReduction_216 happy_x_1
	 =  case happyOut55 happy_x_1 of { happy_var_1 -> 
	happyIn54
		 ({-TeleBind-} happy_var_1
	)}

happyReduce_217 = happySpecReduce_2  46# happyReduction_217
happyReduction_217 happy_x_2
	happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	case happyOut55 happy_x_2 of { happy_var_2 -> 
	happyIn55
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_218 = happySpecReduce_1  46# happyReduction_218
happyReduction_218 happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	happyIn55
		 ([happy_var_1]
	)}

happyReduce_219 = happyReduce 4# 47# happyReduction_219
happyReduction_219 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_2 of { (TokSymbol SymOpenParen happy_var_2) -> 
	case happyOut58 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseParen happy_var_4) -> 
	happyIn56
		 (setRange (getRange (happy_var_2,happy_var_3,happy_var_4)) $
                             setRelevance Irrelevant happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_220 = happyReduce 4# 47# happyReduction_220
happyReduction_220 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_2 of { (TokSymbol SymOpenBrace happy_var_2) -> 
	case happyOut57 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseBrace happy_var_4) -> 
	happyIn56
		 (setRange (getRange (happy_var_2,happy_var_3,happy_var_4)) $
                             setHiding Hidden $
                             setRelevance Irrelevant happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_221 = happyReduce 4# 47# happyReduction_221
happyReduction_221 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_2 of { (TokSymbol SymDoubleOpenBrace happy_var_2) -> 
	case happyOut57 happy_x_3 of { happy_var_3 -> 
	case happyOut20 happy_x_4 of { happy_var_4 -> 
	happyIn56
		 (setRange (getRange (happy_var_2,happy_var_3,happy_var_4)) $
                             setHiding Instance $
                             setRelevance Irrelevant happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_222 = happyReduce 4# 47# happyReduction_222
happyReduction_222 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_2 of { (TokSymbol SymOpenParen happy_var_2) -> 
	case happyOut58 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseParen happy_var_4) -> 
	happyIn56
		 (setRange (getRange (happy_var_2,happy_var_3,happy_var_4)) $
                             setRelevance NonStrict happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_223 = happyReduce 4# 47# happyReduction_223
happyReduction_223 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_2 of { (TokSymbol SymOpenBrace happy_var_2) -> 
	case happyOut57 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseBrace happy_var_4) -> 
	happyIn56
		 (setRange (getRange (happy_var_2,happy_var_3,happy_var_4)) $
                             setHiding Hidden $
                             setRelevance NonStrict happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_224 = happyReduce 4# 47# happyReduction_224
happyReduction_224 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_2 of { (TokSymbol SymDoubleOpenBrace happy_var_2) -> 
	case happyOut57 happy_x_3 of { happy_var_3 -> 
	case happyOut20 happy_x_4 of { happy_var_4 -> 
	happyIn56
		 (setRange (getRange (happy_var_2,happy_var_3,happy_var_4)) $
                             setHiding Instance $
                             setRelevance NonStrict happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_225 = happySpecReduce_3  47# happyReduction_225
happyReduction_225 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenParen happy_var_1) -> 
	case happyOut58 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymCloseParen happy_var_3) -> 
	happyIn56
		 (setRange (getRange (happy_var_1,happy_var_2,happy_var_3)) happy_var_2
	)}}}

happyReduce_226 = happySpecReduce_3  47# happyReduction_226
happyReduction_226 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymDoubleOpenBrace happy_var_1) -> 
	case happyOut57 happy_x_2 of { happy_var_2 -> 
	case happyOut20 happy_x_3 of { happy_var_3 -> 
	happyIn56
		 (setRange (getRange (happy_var_1,happy_var_2,happy_var_3)) $
                             setHiding Instance happy_var_2
	)}}}

happyReduce_227 = happySpecReduce_3  47# happyReduction_227
happyReduction_227 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenBrace happy_var_1) -> 
	case happyOut57 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymCloseBrace happy_var_3) -> 
	happyIn56
		 (setRange (getRange (happy_var_1,happy_var_2,happy_var_3)) $
                             setHiding Hidden happy_var_2
	)}}}

happyReduce_228 = happySpecReduce_3  47# happyReduction_228
happyReduction_228 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenParen happy_var_1) -> 
	case happyOut120 happy_x_2 of { happy_var_2 -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymCloseParen happy_var_3) -> 
	happyIn56
		 (tLet (getRange (happy_var_1,happy_var_3)) happy_var_2
	)}}}

happyReduce_229 = happyReduce 4# 47# happyReduction_229
happyReduction_229 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenParen happy_var_1) -> 
	case happyOut164 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseParen happy_var_4) -> 
	happyIn56
		 (tLet (getRange (happy_var_1,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}

happyReduce_230 = happySpecReduce_3  48# happyReduction_230
happyReduction_230 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut28 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymColon happy_var_2) -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn57
		 (let r = getRange (happy_var_1,happy_var_2,happy_var_3) -- the range is approximate only for TypedBindings
    in TypedBindings r $ defaultArg $ TBind r (map (pure . mkBoundName_) happy_var_1) happy_var_3
	)}}}

happyReduce_231 = happySpecReduce_3  49# happyReduction_231
happyReduction_231 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut30 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymColon happy_var_2) -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn58
		 (let r = getRange (happy_var_1,happy_var_2,happy_var_3) -- the range is approximate only for TypedBindings
    in TypedBindings r $ defaultArg $ TBind r (map (fmap mkBoundName_) happy_var_1) happy_var_3
	)}}}

happyReduce_232 = happyMonadReduce 2# 50# happyReduction_232
happyReduction_232 (happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut61 happy_x_1 of { happy_var_1 -> 
	(
      case reverse happy_var_1 of
        Left _ : _ -> parseError "Absurd lambda cannot have a body."
        _ : _      -> return [ b | Right b <- happy_var_1 ]
        []         -> parsePanic "Empty LamBinds")}
	) (\r -> happyReturn (happyIn59 r))

happyReduce_233 = happyMonadReduce 1# 51# happyReduction_233
happyReduction_233 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut62 happy_x_1 of { happy_var_1 -> 
	(
    case happy_var_1 of
      Left lb -> case reverse lb of
                   Right _ : _ -> parseError "Missing body for lambda"
                   Left h  : _ -> return $ Left ([ b | Right b <- init lb], h)
                   _           -> parseError "Unsupported variant of lambda"
      Right es -> return $ Right es)}
	) (\r -> happyReturn (happyIn60 r))

happyReduce_234 = happySpecReduce_2  52# happyReduction_234
happyReduction_234 happy_x_2
	happy_x_1
	 =  case happyOut70 happy_x_1 of { happy_var_1 -> 
	case happyOut61 happy_x_2 of { happy_var_2 -> 
	happyIn61
		 (map Right happy_var_1 ++ happy_var_2
	)}}

happyReduce_235 = happySpecReduce_2  52# happyReduction_235
happyReduction_235 happy_x_2
	happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	case happyOut61 happy_x_2 of { happy_var_2 -> 
	happyIn61
		 (Right (DomainFull happy_var_1) : happy_var_2
	)}}

happyReduce_236 = happySpecReduce_1  52# happyReduction_236
happyReduction_236 happy_x_1
	 =  case happyOut70 happy_x_1 of { happy_var_1 -> 
	happyIn61
		 (map Right happy_var_1
	)}

happyReduce_237 = happySpecReduce_1  52# happyReduction_237
happyReduction_237 happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	happyIn61
		 ([Right $ DomainFull happy_var_1]
	)}

happyReduce_238 = happySpecReduce_2  52# happyReduction_238
happyReduction_238 happy_x_2
	happy_x_1
	 =  happyIn61
		 ([Left NotHidden]
	)

happyReduce_239 = happySpecReduce_2  52# happyReduction_239
happyReduction_239 happy_x_2
	happy_x_1
	 =  happyIn61
		 ([Left Hidden]
	)

happyReduce_240 = happySpecReduce_2  52# happyReduction_240
happyReduction_240 happy_x_2
	happy_x_1
	 =  happyIn61
		 ([Left Instance]
	)

happyReduce_241 = happySpecReduce_2  53# happyReduction_241
happyReduction_241 happy_x_2
	happy_x_1
	 =  case happyOut70 happy_x_1 of { happy_var_1 -> 
	case happyOut61 happy_x_2 of { happy_var_2 -> 
	happyIn62
		 (Left $ map Right happy_var_1 ++ happy_var_2
	)}}

happyReduce_242 = happySpecReduce_2  53# happyReduction_242
happyReduction_242 happy_x_2
	happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	case happyOut61 happy_x_2 of { happy_var_2 -> 
	happyIn62
		 (Left $ Right (DomainFull happy_var_1) : happy_var_2
	)}}

happyReduce_243 = happySpecReduce_1  53# happyReduction_243
happyReduction_243 happy_x_1
	 =  case happyOut71 happy_x_1 of { happy_var_1 -> 
	happyIn62
		 (case happy_var_1 of
                                    Left lb -> Left $ map Right lb
                                    Right es -> Right es
	)}

happyReduce_244 = happySpecReduce_1  53# happyReduction_244
happyReduction_244 happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	happyIn62
		 (Left [Right $ DomainFull happy_var_1]
	)}

happyReduce_245 = happySpecReduce_2  53# happyReduction_245
happyReduction_245 happy_x_2
	happy_x_1
	 =  happyIn62
		 (Left [Left NotHidden]
	)

happyReduce_246 = happySpecReduce_2  53# happyReduction_246
happyReduction_246 happy_x_2
	happy_x_1
	 =  happyIn62
		 (Left [Left Hidden]
	)

happyReduce_247 = happySpecReduce_2  53# happyReduction_247
happyReduction_247 happy_x_2
	happy_x_1
	 =  happyIn62
		 (Left [Left Instance]
	)

happyReduce_248 = happyMonadReduce 3# 54# happyReduction_248
happyReduction_248 (happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut42 happy_x_1 of { happy_var_1 -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	( do
      p <- exprToLHS (RawApp (getRange happy_var_1) happy_var_1) ;
      return (p [] [], RHS happy_var_3, NoWhere, False))}}
	) (\r -> happyReturn (happyIn63 r))

happyReduce_249 = happyMonadReduce 4# 54# happyReduction_249
happyReduction_249 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut42 happy_x_2 of { happy_var_2 -> 
	case happyOut36 happy_x_4 of { happy_var_4 -> 
	( do
      p <- exprToLHS (RawApp (getRange happy_var_2) happy_var_2) ;
      return (p [] [], RHS happy_var_4, NoWhere, True))}}
	) (\r -> happyReturn (happyIn63 r))

happyReduce_250 = happyMonadReduce 1# 55# happyReduction_250
happyReduction_250 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut39 happy_x_1 of { happy_var_1 -> 
	( do
      p <- exprToLHS (RawApp (getRange happy_var_1) happy_var_1);
      return (p [] [], AbsurdRHS, NoWhere, False))}
	) (\r -> happyReturn (happyIn64 r))

happyReduce_251 = happyMonadReduce 2# 55# happyReduction_251
happyReduction_251 (happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut39 happy_x_2 of { happy_var_2 -> 
	( do
      p <- exprToLHS (RawApp (getRange happy_var_2) happy_var_2);
      return (p [] [], AbsurdRHS, NoWhere, True))}
	) (\r -> happyReturn (happyIn64 r))

happyReduce_252 = happySpecReduce_1  56# happyReduction_252
happyReduction_252 happy_x_1
	 =  case happyOut63 happy_x_1 of { happy_var_1 -> 
	happyIn65
		 (happy_var_1
	)}

happyReduce_253 = happySpecReduce_1  56# happyReduction_253
happyReduction_253 happy_x_1
	 =  case happyOut64 happy_x_1 of { happy_var_1 -> 
	happyIn65
		 (happy_var_1
	)}

happyReduce_254 = happySpecReduce_3  57# happyReduction_254
happyReduction_254 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut66 happy_x_1 of { happy_var_1 -> 
	case happyOut65 happy_x_3 of { happy_var_3 -> 
	happyIn66
		 (happy_var_3 : happy_var_1
	)}}

happyReduce_255 = happySpecReduce_3  57# happyReduction_255
happyReduction_255 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut64 happy_x_1 of { happy_var_1 -> 
	case happyOut65 happy_x_3 of { happy_var_3 -> 
	happyIn66
		 ([happy_var_3, happy_var_1]
	)}}

happyReduce_256 = happySpecReduce_1  57# happyReduction_256
happyReduction_256 happy_x_1
	 =  case happyOut63 happy_x_1 of { happy_var_1 -> 
	happyIn66
		 ([happy_var_1]
	)}

happyReduce_257 = happySpecReduce_2  58# happyReduction_257
happyReduction_257 happy_x_2
	happy_x_1
	 =  case happyOut68 happy_x_1 of { happy_var_1 -> 
	happyIn67
		 (happy_var_1
	)}

happyReduce_258 = happySpecReduce_2  59# happyReduction_258
happyReduction_258 happy_x_2
	happy_x_1
	 =  case happyOut70 happy_x_1 of { happy_var_1 -> 
	case happyOut68 happy_x_2 of { happy_var_2 -> 
	happyIn68
		 (happy_var_1 ++ happy_var_2
	)}}

happyReduce_259 = happySpecReduce_2  59# happyReduction_259
happyReduction_259 happy_x_2
	happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	case happyOut68 happy_x_2 of { happy_var_2 -> 
	happyIn68
		 (DomainFull happy_var_1 : happy_var_2
	)}}

happyReduce_260 = happySpecReduce_1  59# happyReduction_260
happyReduction_260 happy_x_1
	 =  case happyOut70 happy_x_1 of { happy_var_1 -> 
	happyIn68
		 (happy_var_1
	)}

happyReduce_261 = happySpecReduce_1  59# happyReduction_261
happyReduction_261 happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	happyIn68
		 ([DomainFull happy_var_1]
	)}

happyReduce_262 = happySpecReduce_2  60# happyReduction_262
happyReduction_262 happy_x_2
	happy_x_1
	 =  case happyOut70 happy_x_1 of { happy_var_1 -> 
	case happyOut69 happy_x_2 of { happy_var_2 -> 
	happyIn69
		 (happy_var_1 ++ happy_var_2
	)}}

happyReduce_263 = happySpecReduce_2  60# happyReduction_263
happyReduction_263 happy_x_2
	happy_x_1
	 =  case happyOut56 happy_x_1 of { happy_var_1 -> 
	case happyOut69 happy_x_2 of { happy_var_2 -> 
	happyIn69
		 (DomainFull happy_var_1 : happy_var_2
	)}}

happyReduce_264 = happySpecReduce_0  60# happyReduction_264
happyReduction_264  =  happyIn69
		 ([]
	)

happyReduce_265 = happySpecReduce_1  61# happyReduction_265
happyReduction_265 happy_x_1
	 =  case happyOut71 happy_x_1 of { happy_var_1 -> 
	happyIn70
		 (case happy_var_1 of
                             Left lbs -> lbs
                             Right _ -> fail "expected sequence of bound identifiers, not absurd pattern"
	)}

happyReduce_266 = happySpecReduce_1  62# happyReduction_266
happyReduction_266 happy_x_1
	 =  case happyOut26 happy_x_1 of { happy_var_1 -> 
	happyIn71
		 (Left [DomainFree defaultArgInfo $ mkBoundName_ happy_var_1]
	)}

happyReduce_267 = happySpecReduce_2  62# happyReduction_267
happyReduction_267 happy_x_2
	happy_x_1
	 =  case happyOut26 happy_x_2 of { happy_var_2 -> 
	happyIn71
		 (Left [DomainFree (setRelevance Irrelevant $ defaultArgInfo) $ mkBoundName_ happy_var_2]
	)}

happyReduce_268 = happySpecReduce_2  62# happyReduction_268
happyReduction_268 happy_x_2
	happy_x_1
	 =  case happyOut26 happy_x_2 of { happy_var_2 -> 
	happyIn71
		 (Left [DomainFree (setRelevance NonStrict $ defaultArgInfo) $ mkBoundName_ happy_var_2]
	)}

happyReduce_269 = happySpecReduce_3  62# happyReduction_269
happyReduction_269 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut29 happy_x_2 of { happy_var_2 -> 
	happyIn71
		 (mapLeft (map (DomainFree (setHiding Hidden $ defaultArgInfo) . mkBoundName_)) happy_var_2
	)}

happyReduce_270 = happySpecReduce_3  62# happyReduction_270
happyReduction_270 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut28 happy_x_2 of { happy_var_2 -> 
	happyIn71
		 (Left $ map (DomainFree (setHiding Instance $ defaultArgInfo) . mkBoundName_) happy_var_2
	)}

happyReduce_271 = happyReduce 4# 62# happyReduction_271
happyReduction_271 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut28 happy_x_3 of { happy_var_3 -> 
	happyIn71
		 (Left $ map (DomainFree (setHiding Hidden $ setRelevance Irrelevant $ defaultArgInfo) . mkBoundName_) happy_var_3
	) `HappyStk` happyRest}

happyReduce_272 = happyReduce 4# 62# happyReduction_272
happyReduction_272 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut28 happy_x_3 of { happy_var_3 -> 
	happyIn71
		 (Left $ map (DomainFree (setHiding Instance $ setRelevance Irrelevant $ defaultArgInfo) . mkBoundName_) happy_var_3
	) `HappyStk` happyRest}

happyReduce_273 = happyReduce 4# 62# happyReduction_273
happyReduction_273 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut28 happy_x_3 of { happy_var_3 -> 
	happyIn71
		 (Left $ map (DomainFree (setHiding Hidden $ setRelevance NonStrict $ defaultArgInfo) . mkBoundName_) happy_var_3
	) `HappyStk` happyRest}

happyReduce_274 = happyReduce 4# 62# happyReduction_274
happyReduction_274 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut28 happy_x_3 of { happy_var_3 -> 
	happyIn71
		 (Left $ map (DomainFree  (setHiding Instance $ setRelevance NonStrict $ defaultArgInfo) . mkBoundName_) happy_var_3
	) `HappyStk` happyRest}

happyReduce_275 = happyMonadReduce 1# 63# happyReduction_275
happyReduction_275 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut73 happy_x_1 of { happy_var_1 -> 
	( mergeImportDirectives happy_var_1)}
	) (\r -> happyReturn (happyIn72 r))

happyReduce_276 = happySpecReduce_2  64# happyReduction_276
happyReduction_276 happy_x_2
	happy_x_1
	 =  case happyOut74 happy_x_1 of { happy_var_1 -> 
	case happyOut73 happy_x_2 of { happy_var_2 -> 
	happyIn73
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_277 = happySpecReduce_0  64# happyReduction_277
happyReduction_277  =  happyIn73
		 ([]
	)

happyReduce_278 = happySpecReduce_1  65# happyReduction_278
happyReduction_278 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPublic happy_var_1) -> 
	happyIn74
		 (defaultImportDir { importDirRange = getRange happy_var_1, publicOpen = True }
	)}

happyReduce_279 = happySpecReduce_1  65# happyReduction_279
happyReduction_279 happy_x_1
	 =  case happyOut75 happy_x_1 of { happy_var_1 -> 
	happyIn74
		 (defaultImportDir { importDirRange = snd happy_var_1, using    = fst happy_var_1 }
	)}

happyReduce_280 = happySpecReduce_1  65# happyReduction_280
happyReduction_280 happy_x_1
	 =  case happyOut76 happy_x_1 of { happy_var_1 -> 
	happyIn74
		 (defaultImportDir { importDirRange = snd happy_var_1, hiding   = fst happy_var_1 }
	)}

happyReduce_281 = happySpecReduce_1  65# happyReduction_281
happyReduction_281 happy_x_1
	 =  case happyOut77 happy_x_1 of { happy_var_1 -> 
	happyIn74
		 (defaultImportDir { importDirRange = snd happy_var_1, impRenaming = fst happy_var_1 }
	)}

happyReduce_282 = happyReduce 4# 66# happyReduction_282
happyReduction_282 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwUsing happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymOpenParen happy_var_2) -> 
	case happyOut82 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseParen happy_var_4) -> 
	happyIn75
		 ((Using happy_var_3 , getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4))
	) `HappyStk` happyRest}}}}

happyReduce_283 = happyReduce 4# 67# happyReduction_283
happyReduction_283 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwHiding happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymOpenParen happy_var_2) -> 
	case happyOut82 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseParen happy_var_4) -> 
	happyIn76
		 ((happy_var_3 , getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4))
	) `HappyStk` happyRest}}}}

happyReduce_284 = happyReduce 4# 68# happyReduction_284
happyReduction_284 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwRenaming happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymOpenParen happy_var_2) -> 
	case happyOut78 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymCloseParen happy_var_4) -> 
	happyIn77
		 ((happy_var_3 , getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4))
	) `HappyStk` happyRest}}}}

happyReduce_285 = happySpecReduce_3  68# happyReduction_285
happyReduction_285 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwRenaming happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymOpenParen happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymCloseParen happy_var_3) -> 
	happyIn77
		 (([] , getRange (happy_var_1,happy_var_2,happy_var_3))
	)}}}

happyReduce_286 = happySpecReduce_3  69# happyReduction_286
happyReduction_286 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut79 happy_x_1 of { happy_var_1 -> 
	case happyOut78 happy_x_3 of { happy_var_3 -> 
	happyIn78
		 (happy_var_1 : happy_var_3
	)}}

happyReduce_287 = happySpecReduce_1  69# happyReduction_287
happyReduction_287 happy_x_1
	 =  case happyOut79 happy_x_1 of { happy_var_1 -> 
	happyIn78
		 ([happy_var_1]
	)}

happyReduce_288 = happySpecReduce_3  70# happyReduction_288
happyReduction_288 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut80 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwTo happy_var_2) -> 
	case happyOut18 happy_x_3 of { happy_var_3 -> 
	happyIn79
		 (Renaming happy_var_1 (setImportedName happy_var_1 happy_var_3) (getRange happy_var_2)
	)}}}

happyReduce_289 = happySpecReduce_2  71# happyReduction_289
happyReduction_289 happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_2 of { happy_var_2 -> 
	happyIn80
		 (ImportedName happy_var_2
	)}

happyReduce_290 = happySpecReduce_3  71# happyReduction_290
happyReduction_290 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_3 of { happy_var_3 -> 
	happyIn80
		 (ImportedModule happy_var_3
	)}

happyReduce_291 = happySpecReduce_1  72# happyReduction_291
happyReduction_291 happy_x_1
	 =  case happyOut18 happy_x_1 of { happy_var_1 -> 
	happyIn81
		 (ImportedName happy_var_1
	)}

happyReduce_292 = happySpecReduce_2  72# happyReduction_292
happyReduction_292 happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_2 of { happy_var_2 -> 
	happyIn81
		 (ImportedModule happy_var_2
	)}

happyReduce_293 = happySpecReduce_0  73# happyReduction_293
happyReduction_293  =  happyIn82
		 ([]
	)

happyReduce_294 = happySpecReduce_1  73# happyReduction_294
happyReduction_294 happy_x_1
	 =  case happyOut83 happy_x_1 of { happy_var_1 -> 
	happyIn82
		 (happy_var_1
	)}

happyReduce_295 = happySpecReduce_1  74# happyReduction_295
happyReduction_295 happy_x_1
	 =  case happyOut81 happy_x_1 of { happy_var_1 -> 
	happyIn83
		 ([happy_var_1]
	)}

happyReduce_296 = happySpecReduce_3  74# happyReduction_296
happyReduction_296 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut81 happy_x_1 of { happy_var_1 -> 
	case happyOut83 happy_x_3 of { happy_var_3 -> 
	happyIn83
		 (happy_var_1 : happy_var_3
	)}}

happyReduce_297 = happyMonadReduce 3# 75# happyReduction_297
happyReduction_297 (happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut37 happy_x_1 of { happy_var_1 -> 
	case happyOut87 happy_x_2 of { happy_var_2 -> 
	case happyOut86 happy_x_3 of { happy_var_3 -> 
	( exprToLHS happy_var_1 >>= \p -> return (p happy_var_2 happy_var_3))}}}
	) (\r -> happyReturn (happyIn84 r))

happyReduce_298 = happyReduce 4# 75# happyReduction_298
happyReduction_298 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymEllipsis happy_var_1) -> 
	case happyOut85 happy_x_2 of { happy_var_2 -> 
	case happyOut87 happy_x_3 of { happy_var_3 -> 
	case happyOut86 happy_x_4 of { happy_var_4 -> 
	happyIn84
		 (Ellipsis (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_2 happy_var_3 happy_var_4
	) `HappyStk` happyRest}}}}

happyReduce_299 = happySpecReduce_0  76# happyReduction_299
happyReduction_299  =  happyIn85
		 ([]
	)

happyReduce_300 = happyMonadReduce 3# 76# happyReduction_300
happyReduction_300 (happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut42 happy_x_2 of { happy_var_2 -> 
	case happyOut85 happy_x_3 of { happy_var_3 -> 
	( exprToPattern (RawApp (getRange happy_var_2) happy_var_2) >>= \p ->
                   return (p : happy_var_3))}}
	) (\r -> happyReturn (happyIn85 r))

happyReduce_301 = happySpecReduce_0  77# happyReduction_301
happyReduction_301  =  happyIn86
		 ([]
	)

happyReduce_302 = happySpecReduce_2  77# happyReduction_302
happyReduction_302 happy_x_2
	happy_x_1
	 =  case happyOut36 happy_x_2 of { happy_var_2 -> 
	happyIn86
		 (case happy_var_2 of { WithApp _ e es -> e : es; e -> [e] }
	)}

happyReduce_303 = happySpecReduce_0  78# happyReduction_303
happyReduction_303  =  happyIn87
		 ([]
	)

happyReduce_304 = happySpecReduce_2  78# happyReduction_304
happyReduction_304 happy_x_2
	happy_x_1
	 =  case happyOut37 happy_x_2 of { happy_var_2 -> 
	happyIn87
		 (case happy_var_2 of { WithApp _ e es -> e : es; e -> [e] }
	)}

happyReduce_305 = happySpecReduce_0  79# happyReduction_305
happyReduction_305  =  happyIn88
		 (NoWhere
	)

happyReduce_306 = happySpecReduce_2  79# happyReduction_306
happyReduction_306 happy_x_2
	happy_x_1
	 =  case happyOut165 happy_x_2 of { happy_var_2 -> 
	happyIn88
		 (AnyWhere happy_var_2
	)}

happyReduce_307 = happyReduce 4# 79# happyReduction_307
happyReduction_307 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut165 happy_x_4 of { happy_var_4 -> 
	happyIn88
		 (SomeWhere happy_var_2 happy_var_4
	) `HappyStk` happyRest}}

happyReduce_308 = happyReduce 4# 79# happyReduction_308
happyReduction_308 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut125 happy_x_2 of { happy_var_2 -> 
	case happyOut165 happy_x_4 of { happy_var_4 -> 
	happyIn88
		 (SomeWhere happy_var_2 happy_var_4
	) `HappyStk` happyRest}}

happyReduce_309 = happySpecReduce_2  80# happyReduction_309
happyReduction_309 happy_x_2
	happy_x_1
	 =  case happyOut36 happy_x_1 of { happy_var_1 -> 
	case happyOut88 happy_x_2 of { happy_var_2 -> 
	happyIn89
		 (ExprWhere happy_var_1 happy_var_2
	)}}

happyReduce_310 = happySpecReduce_1  81# happyReduction_310
happyReduction_310 happy_x_1
	 =  case happyOut101 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 (happy_var_1
	)}

happyReduce_311 = happySpecReduce_1  81# happyReduction_311
happyReduction_311 happy_x_1
	 =  case happyOut93 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 (happy_var_1
	)}

happyReduce_312 = happySpecReduce_1  81# happyReduction_312
happyReduction_312 happy_x_1
	 =  case happyOut95 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_313 = happySpecReduce_1  81# happyReduction_313
happyReduction_313 happy_x_1
	 =  case happyOut96 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_314 = happySpecReduce_1  81# happyReduction_314
happyReduction_314 happy_x_1
	 =  case happyOut97 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_315 = happySpecReduce_1  81# happyReduction_315
happyReduction_315 happy_x_1
	 =  case happyOut98 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_316 = happySpecReduce_1  81# happyReduction_316
happyReduction_316 happy_x_1
	 =  case happyOut100 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_317 = happySpecReduce_1  81# happyReduction_317
happyReduction_317 happy_x_1
	 =  case happyOut102 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_318 = happySpecReduce_1  81# happyReduction_318
happyReduction_318 happy_x_1
	 =  case happyOut103 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_319 = happySpecReduce_1  81# happyReduction_319
happyReduction_319 happy_x_1
	 =  case happyOut104 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_320 = happySpecReduce_1  81# happyReduction_320
happyReduction_320 happy_x_1
	 =  case happyOut105 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_321 = happySpecReduce_1  81# happyReduction_321
happyReduction_321 happy_x_1
	 =  case happyOut106 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_322 = happySpecReduce_1  81# happyReduction_322
happyReduction_322 happy_x_1
	 =  case happyOut107 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_323 = happySpecReduce_1  81# happyReduction_323
happyReduction_323 happy_x_1
	 =  case happyOut108 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_324 = happySpecReduce_1  81# happyReduction_324
happyReduction_324 happy_x_1
	 =  case happyOut120 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 (happy_var_1
	)}

happyReduce_325 = happySpecReduce_1  81# happyReduction_325
happyReduction_325 happy_x_1
	 =  case happyOut123 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_326 = happySpecReduce_1  81# happyReduction_326
happyReduction_326 happy_x_1
	 =  case happyOut124 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_327 = happySpecReduce_1  81# happyReduction_327
happyReduction_327 happy_x_1
	 =  case happyOut127 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_328 = happySpecReduce_1  81# happyReduction_328
happyReduction_328 happy_x_1
	 =  case happyOut110 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_329 = happySpecReduce_1  81# happyReduction_329
happyReduction_329 happy_x_1
	 =  case happyOut111 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_330 = happySpecReduce_1  81# happyReduction_330
happyReduction_330 happy_x_1
	 =  case happyOut109 happy_x_1 of { happy_var_1 -> 
	happyIn90
		 ([happy_var_1]
	)}

happyReduce_331 = happySpecReduce_3  82# happyReduction_331
happyReduction_331 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut19 happy_x_1 of { happy_var_1 -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn91
		 (map (\ x -> TypeSig defaultArgInfo x happy_var_3) happy_var_1
	)}}

happyReduce_332 = happySpecReduce_3  83# happyReduction_332
happyReduction_332 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut23 happy_x_1 of { happy_var_1 -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn92
		 (map (fmap (\ x -> TypeSig defaultArgInfo x happy_var_3)) happy_var_1
	)}}

happyReduce_333 = happySpecReduce_2  83# happyReduction_333
happyReduction_333 happy_x_2
	happy_x_1
	 =  case happyOut157 happy_x_2 of { happy_var_2 -> 
	happyIn92
		 (let
      setInstance (TypeSig info x t) = TypeSig (setHiding Instance info) x t
      setInstance _ = __IMPOSSIBLE__ in
    map (fmap setInstance) happy_var_2
	)}

happyReduce_334 = happyMonadReduce 3# 84# happyReduction_334
happyReduction_334 (happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut84 happy_x_1 of { happy_var_1 -> 
	case happyOut94 happy_x_2 of { happy_var_2 -> 
	case happyOut88 happy_x_3 of { happy_var_3 -> 
	( funClauseOrTypeSigs happy_var_1 happy_var_2 happy_var_3)}}}
	) (\r -> happyReturn (happyIn93 r))

happyReduce_335 = happySpecReduce_2  85# happyReduction_335
happyReduction_335 happy_x_2
	happy_x_1
	 =  case happyOut36 happy_x_2 of { happy_var_2 -> 
	happyIn94
		 (JustRHS (RHS happy_var_2)
	)}

happyReduce_336 = happySpecReduce_2  85# happyReduction_336
happyReduction_336 happy_x_2
	happy_x_1
	 =  case happyOut36 happy_x_2 of { happy_var_2 -> 
	happyIn94
		 (TypeSigsRHS happy_var_2
	)}

happyReduce_337 = happySpecReduce_0  85# happyReduction_337
happyReduction_337  =  happyIn94
		 (JustRHS AbsurdRHS
	)

happyReduce_338 = happyReduce 7# 86# happyReduction_338
happyReduction_338 (happy_x_7 `HappyStk`
	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 happyOutTok happy_x_1 of { (TokKeyword KwData happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymColon happy_var_4) -> 
	case happyOut36 happy_x_5 of { happy_var_5 -> 
	case happyOutTok happy_x_6 of { (TokKeyword KwWhere happy_var_6) -> 
	case happyOut165 happy_x_7 of { happy_var_7 -> 
	happyIn95
		 (Data (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5,happy_var_6,happy_var_7)) Inductive happy_var_2 happy_var_3 (Just happy_var_5) happy_var_7
	) `HappyStk` happyRest}}}}}}}

happyReduce_339 = happyReduce 7# 86# happyReduction_339
happyReduction_339 (happy_x_7 `HappyStk`
	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 happyOutTok happy_x_1 of { (TokKeyword KwCoData happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymColon happy_var_4) -> 
	case happyOut36 happy_x_5 of { happy_var_5 -> 
	case happyOutTok happy_x_6 of { (TokKeyword KwWhere happy_var_6) -> 
	case happyOut165 happy_x_7 of { happy_var_7 -> 
	happyIn95
		 (Data (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5,happy_var_6,happy_var_7)) CoInductive happy_var_2 happy_var_3 (Just happy_var_5) happy_var_7
	) `HappyStk` happyRest}}}}}}}

happyReduce_340 = happyReduce 5# 86# happyReduction_340
happyReduction_340 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwData happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokKeyword KwWhere happy_var_4) -> 
	case happyOut165 happy_x_5 of { happy_var_5 -> 
	happyIn95
		 (Data (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) Inductive happy_var_2 happy_var_3 Nothing happy_var_5
	) `HappyStk` happyRest}}}}}

happyReduce_341 = happyReduce 5# 86# happyReduction_341
happyReduction_341 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwCoData happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokKeyword KwWhere happy_var_4) -> 
	case happyOut165 happy_x_5 of { happy_var_5 -> 
	happyIn95
		 (Data (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) CoInductive happy_var_2 happy_var_3 Nothing happy_var_5
	) `HappyStk` happyRest}}}}}

happyReduce_342 = happyReduce 5# 87# 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 happyOutTok happy_x_1 of { (TokKeyword KwData happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymColon happy_var_4) -> 
	case happyOut36 happy_x_5 of { happy_var_5 -> 
	happyIn96
		 (DataSig (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) Inductive happy_var_2 happy_var_3 happy_var_5
	) `HappyStk` happyRest}}}}}

happyReduce_343 = happyMonadReduce 7# 88# happyReduction_343
happyReduction_343 (happy_x_7 `HappyStk`
	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) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokKeyword KwRecord happy_var_1) -> 
	case happyOut44 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymColon happy_var_4) -> 
	case happyOut36 happy_x_5 of { happy_var_5 -> 
	case happyOutTok happy_x_6 of { (TokKeyword KwWhere happy_var_6) -> 
	case happyOut159 happy_x_7 of { happy_var_7 -> 
	( exprToName happy_var_2 >>= \ n -> let ((x,y,z),ds) = happy_var_7 in return $ Record (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5,happy_var_6,happy_var_7)) n x y z happy_var_3 (Just happy_var_5) ds)}}}}}}}
	) (\r -> happyReturn (happyIn97 r))

happyReduce_344 = happyMonadReduce 5# 88# happyReduction_344
happyReduction_344 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokKeyword KwRecord happy_var_1) -> 
	case happyOut44 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokKeyword KwWhere happy_var_4) -> 
	case happyOut159 happy_x_5 of { happy_var_5 -> 
	( exprToName happy_var_2 >>= \ n -> let ((x,y,z),ds) = happy_var_5 in return $ Record (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) n x y z happy_var_3 Nothing ds)}}}}}
	) (\r -> happyReturn (happyIn97 r))

happyReduce_345 = happyMonadReduce 5# 89# happyReduction_345
happyReduction_345 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokKeyword KwRecord happy_var_1) -> 
	case happyOut44 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymColon happy_var_4) -> 
	case happyOut36 happy_x_5 of { happy_var_5 -> 
	( exprToName happy_var_2 >>= \ n -> return $ RecordSig (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) n happy_var_3 happy_var_5)}}}}}
	) (\r -> happyReturn (happyIn98 r))

happyReduce_346 = happySpecReduce_2  90# happyReduction_346
happyReduction_346 happy_x_2
	happy_x_1
	 =  case happyOut18 happy_x_2 of { happy_var_2 -> 
	happyIn99
		 ((happy_var_2, NotInstanceDef)
	)}

happyReduce_347 = happyReduce 5# 90# happyReduction_347
happyReduction_347 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut18 happy_x_4 of { happy_var_4 -> 
	happyIn99
		 ((happy_var_4, InstanceDef)
	) `HappyStk` happyRest}

happyReduce_348 = happySpecReduce_3  91# happyReduction_348
happyReduction_348 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInfix happy_var_1) -> 
	case happyOut17 happy_x_2 of { happy_var_2 -> 
	case happyOut27 happy_x_3 of { happy_var_3 -> 
	happyIn100
		 (Infix (Fixity (getRange (happy_var_1,happy_var_3)) (Related happy_var_2) NonAssoc)   happy_var_3
	)}}}

happyReduce_349 = happySpecReduce_3  91# happyReduction_349
happyReduction_349 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInfixL happy_var_1) -> 
	case happyOut17 happy_x_2 of { happy_var_2 -> 
	case happyOut27 happy_x_3 of { happy_var_3 -> 
	happyIn100
		 (Infix (Fixity (getRange (happy_var_1,happy_var_3)) (Related happy_var_2) LeftAssoc)  happy_var_3
	)}}}

happyReduce_350 = happySpecReduce_3  91# happyReduction_350
happyReduction_350 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInfixR happy_var_1) -> 
	case happyOut17 happy_x_2 of { happy_var_2 -> 
	case happyOut27 happy_x_3 of { happy_var_3 -> 
	happyIn100
		 (Infix (Fixity (getRange (happy_var_1,happy_var_3)) (Related happy_var_2) RightAssoc) happy_var_3
	)}}}

happyReduce_351 = happySpecReduce_2  92# happyReduction_351
happyReduction_351 happy_x_2
	happy_x_1
	 =  case happyOut157 happy_x_2 of { happy_var_2 -> 
	happyIn101
		 (let
                inst i | getHiding i == Instance = InstanceDef
                       | otherwise               = NotInstanceDef
                toField (Arg info (TypeSig info' x t)) = Field (inst info') x (Arg info t)
              in map toField happy_var_2
	)}

happyReduce_352 = happySpecReduce_2  93# happyReduction_352
happyReduction_352 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwMutual happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	happyIn102
		 (Mutual (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_353 = happySpecReduce_2  94# happyReduction_353
happyReduction_353 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwAbstract happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	happyIn103
		 (Abstract (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_354 = happySpecReduce_2  95# happyReduction_354
happyReduction_354 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPrivate happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	happyIn104
		 (Private (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_355 = happySpecReduce_2  96# happyReduction_355
happyReduction_355 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInstance happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	happyIn105
		 (InstanceB (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_356 = happySpecReduce_2  97# happyReduction_356
happyReduction_356 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwMacro happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	happyIn106
		 (Macro (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_357 = happySpecReduce_2  98# happyReduction_357
happyReduction_357 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPostulate happy_var_1) -> 
	case happyOut164 happy_x_2 of { happy_var_2 -> 
	happyIn107
		 (Postulate (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_358 = happySpecReduce_2  99# happyReduction_358
happyReduction_358 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwPrimitive happy_var_1) -> 
	case happyOut155 happy_x_2 of { happy_var_2 -> 
	happyIn108
		 (Primitive (fuseRange happy_var_1 happy_var_2) happy_var_2
	)}}

happyReduce_359 = happySpecReduce_3  100# happyReduction_359
happyReduction_359 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwUnquoteDecl happy_var_1) -> 
	case happyOut36 happy_x_3 of { happy_var_3 -> 
	happyIn109
		 (UnquoteDecl (fuseRange happy_var_1 happy_var_3) [] happy_var_3
	)}}

happyReduce_360 = happyReduce 4# 100# happyReduction_360
happyReduction_360 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwUnquoteDecl happy_var_1) -> 
	case happyOut19 happy_x_2 of { happy_var_2 -> 
	case happyOut36 happy_x_4 of { happy_var_4 -> 
	happyIn109
		 (UnquoteDecl (fuseRange happy_var_1 happy_var_4) happy_var_2 happy_var_4
	) `HappyStk` happyRest}}}

happyReduce_361 = happyReduce 4# 100# happyReduction_361
happyReduction_361 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwUnquoteDef happy_var_1) -> 
	case happyOut19 happy_x_2 of { happy_var_2 -> 
	case happyOut36 happy_x_4 of { happy_var_4 -> 
	happyIn109
		 (UnquoteDef (fuseRange happy_var_1 happy_var_4) happy_var_2 happy_var_4
	) `HappyStk` happyRest}}}

happyReduce_362 = happyMonadReduce 5# 101# happyReduction_362
happyReduction_362 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut114 happy_x_3 of { happy_var_3 -> 
	case happyOut113 happy_x_5 of { happy_var_5 -> 
	(
  case happy_var_2 of
    Name _ [_] -> case mkNotation happy_var_3 (map rangedThing happy_var_5) of
      Left err -> parseError $ "Malformed syntax declaration: " ++ err
      Right n -> return $ Syntax happy_var_2 n
    _ -> parseError "Syntax declarations are allowed only for simple names (without holes)")}}}
	) (\r -> happyReturn (happyIn110 r))

happyReduce_363 = happyMonadReduce 5# 102# happyReduction_363
happyReduction_363 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokKeyword KwPatternSyn happy_var_1) -> 
	case happyOut18 happy_x_2 of { happy_var_2 -> 
	case happyOut112 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymEqual happy_var_4) -> 
	case happyOut36 happy_x_5 of { happy_var_5 -> 
	( do
  p <- exprToPattern happy_var_5
  return (PatternSyn (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) happy_var_2 happy_var_3 p))}}}}}
	) (\r -> happyReturn (happyIn111 r))

happyReduce_364 = happySpecReduce_0  103# happyReduction_364
happyReduction_364  =  happyIn112
		 ([]
	)

happyReduce_365 = happyMonadReduce 1# 103# happyReduction_365
happyReduction_365 (happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut61 happy_x_1 of { happy_var_1 -> 
	( patternSynArgs happy_var_1)}
	) (\r -> happyReturn (happyIn112 r))

happyReduce_366 = happySpecReduce_1  104# happyReduction_366
happyReduction_366 happy_x_1
	 =  case happyOut118 happy_x_1 of { happy_var_1 -> 
	happyIn113
		 ([happy_var_1]
	)}

happyReduce_367 = happySpecReduce_2  104# happyReduction_367
happyReduction_367 happy_x_2
	happy_x_1
	 =  case happyOut113 happy_x_1 of { happy_var_1 -> 
	case happyOut118 happy_x_2 of { happy_var_2 -> 
	happyIn113
		 (happy_var_1 ++ [happy_var_2]
	)}}

happyReduce_368 = happySpecReduce_1  105# happyReduction_368
happyReduction_368 happy_x_1
	 =  case happyOut115 happy_x_1 of { happy_var_1 -> 
	happyIn114
		 ([happy_var_1]
	)}

happyReduce_369 = happySpecReduce_2  105# happyReduction_369
happyReduction_369 happy_x_2
	happy_x_1
	 =  case happyOut114 happy_x_1 of { happy_var_1 -> 
	case happyOut115 happy_x_2 of { happy_var_2 -> 
	happyIn114
		 (happy_var_1 ++ [happy_var_2]
	)}}

happyReduce_370 = happySpecReduce_1  106# happyReduction_370
happyReduction_370 happy_x_1
	 =  case happyOut116 happy_x_1 of { happy_var_1 -> 
	happyIn115
		 (defaultNamedArg happy_var_1
	)}

happyReduce_371 = happySpecReduce_3  106# happyReduction_371
happyReduction_371 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut117 happy_x_2 of { happy_var_2 -> 
	happyIn115
		 (setHiding Hidden   $ defaultNamedArg happy_var_2
	)}

happyReduce_372 = happySpecReduce_3  106# happyReduction_372
happyReduction_372 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut117 happy_x_2 of { happy_var_2 -> 
	happyIn115
		 (setHiding Instance $ defaultNamedArg happy_var_2
	)}

happyReduce_373 = happyReduce 5# 106# happyReduction_373
happyReduction_373 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut118 happy_x_2 of { happy_var_2 -> 
	case happyOut117 happy_x_4 of { happy_var_4 -> 
	happyIn115
		 (setHiding Hidden   $ defaultArg $ named happy_var_2 happy_var_4
	) `HappyStk` happyRest}}

happyReduce_374 = happyReduce 5# 106# happyReduction_374
happyReduction_374 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut118 happy_x_2 of { happy_var_2 -> 
	case happyOut117 happy_x_4 of { happy_var_4 -> 
	happyIn115
		 (setHiding Instance $ defaultArg $ named happy_var_2 happy_var_4
	) `HappyStk` happyRest}}

happyReduce_375 = happySpecReduce_1  107# happyReduction_375
happyReduction_375 happy_x_1
	 =  case happyOut118 happy_x_1 of { happy_var_1 -> 
	happyIn116
		 (ExprHole (rangedThing happy_var_1)
	)}

happyReduce_376 = happyReduce 6# 107# happyReduction_376
happyReduction_376 (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 happyOut118 happy_x_3 of { happy_var_3 -> 
	case happyOut118 happy_x_5 of { happy_var_5 -> 
	happyIn116
		 (LambdaHole (rangedThing happy_var_3) (rangedThing happy_var_5)
	) `HappyStk` happyRest}}

happyReduce_377 = happyReduce 6# 107# happyReduction_377
happyReduction_377 (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 happyOut118 happy_x_5 of { happy_var_5 -> 
	happyIn116
		 (LambdaHole "_" (rangedThing happy_var_5)
	) `HappyStk` happyRest}

happyReduce_378 = happySpecReduce_1  108# happyReduction_378
happyReduction_378 happy_x_1
	 =  case happyOut118 happy_x_1 of { happy_var_1 -> 
	happyIn117
		 (ExprHole (rangedThing happy_var_1)
	)}

happyReduce_379 = happyReduce 4# 108# happyReduction_379
happyReduction_379 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut118 happy_x_2 of { happy_var_2 -> 
	case happyOut118 happy_x_4 of { happy_var_4 -> 
	happyIn117
		 (LambdaHole (rangedThing happy_var_2) (rangedThing happy_var_4)
	) `HappyStk` happyRest}}

happyReduce_380 = happyReduce 4# 108# happyReduction_380
happyReduction_380 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut118 happy_x_4 of { happy_var_4 -> 
	happyIn117
		 (LambdaHole "_" (rangedThing happy_var_4)
	) `HappyStk` happyRest}

happyReduce_381 = happySpecReduce_1  109# happyReduction_381
happyReduction_381 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokId happy_var_1) -> 
	happyIn118
		 (Ranged (getRange $ fst happy_var_1) (stringToRawName $ snd happy_var_1)
	)}

happyReduce_382 = happySpecReduce_1  110# happyReduction_382
happyReduction_382 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwOpen happy_var_1) -> 
	happyIn119
		 (Just (getRange happy_var_1)
	)}

happyReduce_383 = happySpecReduce_0  110# happyReduction_383
happyReduction_383  =  happyIn119
		 (Nothing
	)

happyReduce_384 = happyMonadReduce 5# 111# 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) tk
	 = happyThen (case happyOut119 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwImport happy_var_2) -> 
	case happyOut25 happy_x_3 of { happy_var_3 -> 
	case happyOut121 happy_x_4 of { happy_var_4 -> 
	case happyOut72 happy_x_5 of { happy_var_5 -> 
	(
    let
    { doOpen = maybe DontOpen (const DoOpen) happy_var_1
    ; m   = happy_var_3
    ; es  = happy_var_4
    ; dir = happy_var_5
    ; r   = getRange (m, es, dir)
    ; mr  = getRange m
    ; unique = hashString $ show $ (Nothing :: Maybe ()) <$ r
         -- turn range into unique id, but delete file path
         -- which is absolute and messes up suite of failing tests
         -- (different hashs on different installations)
         -- TODO: Don't use (insecure) hashes in this way.
    ; fresh = Name mr [ Id $ stringToRawName $ ".#" ++ show m ++ "-" ++ show unique ]
    ; impStm asR = Import mr m (Just (AsName fresh asR)) DontOpen defaultImportDir
    ; appStm m' es =
        let r = getRange (m, es) in
        Private r
          [ ModuleMacro r m'
             (SectionApp (getRange es) []
               (RawApp (getRange es) (Ident (QName fresh) : es)))
             doOpen dir
          ]
    ; (initArgs, last2Args) = splitAt (length es - 2) es
    ; parseAsClause = case last2Args of
      { [ Ident (QName (Name asR [Id x]))
        , Ident (QName m')
        ] | rawNameToString x == "as" -> Just (asR, m')
      ; _ -> Nothing
      }
    } in
    case es of
      { [] -> return [Import mr m Nothing doOpen dir]
      ; _ | Just (asR, m') <- parseAsClause ->
              if null initArgs then return
                 [ Import (getRange (m, asR, m', dir)) m
                     (Just (AsName m' asR)) doOpen dir
                 ]
              else return [ impStm asR, appStm m' initArgs ]
          | DontOpen <- doOpen -> parseErrorAt (fromJust $ rStart' $ getRange happy_var_2) "An import statement with module instantiation does not actually import the module.  This statement achieves nothing.  Either add the `open' keyword or bind the instantiated module with an `as' clause."
          | otherwise -> return
              [ impStm noRange
              , appStm (noName $ beginningOf $ getRange m) es
              ]
      })}}}}}
	) (\r -> happyReturn (happyIn120 r))

happyReduce_385 = happyReduce 4# 111# happyReduction_385
happyReduction_385 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut25 happy_x_2 of { happy_var_2 -> 
	case happyOut121 happy_x_3 of { happy_var_3 -> 
	case happyOut72 happy_x_4 of { happy_var_4 -> 
	happyIn120
		 (let
    { m   = happy_var_2
    ; es  = happy_var_3
    ; dir = happy_var_4
    ; r   = getRange (m, es, dir)
    } in
    [ case es of
      { []  -> Open r m dir
      ; _   -> Private r [ ModuleMacro r (noName $ beginningOf $ getRange m)
                             (SectionApp (getRange (m , es)) [] (RawApp (fuseRange m es) (Ident m : es)))
                             DoOpen dir
                         ]
      }
    ]
	) `HappyStk` happyRest}}}

happyReduce_386 = happyReduce 6# 111# happyReduction_386
happyReduction_386 (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 happyOut25 happy_x_2 of { happy_var_2 -> 
	case happyOut72 happy_x_6 of { happy_var_6 -> 
	happyIn120
		 (let r = getRange happy_var_2 in
    [ Private r [ ModuleMacro r (noName $ beginningOf $ getRange happy_var_2)
                (RecordModuleIFS r happy_var_2) DoOpen happy_var_6
                ]
    ]
	) `HappyStk` happyRest}}

happyReduce_387 = happySpecReduce_0  112# happyReduction_387
happyReduction_387  =  happyIn121
		 ([]
	)

happyReduce_388 = happySpecReduce_2  112# happyReduction_388
happyReduction_388 happy_x_2
	happy_x_1
	 =  case happyOut45 happy_x_1 of { happy_var_1 -> 
	case happyOut121 happy_x_2 of { happy_var_2 -> 
	happyIn121
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_389 = happyReduce 4# 113# happyReduction_389
happyReduction_389 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut25 happy_x_1 of { happy_var_1 -> 
	case happyOutTok happy_x_2 of { (TokSymbol SymDoubleOpenBrace happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymEllipsis happy_var_3) -> 
	case happyOut20 happy_x_4 of { happy_var_4 -> 
	happyIn122
		 ((\ts ->
                    if null ts then return $ RecordModuleIFS (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_1
                    else parseError "No bindings allowed for record module with non-canonical implicits" )
	) `HappyStk` happyRest}}}}

happyReduce_390 = happySpecReduce_2  113# happyReduction_390
happyReduction_390 happy_x_2
	happy_x_1
	 =  case happyOut25 happy_x_1 of { happy_var_1 -> 
	case happyOut121 happy_x_2 of { happy_var_2 -> 
	happyIn122
		 ((\ts -> return $ SectionApp (getRange (happy_var_1, happy_var_2)) ts (RawApp (fuseRange happy_var_1 happy_var_2) (Ident happy_var_1 : happy_var_2)) )
	)}}

happyReduce_391 = happyMonadReduce 6# 114# happyReduction_391
happyReduction_391 (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) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokKeyword KwModule happy_var_1) -> 
	case happyOut25 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOut122 happy_x_5 of { happy_var_5 -> 
	case happyOut72 happy_x_6 of { happy_var_6 -> 
	( do { ma <- happy_var_5 (map addType happy_var_3)
                          ; name <- ensureUnqual happy_var_2
                          ; return $ ModuleMacro (getRange (happy_var_1, happy_var_2, ma, happy_var_6)) name ma DontOpen happy_var_6 })}}}}}
	) (\r -> happyReturn (happyIn123 r))

happyReduce_392 = happyMonadReduce 7# 114# happyReduction_392
happyReduction_392 (happy_x_7 `HappyStk`
	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) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokKeyword KwOpen happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwModule happy_var_2) -> 
	case happyOut18 happy_x_3 of { happy_var_3 -> 
	case happyOut69 happy_x_4 of { happy_var_4 -> 
	case happyOut122 happy_x_6 of { happy_var_6 -> 
	case happyOut72 happy_x_7 of { happy_var_7 -> 
	( do {ma <- happy_var_6 (map addType happy_var_4); return $ ModuleMacro (getRange (happy_var_1, happy_var_2, happy_var_3, ma, happy_var_7)) happy_var_3 ma DoOpen happy_var_7 })}}}}}}
	) (\r -> happyReturn (happyIn123 r))

happyReduce_393 = happyReduce 5# 115# happyReduction_393
happyReduction_393 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwModule happy_var_1) -> 
	case happyOut25 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokKeyword KwWhere happy_var_4) -> 
	case happyOut165 happy_x_5 of { happy_var_5 -> 
	happyIn124
		 (Module (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) happy_var_2 (map addType happy_var_3) happy_var_5
	) `HappyStk` happyRest}}}}}

happyReduce_394 = happyReduce 5# 115# happyReduction_394
happyReduction_394 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokKeyword KwModule happy_var_1) -> 
	case happyOut125 happy_x_2 of { happy_var_2 -> 
	case happyOut69 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokKeyword KwWhere happy_var_4) -> 
	case happyOut165 happy_x_5 of { happy_var_5 -> 
	happyIn124
		 (Module (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) (QName happy_var_2) (map addType happy_var_3) happy_var_5
	) `HappyStk` happyRest}}}}}

happyReduce_395 = happySpecReduce_1  116# happyReduction_395
happyReduction_395 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymUnderscore happy_var_1) -> 
	happyIn125
		 (noName (getRange happy_var_1)
	)}

happyReduce_396 = happySpecReduce_1  117# happyReduction_396
happyReduction_396 happy_x_1
	 =  case happyOut167 happy_x_1 of { happy_var_1 -> 
	happyIn126
		 (figureOutTopLevelModule happy_var_1
	)}

happyReduce_397 = happySpecReduce_1  118# happyReduction_397
happyReduction_397 happy_x_1
	 =  case happyOut128 happy_x_1 of { happy_var_1 -> 
	happyIn127
		 (Pragma happy_var_1
	)}

happyReduce_398 = happySpecReduce_1  119# happyReduction_398
happyReduction_398 happy_x_1
	 =  case happyOut130 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_399 = happySpecReduce_1  119# happyReduction_399
happyReduction_399 happy_x_1
	 =  case happyOut131 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_400 = happySpecReduce_1  119# happyReduction_400
happyReduction_400 happy_x_1
	 =  case happyOut132 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_401 = happySpecReduce_1  119# happyReduction_401
happyReduction_401 happy_x_1
	 =  case happyOut133 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_402 = happySpecReduce_1  119# happyReduction_402
happyReduction_402 happy_x_1
	 =  case happyOut136 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_403 = happySpecReduce_1  119# happyReduction_403
happyReduction_403 happy_x_1
	 =  case happyOut134 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_404 = happySpecReduce_1  119# happyReduction_404
happyReduction_404 happy_x_1
	 =  case happyOut135 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_405 = happySpecReduce_1  119# happyReduction_405
happyReduction_405 happy_x_1
	 =  case happyOut137 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_406 = happySpecReduce_1  119# happyReduction_406
happyReduction_406 happy_x_1
	 =  case happyOut138 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_407 = happySpecReduce_1  119# happyReduction_407
happyReduction_407 happy_x_1
	 =  case happyOut139 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_408 = happySpecReduce_1  119# happyReduction_408
happyReduction_408 happy_x_1
	 =  case happyOut140 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_409 = happySpecReduce_1  119# happyReduction_409
happyReduction_409 happy_x_1
	 =  case happyOut141 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_410 = happySpecReduce_1  119# happyReduction_410
happyReduction_410 happy_x_1
	 =  case happyOut142 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_411 = happySpecReduce_1  119# happyReduction_411
happyReduction_411 happy_x_1
	 =  case happyOut143 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_412 = happySpecReduce_1  119# happyReduction_412
happyReduction_412 happy_x_1
	 =  case happyOut144 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_413 = happySpecReduce_1  119# happyReduction_413
happyReduction_413 happy_x_1
	 =  case happyOut151 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_414 = happySpecReduce_1  119# happyReduction_414
happyReduction_414 happy_x_1
	 =  case happyOut152 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_415 = happySpecReduce_1  119# happyReduction_415
happyReduction_415 happy_x_1
	 =  case happyOut153 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_416 = happySpecReduce_1  119# happyReduction_416
happyReduction_416 happy_x_1
	 =  case happyOut148 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_417 = happySpecReduce_1  119# happyReduction_417
happyReduction_417 happy_x_1
	 =  case happyOut147 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_418 = happySpecReduce_1  119# happyReduction_418
happyReduction_418 happy_x_1
	 =  case happyOut146 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_419 = happySpecReduce_1  119# happyReduction_419
happyReduction_419 happy_x_1
	 =  case happyOut149 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_420 = happySpecReduce_1  119# happyReduction_420
happyReduction_420 happy_x_1
	 =  case happyOut150 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_421 = happySpecReduce_1  119# happyReduction_421
happyReduction_421 happy_x_1
	 =  case happyOut145 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_422 = happySpecReduce_1  119# happyReduction_422
happyReduction_422 happy_x_1
	 =  case happyOut154 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_423 = happySpecReduce_1  119# happyReduction_423
happyReduction_423 happy_x_1
	 =  case happyOut129 happy_x_1 of { happy_var_1 -> 
	happyIn128
		 (happy_var_1
	)}

happyReduce_424 = happyReduce 4# 120# happyReduction_424
happyReduction_424 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwOPTIONS happy_var_2) -> 
	case happyOut31 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn129
		 (OptionsPragma (getRange (happy_var_1,happy_var_2,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}}

happyReduce_425 = happyReduce 5# 121# happyReduction_425
happyReduction_425 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwBUILTIN happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokString happy_var_3) -> 
	case happyOut35 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn130
		 (BuiltinPragma (getRange (happy_var_1,happy_var_2,fst happy_var_3,happy_var_4,happy_var_5)) (snd happy_var_3) (Ident happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_426 = happyReduce 5# 121# happyReduction_426
happyReduction_426 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwBUILTIN happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokKeyword KwREWRITE happy_var_3) -> 
	case happyOut35 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn130
		 (BuiltinPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4,happy_var_5)) "REWRITE" (Ident happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_427 = happyReduce 4# 122# happyReduction_427
happyReduction_427 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwREWRITE happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn131
		 (RewritePragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}}

happyReduce_428 = happyReduce 5# 123# happyReduction_428
happyReduction_428 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn132
		 (CompiledPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 (unwords happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_429 = happyReduce 5# 124# happyReduction_429
happyReduction_429 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_EXPORT happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut32 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn133
		 (CompiledExportPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 happy_var_4
	) `HappyStk` happyRest}}}}}

happyReduce_430 = happyReduce 5# 125# happyReduction_430
happyReduction_430 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_DECLARE_DATA happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn134
		 (CompiledDeclareDataPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 (unwords happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_431 = happyReduce 5# 126# happyReduction_431
happyReduction_431 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_TYPE happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn135
		 (CompiledTypePragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 (unwords happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_432 = happyReduce 6# 127# happyReduction_432
happyReduction_432 (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 happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_DATA happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokString happy_var_4) -> 
	case happyOut31 happy_x_5 of { happy_var_5 -> 
	case happyOutTok happy_x_6 of { (TokSymbol SymClosePragma happy_var_6) -> 
	happyIn136
		 (CompiledDataPragma (getRange (happy_var_1,happy_var_2,happy_var_3,fst happy_var_4,happy_var_6)) happy_var_3 (snd happy_var_4) happy_var_5
	) `HappyStk` happyRest}}}}}}

happyReduce_433 = happyReduce 5# 128# happyReduction_433
happyReduction_433 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_EPIC happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn137
		 (CompiledEpicPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 (unwords happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_434 = happyReduce 5# 129# happyReduction_434
happyReduction_434 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_JS happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn138
		 (CompiledJSPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 (unwords happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_435 = happyReduce 5# 130# happyReduction_435
happyReduction_435 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_UHC happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	happyIn139
		 (CompiledUHCPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_5)) happy_var_3 (unwords happy_var_4)
	) `HappyStk` happyRest}}}}}

happyReduce_436 = happyReduce 6# 131# happyReduction_436
happyReduction_436 (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 happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCOMPILED_DATA_UHC happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokString happy_var_4) -> 
	case happyOut31 happy_x_5 of { happy_var_5 -> 
	case happyOutTok happy_x_6 of { (TokSymbol SymClosePragma happy_var_6) -> 
	happyIn140
		 (CompiledDataUHCPragma (getRange (happy_var_1,happy_var_2,happy_var_3,fst happy_var_4,happy_var_6)) happy_var_3 (snd happy_var_4) happy_var_5
	) `HappyStk` happyRest}}}}}}

happyReduce_437 = happyReduce 4# 132# happyReduction_437
happyReduction_437 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwHASKELL happy_var_2) -> 
	case happyOut33 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn141
		 (HaskellCodePragma (getRange (happy_var_1, happy_var_2, happy_var_4)) (recoverLayout happy_var_3)
	) `HappyStk` happyRest}}}}

happyReduce_438 = happyReduce 4# 133# happyReduction_438
happyReduction_438 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwNO_SMASHING happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn142
		 (NoSmashingPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}}

happyReduce_439 = happyReduce 4# 134# happyReduction_439
happyReduction_439 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwSTATIC happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn143
		 (StaticPragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}}

happyReduce_440 = happyReduce 4# 135# happyReduction_440
happyReduction_440 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwINLINE happy_var_2) -> 
	case happyOut35 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn144
		 (InlinePragma (getRange (happy_var_1,happy_var_2,happy_var_3,happy_var_4)) happy_var_3
	) `HappyStk` happyRest}}}}

happyReduce_441 = happyMonadReduce 5# 136# happyReduction_441
happyReduction_441 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_3 of { (TokString happy_var_3) -> 
	case happyOut31 happy_x_4 of { happy_var_4 -> 
	case happyOutTok happy_x_5 of { (TokSymbol SymClosePragma happy_var_5) -> 
	(
      let (r, s) = happy_var_3 in
      parseDisplayPragma (fuseRange happy_var_1 happy_var_5) (iStart r) (unwords (s : happy_var_4)))}}}}
	) (\r -> happyReturn (happyIn145 r))

happyReduce_442 = happySpecReduce_3  137# happyReduction_442
happyReduction_442 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwNO_TERMINATION_CHECK happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymClosePragma happy_var_3) -> 
	happyIn146
		 (TerminationCheckPragma (getRange (happy_var_1,happy_var_2,happy_var_3)) NoTerminationCheck
	)}}}

happyReduce_443 = happySpecReduce_3  138# happyReduction_443
happyReduction_443 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwNON_TERMINATING happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymClosePragma happy_var_3) -> 
	happyIn147
		 (TerminationCheckPragma (getRange (happy_var_1,happy_var_2,happy_var_3)) NonTerminating
	)}}}

happyReduce_444 = happySpecReduce_3  139# happyReduction_444
happyReduction_444 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwTERMINATING happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymClosePragma happy_var_3) -> 
	happyIn148
		 (TerminationCheckPragma (getRange (happy_var_1,happy_var_2,happy_var_3)) Terminating
	)}}}

happyReduce_445 = happyReduce 4# 140# happyReduction_445
happyReduction_445 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwMEASURE happy_var_2) -> 
	case happyOut34 happy_x_3 of { happy_var_3 -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	happyIn149
		 (let r = getRange (happy_var_1, happy_var_2, happy_var_3, happy_var_4) in
      TerminationCheckPragma r (TerminationMeasure r happy_var_3)
	) `HappyStk` happyRest}}}}

happyReduce_446 = happySpecReduce_3  141# happyReduction_446
happyReduction_446 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwCATCHALL happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymClosePragma happy_var_3) -> 
	happyIn150
		 (CatchallPragma (getRange (happy_var_1,happy_var_2,happy_var_3))
	)}}}

happyReduce_447 = happyMonadReduce 4# 142# happyReduction_447
happyReduction_447 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwIMPORT happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokString happy_var_3) -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	( let s = snd happy_var_3 in
       if validHaskellModuleName s
       then return $ ImportPragma (getRange (happy_var_1,happy_var_2,fst happy_var_3,happy_var_4)) s
       else parseError $ "Malformed module name: " ++ s ++ ".")}}}}
	) (\r -> happyReturn (happyIn151 r))

happyReduce_448 = happyMonadReduce 4# 143# happyReduction_448
happyReduction_448 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwIMPORT_UHC happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokString happy_var_3) -> 
	case happyOutTok happy_x_4 of { (TokSymbol SymClosePragma happy_var_4) -> 
	( let s = snd happy_var_3 in
       if validHaskellModuleName s
       then return $ ImportUHCPragma (getRange (happy_var_1,happy_var_2,fst happy_var_3,happy_var_4)) s
       else parseError $ "Malformed module name: " ++ s ++ ".")}}}}
	) (\r -> happyReturn (happyIn152 r))

happyReduce_449 = happySpecReduce_3  144# happyReduction_449
happyReduction_449 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwIMPOSSIBLE happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymClosePragma happy_var_3) -> 
	happyIn153
		 (ImpossiblePragma (getRange (happy_var_1,happy_var_2,happy_var_3))
	)}}}

happyReduce_450 = happySpecReduce_3  145# happyReduction_450
happyReduction_450 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokSymbol SymOpenPragma happy_var_1) -> 
	case happyOutTok happy_x_2 of { (TokKeyword KwNO_POSITIVITY_CHECK happy_var_2) -> 
	case happyOutTok happy_x_3 of { (TokSymbol SymClosePragma happy_var_3) -> 
	happyIn154
		 (NoPositivityCheckPragma (getRange (happy_var_1,happy_var_2,happy_var_3))
	)}}}

happyReduce_451 = happySpecReduce_3  146# happyReduction_451
happyReduction_451 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut156 happy_x_2 of { happy_var_2 -> 
	happyIn155
		 (reverse happy_var_2
	)}

happyReduce_452 = happySpecReduce_3  147# happyReduction_452
happyReduction_452 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut156 happy_x_1 of { happy_var_1 -> 
	case happyOut91 happy_x_3 of { happy_var_3 -> 
	happyIn156
		 (reverse happy_var_3 ++ happy_var_1
	)}}

happyReduce_453 = happySpecReduce_1  147# happyReduction_453
happyReduction_453 happy_x_1
	 =  case happyOut91 happy_x_1 of { happy_var_1 -> 
	happyIn156
		 (reverse happy_var_1
	)}

happyReduce_454 = happySpecReduce_3  148# happyReduction_454
happyReduction_454 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut158 happy_x_2 of { happy_var_2 -> 
	happyIn157
		 (reverse happy_var_2
	)}

happyReduce_455 = happySpecReduce_3  149# happyReduction_455
happyReduction_455 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut158 happy_x_1 of { happy_var_1 -> 
	case happyOut92 happy_x_3 of { happy_var_3 -> 
	happyIn158
		 (reverse happy_var_3 ++ happy_var_1
	)}}

happyReduce_456 = happySpecReduce_1  149# happyReduction_456
happyReduction_456 happy_x_1
	 =  case happyOut92 happy_x_1 of { happy_var_1 -> 
	happyIn158
		 (reverse happy_var_1
	)}

happyReduce_457 = happyMonadReduce 3# 150# happyReduction_457
happyReduction_457 (happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut160 happy_x_2 of { happy_var_2 -> 
	( ((,) `fmap` verifyRecordDirectives happy_var_2 <*> pure []))}
	) (\r -> happyReturn (happyIn159 r))

happyReduce_458 = happyMonadReduce 5# 150# happyReduction_458
happyReduction_458 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut160 happy_x_2 of { happy_var_2 -> 
	case happyOut166 happy_x_4 of { happy_var_4 -> 
	( ((,) `fmap` verifyRecordDirectives happy_var_2 <*> pure happy_var_4))}}
	) (\r -> happyReturn (happyIn159 r))

happyReduce_459 = happyMonadReduce 3# 150# happyReduction_459
happyReduction_459 (happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest) tk
	 = happyThen (case happyOut166 happy_x_2 of { happy_var_2 -> 
	( ((,) `fmap` verifyRecordDirectives [] <*> pure happy_var_2))}
	) (\r -> happyReturn (happyIn159 r))

happyReduce_460 = happySpecReduce_0  151# happyReduction_460
happyReduction_460  =  happyIn160
		 ([]
	)

happyReduce_461 = happySpecReduce_3  151# happyReduction_461
happyReduction_461 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut160 happy_x_1 of { happy_var_1 -> 
	case happyOut161 happy_x_3 of { happy_var_3 -> 
	happyIn160
		 (happy_var_3 : happy_var_1
	)}}

happyReduce_462 = happySpecReduce_1  151# happyReduction_462
happyReduction_462 happy_x_1
	 =  case happyOut161 happy_x_1 of { happy_var_1 -> 
	happyIn160
		 ([happy_var_1]
	)}

happyReduce_463 = happySpecReduce_1  152# happyReduction_463
happyReduction_463 happy_x_1
	 =  case happyOut99 happy_x_1 of { happy_var_1 -> 
	happyIn161
		 (Constructor happy_var_1
	)}

happyReduce_464 = happySpecReduce_1  152# happyReduction_464
happyReduction_464 happy_x_1
	 =  case happyOut163 happy_x_1 of { happy_var_1 -> 
	happyIn161
		 (Induction happy_var_1
	)}

happyReduce_465 = happySpecReduce_1  152# happyReduction_465
happyReduction_465 happy_x_1
	 =  case happyOut162 happy_x_1 of { happy_var_1 -> 
	happyIn161
		 (Eta happy_var_1
	)}

happyReduce_466 = happySpecReduce_1  153# happyReduction_466
happyReduction_466 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwEta happy_var_1) -> 
	happyIn162
		 (Ranged (getRange happy_var_1) True
	)}

happyReduce_467 = happySpecReduce_1  153# happyReduction_467
happyReduction_467 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwNoEta happy_var_1) -> 
	happyIn162
		 (Ranged (getRange happy_var_1) False
	)}

happyReduce_468 = happySpecReduce_1  154# happyReduction_468
happyReduction_468 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwInductive happy_var_1) -> 
	happyIn163
		 (Ranged (getRange happy_var_1) Inductive
	)}

happyReduce_469 = happySpecReduce_1  154# happyReduction_469
happyReduction_469 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TokKeyword KwCoInductive happy_var_1) -> 
	happyIn163
		 (Ranged (getRange happy_var_1) CoInductive
	)}

happyReduce_470 = happySpecReduce_3  155# happyReduction_470
happyReduction_470 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut166 happy_x_2 of { happy_var_2 -> 
	happyIn164
		 (happy_var_2
	)}

happyReduce_471 = happySpecReduce_2  156# happyReduction_471
happyReduction_471 happy_x_2
	happy_x_1
	 =  happyIn165
		 ([]
	)

happyReduce_472 = happySpecReduce_1  156# happyReduction_472
happyReduction_472 happy_x_1
	 =  case happyOut164 happy_x_1 of { happy_var_1 -> 
	happyIn165
		 (happy_var_1
	)}

happyReduce_473 = happySpecReduce_3  157# happyReduction_473
happyReduction_473 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut90 happy_x_1 of { happy_var_1 -> 
	case happyOut166 happy_x_3 of { happy_var_3 -> 
	happyIn166
		 (happy_var_1 ++ happy_var_3
	)}}

happyReduce_474 = happySpecReduce_1  157# happyReduction_474
happyReduction_474 happy_x_1
	 =  case happyOut90 happy_x_1 of { happy_var_1 -> 
	happyIn166
		 (happy_var_1
	)}

happyReduce_475 = happySpecReduce_0  158# happyReduction_475
happyReduction_475  =  happyIn167
		 ([]
	)

happyReduce_476 = happySpecReduce_1  158# happyReduction_476
happyReduction_476 happy_x_1
	 =  case happyOut166 happy_x_1 of { happy_var_1 -> 
	happyIn167
		 (happy_var_1
	)}

happyNewToken action sts stk
	= lexer(\tk -> 
	let cont i = happyDoAction i tk action sts stk in
	case tk of {
	TokEOF -> happyDoAction 102# tk action sts stk;
	TokKeyword KwAbstract happy_dollar_dollar -> cont 1#;
	TokKeyword KwCoData happy_dollar_dollar -> cont 2#;
	TokKeyword KwCoInductive happy_dollar_dollar -> cont 3#;
	TokKeyword KwConstructor happy_dollar_dollar -> cont 4#;
	TokKeyword KwData happy_dollar_dollar -> cont 5#;
	TokKeyword KwEta happy_dollar_dollar -> cont 6#;
	TokKeyword KwField happy_dollar_dollar -> cont 7#;
	TokKeyword KwForall happy_dollar_dollar -> cont 8#;
	TokKeyword KwHiding happy_dollar_dollar -> cont 9#;
	TokKeyword KwImport happy_dollar_dollar -> cont 10#;
	TokKeyword KwIn happy_dollar_dollar -> cont 11#;
	TokKeyword KwInductive happy_dollar_dollar -> cont 12#;
	TokKeyword KwInfix happy_dollar_dollar -> cont 13#;
	TokKeyword KwInfixL happy_dollar_dollar -> cont 14#;
	TokKeyword KwInfixR happy_dollar_dollar -> cont 15#;
	TokKeyword KwInstance happy_dollar_dollar -> cont 16#;
	TokKeyword KwLet happy_dollar_dollar -> cont 17#;
	TokKeyword KwMacro happy_dollar_dollar -> cont 18#;
	TokKeyword KwModule happy_dollar_dollar -> cont 19#;
	TokKeyword KwMutual happy_dollar_dollar -> cont 20#;
	TokKeyword KwNoEta happy_dollar_dollar -> cont 21#;
	TokKeyword KwOpen happy_dollar_dollar -> cont 22#;
	TokKeyword KwPatternSyn happy_dollar_dollar -> cont 23#;
	TokKeyword KwPostulate happy_dollar_dollar -> cont 24#;
	TokKeyword KwPrimitive happy_dollar_dollar -> cont 25#;
	TokKeyword KwPrivate happy_dollar_dollar -> cont 26#;
	TokKeyword KwProp happy_dollar_dollar -> cont 27#;
	TokKeyword KwPublic happy_dollar_dollar -> cont 28#;
	TokKeyword KwQuote happy_dollar_dollar -> cont 29#;
	TokKeyword KwQuoteContext happy_dollar_dollar -> cont 30#;
	TokKeyword KwQuoteGoal happy_dollar_dollar -> cont 31#;
	TokKeyword KwQuoteTerm happy_dollar_dollar -> cont 32#;
	TokKeyword KwRecord happy_dollar_dollar -> cont 33#;
	TokKeyword KwRenaming happy_dollar_dollar -> cont 34#;
	TokKeyword KwRewrite happy_dollar_dollar -> cont 35#;
	TokKeyword KwSet happy_dollar_dollar -> cont 36#;
	TokKeyword KwSyntax happy_dollar_dollar -> cont 37#;
	TokKeyword KwTactic happy_dollar_dollar -> cont 38#;
	TokKeyword KwTo happy_dollar_dollar -> cont 39#;
	TokKeyword KwUnquote happy_dollar_dollar -> cont 40#;
	TokKeyword KwUnquoteDecl happy_dollar_dollar -> cont 41#;
	TokKeyword KwUnquoteDef happy_dollar_dollar -> cont 42#;
	TokKeyword KwUsing happy_dollar_dollar -> cont 43#;
	TokKeyword KwWhere happy_dollar_dollar -> cont 44#;
	TokKeyword KwWith happy_dollar_dollar -> cont 45#;
	TokKeyword KwBUILTIN happy_dollar_dollar -> cont 46#;
	TokKeyword KwCATCHALL happy_dollar_dollar -> cont 47#;
	TokKeyword KwCOMPILED happy_dollar_dollar -> cont 48#;
	TokKeyword KwCOMPILED_DATA happy_dollar_dollar -> cont 49#;
	TokKeyword KwCOMPILED_DATA_UHC happy_dollar_dollar -> cont 50#;
	TokKeyword KwCOMPILED_DECLARE_DATA happy_dollar_dollar -> cont 51#;
	TokKeyword KwCOMPILED_EPIC happy_dollar_dollar -> cont 52#;
	TokKeyword KwCOMPILED_EXPORT happy_dollar_dollar -> cont 53#;
	TokKeyword KwCOMPILED_JS happy_dollar_dollar -> cont 54#;
	TokKeyword KwCOMPILED_TYPE happy_dollar_dollar -> cont 55#;
	TokKeyword KwCOMPILED_UHC happy_dollar_dollar -> cont 56#;
	TokKeyword KwHASKELL happy_dollar_dollar -> cont 57#;
	TokKeyword KwDISPLAY happy_dollar_dollar -> cont 58#;
	TokKeyword KwIMPORT happy_dollar_dollar -> cont 59#;
	TokKeyword KwIMPORT_UHC happy_dollar_dollar -> cont 60#;
	TokKeyword KwIMPOSSIBLE happy_dollar_dollar -> cont 61#;
	TokKeyword KwINLINE happy_dollar_dollar -> cont 62#;
	TokKeyword KwMEASURE happy_dollar_dollar -> cont 63#;
	TokKeyword KwNO_SMASHING happy_dollar_dollar -> cont 64#;
	TokKeyword KwNO_TERMINATION_CHECK happy_dollar_dollar -> cont 65#;
	TokKeyword KwNO_POSITIVITY_CHECK happy_dollar_dollar -> cont 66#;
	TokKeyword KwNON_TERMINATING happy_dollar_dollar -> cont 67#;
	TokKeyword KwOPTIONS happy_dollar_dollar -> cont 68#;
	TokKeyword KwREWRITE happy_dollar_dollar -> cont 69#;
	TokKeyword KwSTATIC happy_dollar_dollar -> cont 70#;
	TokKeyword KwTERMINATING happy_dollar_dollar -> cont 71#;
	TokSetN happy_dollar_dollar -> cont 72#;
	TokTeX happy_dollar_dollar -> cont 73#;
	TokComment happy_dollar_dollar -> cont 74#;
	TokSymbol SymEllipsis happy_dollar_dollar -> cont 75#;
	TokSymbol SymDotDot happy_dollar_dollar -> cont 76#;
	TokSymbol SymDot happy_dollar_dollar -> cont 77#;
	TokSymbol SymSemi happy_dollar_dollar -> cont 78#;
	TokSymbol SymColon happy_dollar_dollar -> cont 79#;
	TokSymbol SymEqual happy_dollar_dollar -> cont 80#;
	TokSymbol SymUnderscore happy_dollar_dollar -> cont 81#;
	TokSymbol SymQuestionMark happy_dollar_dollar -> cont 82#;
	TokSymbol SymArrow happy_dollar_dollar -> cont 83#;
	TokSymbol SymLambda happy_dollar_dollar -> cont 84#;
	TokSymbol SymAs happy_dollar_dollar -> cont 85#;
	TokSymbol SymBar happy_dollar_dollar -> cont 86#;
	TokSymbol SymOpenParen happy_dollar_dollar -> cont 87#;
	TokSymbol SymCloseParen happy_dollar_dollar -> cont 88#;
	TokSymbol SymDoubleOpenBrace happy_dollar_dollar -> cont 89#;
	TokSymbol SymDoubleCloseBrace happy_dollar_dollar -> cont 90#;
	TokSymbol SymOpenBrace happy_dollar_dollar -> cont 91#;
	TokSymbol SymCloseBrace happy_dollar_dollar -> cont 92#;
	TokSymbol SymOpenVirtualBrace happy_dollar_dollar -> cont 93#;
	TokSymbol SymCloseVirtualBrace happy_dollar_dollar -> cont 94#;
	TokSymbol SymVirtualSemi happy_dollar_dollar -> cont 95#;
	TokSymbol SymOpenPragma happy_dollar_dollar -> cont 96#;
	TokSymbol SymClosePragma happy_dollar_dollar -> cont 97#;
	TokId happy_dollar_dollar -> cont 98#;
	TokQId happy_dollar_dollar -> cont 99#;
	TokString happy_dollar_dollar -> cont 100#;
	TokLiteral happy_dollar_dollar -> cont 101#;
	_ -> happyError' tk
	})

happyError_ 102# tk = happyError' tk
happyError_ _ tk = happyError' tk

happyThen :: () => Parser a -> (a -> Parser b) -> Parser b
happyThen = (>>=)
happyReturn :: () => a -> Parser a
happyReturn = (return)
happyThen1 = happyThen
happyReturn1 :: () => a -> Parser a
happyReturn1 = happyReturn
happyError' :: () => (Token) -> Parser a
happyError' tk = (\token -> happyError) tk

tokensParser = happySomeParser where
  happySomeParser = happyThen (happyParse 0#) (\x -> happyReturn (happyOut9 x))

exprParser = happySomeParser where
  happySomeParser = happyThen (happyParse 1#) (\x -> happyReturn (happyOut36 x))

exprWhereParser = happySomeParser where
  happySomeParser = happyThen (happyParse 2#) (\x -> happyReturn (happyOut89 x))

moduleParser = happySomeParser where
  happySomeParser = happyThen (happyParse 3#) (\x -> happyReturn (happyOut12 x))

moduleNameParser = happySomeParser where
  happySomeParser = happyThen (happyParse 4#) (\x -> happyReturn (happyOut25 x))

funclauseParser = happySomeParser where
  happySomeParser = happyThen (happyParse 5#) (\x -> happyReturn (happyOut93 x))

happySeq = happyDontSeq


{--------------------------------------------------------------------------
    Parsers
 --------------------------------------------------------------------------}

-- | Parse the token stream. Used by the TeX compiler.
tokensParser :: Parser [Token]

-- | Parse an expression. Could be used in interactions.
exprParser :: Parser Expr

-- | Parse an expression followed by a where clause. Could be used in interactions.
exprWhereParser :: Parser ExprWhere

-- | Parse a module.
moduleParser :: Parser Module


{--------------------------------------------------------------------------
    Happy stuff
 --------------------------------------------------------------------------}

-- | Required by Happy.
happyError :: Parser a
happyError = parseError "Parse error"


{--------------------------------------------------------------------------
    Utility functions
 --------------------------------------------------------------------------}

-- | Grab leading OPTIONS pragmas.
takeOptionsPragmas :: [Declaration] -> ([Pragma], [Declaration])
takeOptionsPragmas = spanJust $ \ d -> case d of
  Pragma p@OptionsPragma{} -> Just p
  _                        -> Nothing

-- | Insert a top-level module if there is none.
--   Also fix-up for the case the declarations in the top-level module
--   are not indented (this is allowed as a special case).
figureOutTopLevelModule :: [Declaration] -> [Declaration]
figureOutTopLevelModule ds =
  case spanAllowedBeforeModule ds of
    -- Andreas 2016-02-01, issue #1388.
    -- We need to distinguish two additional cases.
    -- Case 1: Regular file layout: imports followed by one module. Nothing to do.
    (ds0, [ Module{} ]) -> ds
    -- Case 2: The declarations in the module are not indented.
    -- This is allowed for the top level module, and thus rectified here.
    (ds0, Module r m tel [] : ds2) -> ds0 ++ [Module r m tel ds2]
    -- Case 3: There is a module with indented declarations,
    -- followed by non-indented declarations.  This should be a
    -- parse error and be reported later (see @toAbstract TopLevel{}@),
    -- thus, we do not do anything here.
    (ds0, Module r m tel ds1 : ds2) -> ds  -- Gives parse error in scope checker.
    -- OLD code causing issue 1388:
    -- (ds0, Module r m tel ds1 : ds2) -> ds0 ++ [Module r m tel $ ds1 ++ ds2]
    -- Case 4: a top-level module declaration is missing.
    (ds0, ds1)                      -> ds0 ++ [Module (getRange ds1) (QName noName_) [] ds1]

-- | Create a name from a string.

mkName :: (Interval, String) -> Parser Name
mkName (i, s) = do
    let xs = C.stringNameParts s
    mapM_ isValidId xs
    unless (alternating xs) $ fail $ "a name cannot contain two consecutive underscores"
    return $ Name (getRange i) xs
    where
        isValidId Hole   = return ()
        isValidId (Id y) = do
          let x = rawNameToString y
          case parse defaultParseFlags [0] (lexer return) x of
            ParseOk _ (TokId _) -> return ()
            _                   -> fail $ "in the name " ++ s ++ ", the part " ++ x ++ " is not valid"

        -- we know that there are no two Ids in a row
        alternating (Hole : Hole : _) = False
        alternating (_ : xs)          = alternating xs
        alternating []                = True

-- | Create a qualified name from a list of strings
mkQName :: [(Interval, String)] -> Parser QName
mkQName ss = do
    xs <- mapM mkName ss
    return $ foldr Qual (QName $ last xs) (init xs)

recoverLayout :: [(Interval, String)] -> String
recoverLayout [] = ""
recoverLayout xs@((i, _) : _) = go (iStart i) xs
  where
    c0 = posCol (iStart i)

    go cur [] = ""
    go cur ((i, s) : xs) = padding cur (iStart i) ++ s ++ go (iEnd i) xs

    padding Pn{ posLine = l1, posCol = c1 } Pn{ posLine = l2, posCol = c2 }
      | l1 < l2  = genericReplicate (l2 - l1) '\n' ++ genericReplicate (max 0 (c2 - c0)) ' '
      | l1 == l2 = genericReplicate (c2 - c1) ' '

ensureUnqual :: QName -> Parser Name
ensureUnqual (QName x) = return x
ensureUnqual q@Qual{}  = parseError' (rStart' $ getRange q) "Qualified name not allowed here"

-- | Match a particular name.
isName :: String -> (Interval, String) -> Parser ()
isName s (_,s')
    | s == s'   = return ()
    | otherwise = fail $ "expected " ++ s ++ ", found " ++ s'

-- | Build a forall pi (forall x y z -> ...)
forallPi :: [LamBinding] -> Expr -> Expr
forallPi bs e = Pi (map addType bs) e

-- | Build a telescoping let (let Ds)
tLet :: Range -> [Declaration] -> TypedBindings
tLet r = TypedBindings r . Arg defaultArgInfo . TLet r

-- | Converts lambda bindings to typed bindings.
addType :: LamBinding -> TypedBindings
addType (DomainFull b)   = b
addType (DomainFree info x) = TypedBindings r $ Arg info $ TBind r [pure x] $ Underscore r Nothing
  where r = getRange x

mergeImportDirectives :: [ImportDirective] -> Parser ImportDirective
mergeImportDirectives is = do
  i <- foldl merge (return defaultImportDir) is
  verifyImportDirective i
  where
    merge mi i2 = do
      i1 <- mi
      let err = parseError' (rStart' $ getRange i2) "Cannot mix using and hiding module directives"
      return $ ImportDirective
        { importDirRange = fuseRange i1 i2
        , using          = mappend (using i1) (using i2)
        , hiding         = hiding i1 ++ hiding i2
        , impRenaming    = impRenaming i1 ++ impRenaming i2
        , publicOpen     = publicOpen i1 || publicOpen i2 }

-- | Check that an import directive doesn't contain repeated names
verifyImportDirective :: ImportDirective -> Parser ImportDirective
verifyImportDirective i =
    case filter ((>1) . length)
         $ group
         $ sort xs
    of
        []  -> return i
        yss -> let Just pos = rStart' $ getRange $ head $ concat yss in
               parseErrorAt pos $
                "Repeated name" ++ s ++ " in import directive: " ++
                concat (intersperse ", " $ map (show . head) yss)
            where
                s = case yss of
                        [_] -> ""
                        _   -> "s"
    where
        xs = names (using i) ++ hiding i ++ map renFrom (impRenaming i)
        names (Using xs)    = xs
        names UseEverything = []

data RecordDirective
   = Induction (Ranged Induction)
   | Constructor (Name, IsInstance)
   | Eta         (Ranged Bool)
   deriving (Eq,Show)

verifyRecordDirectives :: [RecordDirective] -> Parser (Maybe (Ranged Induction), Maybe Bool, Maybe (Name, IsInstance))
verifyRecordDirectives xs | null rs = return (ltm is, ltm es, ltm cs)
                          | otherwise = let Just pos = rStart' $ (head rs) in
                                          parseErrorAt pos $ "Repeated record directives at: \n" ++ intercalate "\n" (map show rs)

 where
  ltm :: [a] -> Maybe a
  ltm [] = Nothing
  ltm (x:xs) = Just x
  errorFromList [] = []
  errorFromList [x] = []
  errorFromList xs = map getRange xs
  rs = sort (concat ([errorFromList is, errorFromList es', errorFromList cs]))
  is = [ i | Induction i <- xs ]
  es' = [ i | Eta i <- xs ]
  es = map rangedThing es'
  cs = [ i | Constructor i <- xs ]


-- | Breaks up a string into substrings. Returns every maximal
-- subsequence of zero or more characters distinct from @'.'@.
--
-- > splitOnDots ""         == [""]
-- > splitOnDots "foo.bar"  == ["foo", "bar"]
-- > splitOnDots ".foo.bar" == ["", "foo", "bar"]
-- > splitOnDots "foo.bar." == ["foo", "bar", ""]
-- > splitOnDots "foo..bar" == ["foo", "", "bar"]
splitOnDots :: String -> [String]
splitOnDots ""        = [""]
splitOnDots ('.' : s) = [] : splitOnDots s
splitOnDots (c   : s) = case splitOnDots s of
  p : ps -> (c : p) : ps

prop_splitOnDots = and
  [ splitOnDots ""         == [""]
  , splitOnDots "foo.bar"  == ["foo", "bar"]
  , splitOnDots ".foo.bar" == ["", "foo", "bar"]
  , splitOnDots "foo.bar." == ["foo", "bar", ""]
  , splitOnDots "foo..bar" == ["foo", "", "bar"]
  ]

-- | Returns 'True' iff the name is a valid Haskell (hierarchical)
-- module name.
validHaskellModuleName :: String -> Bool
validHaskellModuleName = all ok . splitOnDots
  where
  -- Checks if a dot-less module name is well-formed.
  ok :: String -> Bool
  ok []      = False
  ok (c : s) =
    isUpper c &&
    all (\c -> isLower c || c == '_' ||
               isUpper c ||
               generalCategory c == DecimalNumber ||
               c == '\'')
        s

{--------------------------------------------------------------------------
    Patterns
 --------------------------------------------------------------------------}

-- | Turn an expression into a left hand side.
exprToLHS :: Expr -> Parser ([Expr] -> [Expr] -> LHS)
exprToLHS e = case e of
  WithApp r e es -> LHS <$> exprToPattern e <*> mapM exprToPattern es
  _              -> LHS <$> exprToPattern e <*> return []

-- | Turn an expression into a pattern. Fails if the expression is not a
--   valid pattern.
exprToPattern :: Expr -> Parser Pattern
exprToPattern e = do
    let Just pos = rStart' $ getRange e
        failure = parseErrorAt pos $ "Not a valid pattern: " ++ show e
    case e of
        Ident x                 -> return $ IdentP x
        App _ e1 e2             -> AppP <$> exprToPattern e1
                                        <*> T.mapM (T.mapM exprToPattern) e2
        Paren r e               -> ParenP r
                                        <$> exprToPattern e
        Underscore r _          -> return $ WildP r
        Absurd r                -> return $ AbsurdP r
        As r x e                -> AsP r x <$> exprToPattern e
        Dot r (HiddenArg _ e)   -> return $ HiddenP r $ fmap (DotP r) e
        Dot r e                 -> return $ DotP r e
        Lit l                   -> return $ LitP l
        HiddenArg r e           -> HiddenP r <$> T.mapM exprToPattern e
        InstanceArg r e         -> InstanceP r <$> T.mapM exprToPattern e
        RawApp r es             -> RawAppP r <$> mapM exprToPattern es
        Quote r                 -> return $ QuoteP r
        Rec r es | Just fs <- mapM maybeLeft es -> do
          RecP r <$> T.mapM (T.mapM exprToPattern) fs
        _                       -> failure

opAppExprToPattern :: OpApp Expr -> Parser Pattern
opAppExprToPattern (SyntaxBindingLambda _ _ _) = parseError "Syntax binding lambda cannot appear in a pattern"
opAppExprToPattern (Ordinary e) = exprToPattern e

-- | Turn an expression into a name. Fails if the expression is not a
--   valid identifier.
exprToName :: Expr -> Parser Name
exprToName (Ident (QName x)) = return x
exprToName e =
  let Just pos = rStart' $ getRange e in
  parseErrorAt pos $ "Not a valid identifier: " ++ show e

stripSingletonRawApp :: Expr -> Expr
stripSingletonRawApp (RawApp _ [e]) = stripSingletonRawApp e
stripSingletonRawApp e = e

isEqual :: Expr -> Maybe (Expr, Expr)
isEqual e =
  case stripSingletonRawApp e of
    Equal _ a b -> Just (stripSingletonRawApp a, stripSingletonRawApp b)
    _           -> Nothing

maybeNamed :: Expr -> Named_ Expr
maybeNamed e =
  case isEqual e of
    Just (Ident (QName x), b) -> named (Ranged (getRange x) (nameToRawName x)) b
    _                         -> unnamed e

patternSynArgs :: [Either Hiding LamBinding] -> Parser [Arg Name]
patternSynArgs = mapM pSynArg
  where
    pSynArg Left{}                   = parseError "Absurd patterns are not allowed in pattern synonyms"
    pSynArg (Right DomainFull{})     = parseError "Unexpected type signature in pattern synonym argument"
    pSynArg (Right (DomainFree a x))
      | getHiding a `notElem` [Hidden, NotHidden] = parseError $ show (getHiding a) ++ " arguments not allowed to pattern synonyms"
      | getRelevance a /= Relevant                = parseError "Arguments to pattern synonyms must be relevant"
      | otherwise                                 = return $ Arg a (boundName x)

parsePanic s = parseError $ "Internal parser error: " ++ s ++ ". Please report this as a bug."

{- RHS or type signature -}

data RHSOrTypeSigs
 = JustRHS RHS
 | TypeSigsRHS Expr
 deriving Show

patternToNames :: Pattern -> Parser [(ArgInfo, Name)]
patternToNames p =
  case p of
    IdentP (QName i)         -> return [(defaultArgInfo, i)]
    WildP r                  -> return [(defaultArgInfo, C.noName r)]
    DotP _ (Ident (QName i)) -> return [(setRelevance Irrelevant defaultArgInfo, i)]
    RawAppP _ ps             -> concat <$> mapM patternToNames ps
    _                        -> parseError $
      "Illegal name in type signature: " ++ prettyShow p

funClauseOrTypeSigs :: LHS -> RHSOrTypeSigs -> WhereClause -> Parser [Declaration]
funClauseOrTypeSigs lhs mrhs wh = do
  -- traceShowM lhs
  case mrhs of
    JustRHS rhs   -> return [FunClause lhs rhs wh False]
    TypeSigsRHS e -> case wh of
      NoWhere -> case lhs of
        Ellipsis{}      -> parseError "The ellipsis ... cannot have a type signature"
        LHS _ _ _ (_:_) -> parseError "Illegal: with in type signature"
        LHS _ _ (_:_) _ -> parseError "Illegal: rewrite in type signature"
        LHS _ (_:_) _ _ -> parseError "Illegal: with patterns in type signature"
        LHS p [] [] []  -> map (\ (x, y) -> TypeSig x y e) <$> patternToNames p
      _ -> parseError "A type signature cannot have a where clause"

parseDisplayPragma :: Range -> Position -> String -> Parser Pragma
parseDisplayPragma r pos s =
  case parsePosString pos defaultParseFlags [normal] funclauseParser s of
    ParseOk s [FunClause (LHS lhs [] [] []) (RHS rhs) NoWhere ca] | null (parseInp s) ->
      return $ DisplayPragma r lhs rhs
    _ -> parseError "Invalid DISPLAY pragma. Should have form {-# DISPLAY LHS = RHS #-}."

{--------------------------------------------------------------------------
    Tests
 --------------------------------------------------------------------------}

-- | Test suite.
tests :: IO Bool
tests = runTests "Agda.Syntax.Parser.Parser"
  [ quickCheck' prop_splitOnDots
  ]
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "<command-line>" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
-- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp 

{-# LINE 13 "templates/GenericTemplate.hs" #-}





-- 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
{-# LINE 46 "templates/GenericTemplate.hs" #-}


data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList





{-# LINE 67 "templates/GenericTemplate.hs" #-}

{-# LINE 77 "templates/GenericTemplate.hs" #-}

{-# LINE 86 "templates/GenericTemplate.hs" #-}

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 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    = 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#





data HappyAddr = HappyA# Happy_GHC_Exts.Addr#




-----------------------------------------------------------------------------
-- HappyState data type (not arrays)

{-# LINE 170 "templates/GenericTemplate.hs" #-}

-----------------------------------------------------------------------------
-- 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 = 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 = 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 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_ 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  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.