{-# OPTIONS_GHC -w #-}
{-# OPTIONS -XMagicHash -XBangPatterns -XTypeSynonymInstances -XFlexibleInstances -cpp #-}
#if __GLASGOW_HASKELL__ >= 710
{-# OPTIONS_GHC -XPartialTypeSignatures #-}
#endif
{-# LANGUAGE DeriveAnyClass #-}
    {-# LANGUAGE DeriveGeneric #-}
    {-# LANGUAGE OverloadedStrings #-}
    module Kempe.Parser ( parse
                        , parseWithMax
                        , parseWithCtx
                        , parseWithInitCtx
                        , ParseError (..)
                        ) where

import Control.Composition ((.*))
import Control.DeepSeq (NFData)
import Control.Exception (Exception)
import Control.Monad.Except (ExceptT, runExceptT, throwError)
import Control.Monad.Trans.Class (lift)
import Data.Bifunctor (first)
import qualified Data.ByteString.Lazy as BSL
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T
import Data.Tuple.Extra (fst3)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Kempe.AST
import Kempe.Lexer
import qualified Kempe.Name as Name
import Kempe.Name hiding (loc)
import Prettyprinter (Pretty (pretty), (<+>))
import qualified Data.Array as Happy_Data_Array
import qualified Data.Bits as Bits
import qualified GHC.Exts as Happy_GHC_Exts
import Control.Applicative(Applicative(..))
import Control.Monad (ap)

-- parser produced by Happy Version 1.20.0

newtype HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 = HappyAbsSyn HappyAny
#if __GLASGOW_HASKELL__ >= 607
type HappyAny = Happy_GHC_Exts.Any
#else
type HappyAny = forall a . a
#endif
newtype HappyWrap4 = HappyWrap4 (Module AlexPosn AlexPosn AlexPosn)
happyIn4 :: (Module AlexPosn AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn4 :: Module AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn4 Module AlexPosn AlexPosn AlexPosn
x = HappyWrap4
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (Module AlexPosn AlexPosn AlexPosn -> HappyWrap4
HappyWrap4 Module AlexPosn AlexPosn AlexPosn
x)
{-# INLINE happyIn4 #-}
happyOut4 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap4
happyOut4 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap4
happyOut4 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap4
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut4 #-}
newtype HappyWrap5 = HappyWrap5 (Declarations AlexPosn AlexPosn AlexPosn)
happyIn5 :: (Declarations AlexPosn AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn5 :: Declarations AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn5 Declarations AlexPosn AlexPosn AlexPosn
x = HappyWrap5
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (Declarations AlexPosn AlexPosn AlexPosn -> HappyWrap5
HappyWrap5 Declarations AlexPosn AlexPosn AlexPosn
x)
{-# INLINE happyIn5 #-}
happyOut5 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap5
happyOut5 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap5
happyOut5 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap5
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut5 #-}
newtype HappyWrap6 = HappyWrap6 (BSL.ByteString)
happyIn6 :: (BSL.ByteString) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn6 :: ByteString
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn6 ByteString
x = HappyWrap6
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (ByteString -> HappyWrap6
HappyWrap6 ByteString
x)
{-# INLINE happyIn6 #-}
happyOut6 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap6
happyOut6 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap6
happyOut6 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap6
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut6 #-}
newtype HappyWrap7 = HappyWrap7 (ABI)
happyIn7 :: (ABI) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn7 :: ABI -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn7 ABI
x = HappyWrap7
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (ABI -> HappyWrap7
HappyWrap7 ABI
x)
{-# INLINE happyIn7 #-}
happyOut7 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap7
happyOut7 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap7
happyOut7 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap7
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut7 #-}
newtype HappyWrap8 = HappyWrap8 (KempeDecl AlexPosn AlexPosn AlexPosn)
happyIn8 :: (KempeDecl AlexPosn AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn8 :: KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn8 KempeDecl AlexPosn AlexPosn AlexPosn
x = HappyWrap8
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (KempeDecl AlexPosn AlexPosn AlexPosn -> HappyWrap8
HappyWrap8 KempeDecl AlexPosn AlexPosn AlexPosn
x)
{-# INLINE happyIn8 #-}
happyOut8 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap8
happyOut8 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap8
happyOut8 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap8
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut8 #-}
newtype HappyWrap9 = HappyWrap9 (KempeDecl AlexPosn AlexPosn AlexPosn)
happyIn9 :: (KempeDecl AlexPosn AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn9 :: KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn9 KempeDecl AlexPosn AlexPosn AlexPosn
x = HappyWrap9
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (KempeDecl AlexPosn AlexPosn AlexPosn -> HappyWrap9
HappyWrap9 KempeDecl AlexPosn AlexPosn AlexPosn
x)
{-# INLINE happyIn9 #-}
happyOut9 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap9
happyOut9 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap9
happyOut9 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap9
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut9 #-}
newtype HappyWrap10 = HappyWrap10 (KempeTy AlexPosn)
happyIn10 :: (KempeTy AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn10 :: KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10 KempeTy AlexPosn
x = HappyWrap10
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (KempeTy AlexPosn -> HappyWrap10
HappyWrap10 KempeTy AlexPosn
x)
{-# INLINE happyIn10 #-}
happyOut10 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap10
happyOut10 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
happyOut10 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut10 #-}
newtype HappyWrap11 = HappyWrap11 (KempeDecl AlexPosn AlexPosn AlexPosn)
happyIn11 :: (KempeDecl AlexPosn AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn11 :: KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn11 KempeDecl AlexPosn AlexPosn AlexPosn
x = HappyWrap11
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (KempeDecl AlexPosn AlexPosn AlexPosn -> HappyWrap11
HappyWrap11 KempeDecl AlexPosn AlexPosn AlexPosn
x)
{-# INLINE happyIn11 #-}
happyOut11 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap11
happyOut11 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap11
happyOut11 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap11
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut11 #-}
newtype HappyWrap12 = HappyWrap12 ((AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn]))
happyIn12 :: ((AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn12 :: (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn12 (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
x = HappyWrap12
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# ((AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
-> HappyWrap12
HappyWrap12 (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
x)
{-# INLINE happyIn12 #-}
happyOut12 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap12
happyOut12 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap12
happyOut12 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap12
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut12 #-}
newtype HappyWrap13 = HappyWrap13 ([Atom AlexPosn AlexPosn])
happyIn13 :: ([Atom AlexPosn AlexPosn]) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn13 :: [Atom AlexPosn AlexPosn]
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn13 [Atom AlexPosn AlexPosn]
x = HappyWrap13
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# ([Atom AlexPosn AlexPosn] -> HappyWrap13
HappyWrap13 [Atom AlexPosn AlexPosn]
x)
{-# INLINE happyIn13 #-}
happyOut13 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap13
happyOut13 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap13
happyOut13 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap13
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut13 #-}
newtype HappyWrap14 = HappyWrap14 (Atom AlexPosn AlexPosn)
happyIn14 :: (Atom AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn14 :: Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14 Atom AlexPosn AlexPosn
x = HappyWrap14
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (Atom AlexPosn AlexPosn -> HappyWrap14
HappyWrap14 Atom AlexPosn AlexPosn
x)
{-# INLINE happyIn14 #-}
happyOut14 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap14
happyOut14 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap14
happyOut14 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap14
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut14 #-}
newtype HappyWrap15 = HappyWrap15 ((Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
happyIn15 :: ((Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn15 :: (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn15 (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
x = HappyWrap15
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# ((Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> HappyWrap15
HappyWrap15 (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
x)
{-# INLINE happyIn15 #-}
happyOut15 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap15
happyOut15 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap15
happyOut15 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap15
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut15 #-}
newtype HappyWrap16 = HappyWrap16 (Pattern AlexPosn AlexPosn)
happyIn16 :: (Pattern AlexPosn AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn16 :: Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn16 Pattern AlexPosn AlexPosn
x = HappyWrap16
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# (Pattern AlexPosn AlexPosn -> HappyWrap16
HappyWrap16 Pattern AlexPosn AlexPosn
x)
{-# INLINE happyIn16 #-}
happyOut16 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap16
happyOut16 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap16
happyOut16 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap16
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut16 #-}
newtype HappyWrap17 = HappyWrap17 ((Name AlexPosn, [KempeTy AlexPosn]))
happyIn17 :: ((Name AlexPosn, [KempeTy AlexPosn])) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn17 :: (Name AlexPosn, [KempeTy AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn17 (Name AlexPosn, [KempeTy AlexPosn])
x = HappyWrap17
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# ((Name AlexPosn, [KempeTy AlexPosn]) -> HappyWrap17
HappyWrap17 (Name AlexPosn, [KempeTy AlexPosn])
x)
{-# INLINE happyIn17 #-}
happyOut17 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> HappyWrap17
happyOut17 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
happyOut17 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut17 #-}
happyIn18 :: t18 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn18 :: t18 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn18 t18
x = t18 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t18
x
{-# INLINE happyIn18 #-}
happyOut18 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t18
happyOut18 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t18
happyOut18 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t18
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut18 #-}
happyIn19 :: t19 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn19 :: t19 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn19 t19
x = t19 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t19
x
{-# INLINE happyIn19 #-}
happyOut19 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t19
happyOut19 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t19
happyOut19 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t19
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut19 #-}
happyIn20 :: t20 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn20 :: t20 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn20 t20
x = t20 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t20
x
{-# INLINE happyIn20 #-}
happyOut20 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t20
happyOut20 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t20
happyOut20 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t20
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut20 #-}
happyIn21 :: t21 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn21 :: t21 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn21 t21
x = t21 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t21
x
{-# INLINE happyIn21 #-}
happyOut21 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t21
happyOut21 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut21 #-}
happyIn22 :: t22 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn22 :: t22 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn22 t22
x = t22 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t22
x
{-# INLINE happyIn22 #-}
happyOut22 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t22
happyOut22 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t22
happyOut22 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t22
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut22 #-}
happyIn23 :: t23 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn23 :: t23 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn23 t23
x = t23 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t23
x
{-# INLINE happyIn23 #-}
happyOut23 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t23
happyOut23 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t23
happyOut23 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t23
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut23 #-}
happyIn24 :: t24 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn24 :: t24 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn24 t24
x = t24 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t24
x
{-# INLINE happyIn24 #-}
happyOut24 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t24
happyOut24 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t24
happyOut24 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t24
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut24 #-}
happyIn25 :: t25 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn25 :: t25 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn25 t25
x = t25 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t25
x
{-# INLINE happyIn25 #-}
happyOut25 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t25
happyOut25 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t25
happyOut25 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t25
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut25 #-}
happyIn26 :: t26 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn26 :: t26 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn26 t26
x = t26 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t26
x
{-# INLINE happyIn26 #-}
happyOut26 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t26
happyOut26 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t26
happyOut26 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t26
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut26 #-}
happyIn27 :: t27 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn27 :: t27 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn27 t27
x = t27 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t27
x
{-# INLINE happyIn27 #-}
happyOut27 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t27
happyOut27 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t27
happyOut27 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t27
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut27 #-}
happyIn28 :: t28 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn28 :: t28 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn28 t28
x = t28 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t28
x
{-# INLINE happyIn28 #-}
happyOut28 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t28
happyOut28 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t28
happyOut28 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t28
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut28 #-}
happyIn29 :: t29 -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyIn29 :: t29 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn29 t29
x = t29 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# t29
x
{-# INLINE happyIn29 #-}
happyOut29 :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> t29
happyOut29 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t29
happyOut29 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t29
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOut29 #-}
happyInTok :: (Token AlexPosn) -> (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyInTok :: Token AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyInTok Token AlexPosn
x = Token AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
Happy_GHC_Exts.unsafeCoerce# Token AlexPosn
x
{-# INLINE happyInTok #-}
happyOutTok :: (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29) -> (Token AlexPosn)
happyOutTok :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x = HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
Happy_GHC_Exts.unsafeCoerce# HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
x
{-# INLINE happyOutTok #-}


happyExpList :: HappyAddr
happyExpList :: HappyAddr
happyExpList = Addr# -> HappyAddr
HappyA# Addr#
"\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x81\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x08\x04\x00\x00\x30\x00\xe0\x01\x00\x00\x00\x00\x02\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x80\x01\x00\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\xf8\xff\xff\x39\xc2\xf0\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x30\x00\xe0\x01\x00\x00\x00\x00\x20\x00\x00\x80\x01\x00\x0f\x00\x00\x00\x00\x20\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\xc0\x00\x80\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\xd0\xff\xff\xcf\x11\x86\x3f\x00\x00\x00\x80\x10\xfe\xff\x7f\x8e\x30\xfc\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\x20\x00\x00\x48\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\xf8\xff\xff\x39\xc2\xf0\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\x04\xf0\xff\xff\x73\x84\xe1\x0f\x00\x00"#

{-# NOINLINE happyExpListPerState #-}
happyExpListPerState :: Int -> [a]
happyExpListPerState Int
st =
    [a]
token_strs_expected
  where token_strs :: [a]
token_strs = [a
"error",a
"%dummy",a
"%start_parseModule",a
"Module",a
"Declarations",a
"Import",a
"ABI",a
"Decl",a
"TyDecl",a
"Type",a
"FunDecl",a
"FunSig",a
"FunBody",a
"Atom",a
"CaseLeaf",a
"Pattern",a
"TyLeaf",a
"braces__TyLeaf__",a
"braces__sepBy__TyLeaf__vbar____",a
"brackets__many__Atom____",a
"many__Atom__",a
"many__Decl__",a
"many__Import__",a
"many__Type__",a
"many__name__",a
"parens__many__Atom____",a
"sepBy__TyLeaf__vbar__",a
"some__CaseLeaf__",a
"many__CaseLeaf__",a
"arrow",a
"defEq",a
"colon",a
"lbrace",a
"rbrace",a
"lsqbracket",a
"rsqbracket",a
"lparen",a
"rparen",a
"vbar",a
"caseArr",a
"comma",a
"underscore",a
"plus",a
"plusU",a
"minus",a
"times",a
"timesU",a
"div",a
"percent",a
"eq",a
"neq",a
"leq",a
"lt",a
"geq",a
"gt",a
"shiftrU",a
"shiftlU",a
"shiftr",a
"shiftl",a
"neg",a
"and",a
"or",a
"name",a
"tyName",a
"foreignName",a
"moduleFile",a
"intLit",a
"wordLit",a
"int8Lit",a
"type",a
"case",a
"cfun",a
"if",a
"foreign",a
"cabi",a
"kabi",a
"import",a
"dip",a
"boolLit",a
"bool",a
"int",a
"int8",a
"word",a
"dup",a
"swap",a
"drop",a
"intXor",a
"wordXor",a
"boolXor",a
"popcount",a
"%eof"]
        bit_start :: Int
bit_start = Int
st Int -> Int -> Int
forall a. Num a => a -> a -> a
Prelude.* Int
91
        bit_end :: Int
bit_end = (Int
st Int -> Int -> Int
forall a. Num a => a -> a -> a
Prelude.+ Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
Prelude.* Int
91
        read_bit :: Int -> Bool
read_bit = HappyAddr -> Int -> Bool
readArrayBit HappyAddr
happyExpList
        bits :: [Bool]
bits = (Int -> Bool) -> [Int] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
Prelude.map Int -> Bool
read_bit [Int
bit_start..Int
bit_end Int -> Int -> Int
forall a. Num a => a -> a -> a
Prelude.- Int
1]
        bits_indexed :: [(Bool, Int)]
bits_indexed = [Bool] -> [Int] -> [(Bool, Int)]
forall a b. [a] -> [b] -> [(a, b)]
Prelude.zip [Bool]
bits [Int
0..Int
90]
        token_strs_expected :: [a]
token_strs_expected = ((Bool, Int) -> [a]) -> [(Bool, Int)] -> [a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
Prelude.concatMap (Bool, Int) -> [a]
f [(Bool, Int)]
bits_indexed
        f :: (Bool, Int) -> [a]
f (Bool
Prelude.False, Int
_) = []
        f (Bool
Prelude.True, Int
nr) = [[a]
token_strs [a] -> Int -> a
forall a. [a] -> Int -> a
Prelude.!! Int
nr]

happyActOffsets :: HappyAddr
happyActOffsets :: HappyAddr
happyActOffsets = Addr# -> HappyAddr
HappyA# Addr#
"\x00\x00\x00\x00\xd5\xff\xe4\xff\x00\x00\x00\x00\x31\x00\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2b\x00\x6b\x00\x3c\x00\x34\x00\x4e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\xff\x00\x00\x00\x00\x4d\x00\xf6\x00\xff\xff\x00\x00\x00\x00\x00\x00\x03\x00\x00\x00\x00\x00\x00\x00\xf0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\xff\x00\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6c\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x00\xf0\x00\x4f\x00\x53\x00\x00\x00\x00\x00\xf0\x00\x00\x00\x6a\x00\x00\x00\x6a\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x00\x88\x00\x2f\x00\x69\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\xfb\x00\x00\x00\x8b\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x00\x00\x00\x00\xd3\x00\x00\x00"#

happyGotoOffsets :: HappyAddr
happyGotoOffsets :: HappyAddr
happyGotoOffsets = Addr# -> HappyAddr
HappyA# Addr#
"\x5c\x00\x81\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x00\x00\x95\x00\x00\x00\x00\x00\x00\x00\x84\x00\x8a\x00\x00\x00\x8c\x00\x00\x00\x97\x00\x00\x00\x99\x00\x22\x00\x00\x00\x00\x00\x00\x00\x1b\x00\x00\x00\x00\x00\x96\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x93\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x98\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\xa9\x00\x00\x00\x00\x00\x00\x00\x9c\x00\xc1\x00\x00\x00\xbb\x00\x00\x00\xbf\x00\x00\x00\x00\x00\xbc\x00\xbd\x00\x4c\x00\x00\x00\x9e\x00\xc6\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\xc7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc8\x00\x00\x00\xc5\x00\xce\x00\x00\x00"#

happyAdjustOffset :: Happy_GHC_Exts.Int# -> Happy_GHC_Exts.Int#
happyAdjustOffset :: Int# -> Int#
happyAdjustOffset Int#
off = Int#
off

happyDefActions :: HappyAddr
happyDefActions :: HappyAddr
happyDefActions = Addr# -> HappyAddr
HappyA# Addr#
"\xb6\xff\x00\x00\xb8\xff\x00\x00\xfe\xff\xb7\xff\xfd\xff\x00\x00\xfc\xff\xb9\xff\xf9\xff\xf8\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfb\xff\xfa\xff\xb2\xff\xb4\xff\xec\xff\x00\x00\xe9\xff\xba\xff\x00\x00\x00\x00\x00\x00\xf7\xff\xf5\xff\xf6\xff\x00\x00\xb3\xff\xb5\xff\xb4\xff\x00\x00\xf3\xff\xf2\xff\xf1\xff\xf0\xff\xef\xff\xee\xff\xeb\xff\x00\x00\xbb\xff\x00\x00\xbc\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\xc9\xff\xca\xff\xcb\xff\xcc\xff\xcd\xff\xcf\xff\xce\xff\xe8\xff\xe7\xff\xe5\xff\xe4\xff\xe3\xff\x00\x00\x00\x00\xe0\xff\xdf\xff\xdd\xff\xde\xff\xc8\xff\xc7\xff\xc6\xff\xc5\xff\x00\x00\xea\xff\x00\x00\x00\x00\xf4\xff\xb4\xff\xbf\xff\xbd\xff\x00\x00\xbe\xff\x00\x00\x00\x00\xe2\xff\xba\xff\xba\xff\xac\xff\x00\x00\x00\x00\x00\x00\x00\x00\xed\xff\xaf\xff\xb0\xff\xb1\xff\xba\xff\xae\xff\x00\x00\xe6\xff\x00\x00\xc2\xff\xc3\xff\xc1\xff\xc0\xff\x00\x00\xe1\xff\xba\xff\xc4\xff"#

happyCheck :: HappyAddr
happyCheck :: HappyAddr
happyCheck = Addr# -> HappyAddr
HappyA# Addr#
"\xff\xff\x04\x00\x06\x00\x04\x00\x07\x00\x30\x00\x04\x00\x05\x00\x05\x00\x07\x00\x08\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\x22\x00\x3e\x00\x26\x00\x27\x00\x28\x00\x23\x00\x2b\x00\x0d\x00\x2c\x00\x25\x00\x01\x00\x02\x00\x02\x00\x31\x00\x32\x00\x0e\x00\x0f\x00\x17\x00\x04\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x0c\x00\x12\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\x22\x00\x05\x00\x26\x00\x27\x00\x28\x00\x05\x00\x0a\x00\x29\x00\x2c\x00\x00\x00\x0a\x00\x2d\x00\x23\x00\x31\x00\x32\x00\x2e\x00\x2f\x00\x18\x00\x19\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x04\x00\x03\x00\x13\x00\x22\x00\x24\x00\x09\x00\x2a\x00\x08\x00\x08\x00\x05\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\x23\x00\x09\x00\x26\x00\x27\x00\x28\x00\x0a\x00\x0a\x00\x13\x00\x2c\x00\x0b\x00\x09\x00\x03\x00\x15\x00\x31\x00\x32\x00\x10\x00\x0a\x00\x14\x00\x06\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x04\x00\x11\x00\x0b\x00\x14\x00\x06\x00\x09\x00\x06\x00\x16\x00\x06\x00\x14\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\x06\x00\x0d\x00\x26\x00\x27\x00\x28\x00\x0d\x00\x11\x00\x11\x00\x2c\x00\x0a\x00\x11\x00\x0a\x00\x0c\x00\x31\x00\x32\x00\x11\x00\x04\x00\x0a\x00\xff\xff\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\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\x01\x00\x08\x00\x26\x00\x27\x00\x28\x00\xff\xff\xff\xff\x08\x00\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\x31\x00\x32\x00\xff\xff\xff\xff\x0d\x00\xff\xff\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\xff\xff\x22\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x22\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\x26\x00\xff\xff\x33\x00\x34\x00\x35\x00\x36\x00\xff\xff\xff\xff\x33\x00\x34\x00\x35\x00\x36\x00\x32\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"#

happyTable :: HappyAddr
happyTable :: HappyAddr
happyTable = Addr# -> HappyAddr
HappyA# Addr#
"\x00\x00\x2e\x00\x19\x00\x20\x00\x2f\x00\x08\x00\x09\x00\x0a\x00\x57\x00\x0b\x00\x0c\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\x21\x00\xff\xff\x46\x00\x47\x00\x48\x00\x58\x00\x1a\x00\x54\x00\x49\x00\x09\x00\x04\x00\x05\x00\x17\x00\x4a\x00\x4b\x00\x1d\x00\x1e\x00\x55\x00\x2e\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x6b\x00\x06\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\x0e\x00\x5c\x00\x46\x00\x47\x00\x48\x00\x5a\x00\x5d\x00\x0f\x00\x49\x00\x03\x00\x5b\x00\x10\x00\x14\x00\x4a\x00\x4b\x00\x12\x00\x13\x00\x62\x00\x63\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x2e\x00\x15\x00\x02\x00\x1d\x00\x2b\x00\x6a\x00\x62\x00\x61\x00\x60\x00\x6e\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\x58\x00\x67\x00\x46\x00\x47\x00\x48\x00\x6d\x00\xad\xff\x02\x00\x49\x00\x76\x00\x15\x00\x10\x00\x1b\x00\x4a\x00\x4b\x00\x17\x00\x2c\x00\x1a\x00\x21\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x2e\x00\x2b\x00\x6b\x00\x53\x00\x52\x00\x75\x00\x5d\x00\x5e\x00\x21\x00\x58\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\x21\x00\x68\x00\x46\x00\x47\x00\x48\x00\x67\x00\x65\x00\x64\x00\x49\x00\x2c\x00\x73\x00\x2c\x00\x6e\x00\x4a\x00\x4b\x00\x76\x00\x2e\x00\x2c\x00\x00\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\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\x23\x00\x24\x00\x46\x00\x47\x00\x48\x00\x00\x00\x00\x00\x24\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4a\x00\x4b\x00\x00\x00\x00\x00\x70\x00\x00\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x00\x00\x25\x00\x26\x00\x00\x00\x00\x00\x00\x00\x00\x00\x25\x00\x26\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x00\x00\x00\x00\x00\x72\x00\x00\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x00\x00\x00\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x73\x00\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 :: Array
  Int
  (Int#
   -> Token AlexPosn
   -> Int#
   -> Happy_IntList
   -> HappyStk
        (HappyAbsSyn
           (Name AlexPosn, [KempeTy AlexPosn])
           [(Name AlexPosn, [KempeTy AlexPosn])]
           [Atom AlexPosn AlexPosn]
           [Atom AlexPosn AlexPosn]
           (Declarations AlexPosn AlexPosn AlexPosn)
           [ByteString]
           [KempeTy AlexPosn]
           [Name AlexPosn]
           [Atom AlexPosn AlexPosn]
           [(Name AlexPosn, [KempeTy AlexPosn])]
           (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
           [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
   -> Parse
        (HappyAbsSyn
           (Name AlexPosn, [KempeTy AlexPosn])
           [(Name AlexPosn, [KempeTy AlexPosn])]
           [Atom AlexPosn AlexPosn]
           [Atom AlexPosn AlexPosn]
           (Declarations AlexPosn AlexPosn AlexPosn)
           [ByteString]
           [KempeTy AlexPosn]
           [Name AlexPosn]
           [Atom AlexPosn AlexPosn]
           [(Name AlexPosn, [KempeTy AlexPosn])]
           (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
           [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
happyReduceArr = (Int, Int)
-> [(Int,
     Int#
     -> Token AlexPosn
     -> Int#
     -> Happy_IntList
     -> HappyStk
          (HappyAbsSyn
             (Name AlexPosn, [KempeTy AlexPosn])
             [(Name AlexPosn, [KempeTy AlexPosn])]
             [Atom AlexPosn AlexPosn]
             [Atom AlexPosn AlexPosn]
             (Declarations AlexPosn AlexPosn AlexPosn)
             [ByteString]
             [KempeTy AlexPosn]
             [Name AlexPosn]
             [Atom AlexPosn AlexPosn]
             [(Name AlexPosn, [KempeTy AlexPosn])]
             (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
             [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
     -> Parse
          (HappyAbsSyn
             (Name AlexPosn, [KempeTy AlexPosn])
             [(Name AlexPosn, [KempeTy AlexPosn])]
             [Atom AlexPosn AlexPosn]
             [Atom AlexPosn AlexPosn]
             (Declarations AlexPosn AlexPosn AlexPosn)
             [ByteString]
             [KempeTy AlexPosn]
             [Name AlexPosn]
             [Atom AlexPosn AlexPosn]
             [(Name AlexPosn, [KempeTy AlexPosn])]
             (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
             [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))]
-> Array
     Int
     (Int#
      -> Token AlexPosn
      -> Int#
      -> Happy_IntList
      -> HappyStk
           (HappyAbsSyn
              (Name AlexPosn, [KempeTy AlexPosn])
              [(Name AlexPosn, [KempeTy AlexPosn])]
              [Atom AlexPosn AlexPosn]
              [Atom AlexPosn AlexPosn]
              (Declarations AlexPosn AlexPosn AlexPosn)
              [ByteString]
              [KempeTy AlexPosn]
              [Name AlexPosn]
              [Atom AlexPosn AlexPosn]
              [(Name AlexPosn, [KempeTy AlexPosn])]
              (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
              [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
      -> Parse
           (HappyAbsSyn
              (Name AlexPosn, [KempeTy AlexPosn])
              [(Name AlexPosn, [KempeTy AlexPosn])]
              [Atom AlexPosn AlexPosn]
              [Atom AlexPosn AlexPosn]
              (Declarations AlexPosn AlexPosn AlexPosn)
              [ByteString]
              [KempeTy AlexPosn]
              [Name AlexPosn]
              [Atom AlexPosn AlexPosn]
              [(Name AlexPosn, [KempeTy AlexPosn])]
              (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
              [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
Happy_Data_Array.array (Int
1, Int
83) [
	(Int
1 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_1),
	(Int
2 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_2),
	(Int
3 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_3),
	(Int
4 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_4),
	(Int
5 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_5),
	(Int
6 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_6),
	(Int
7 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_7),
	(Int
8 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_8),
	(Int
9 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_9),
	(Int
10 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_10),
	(Int
11 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_11),
	(Int
12 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_12),
	(Int
13 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_13),
	(Int
14 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_14),
	(Int
15 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_15),
	(Int
16 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_16),
	(Int
17 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_17),
	(Int
18 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_18),
	(Int
19 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_19),
	(Int
20 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_20),
	(Int
21 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_21),
	(Int
22 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_22),
	(Int
23 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_23),
	(Int
24 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_24),
	(Int
25 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_25),
	(Int
26 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_26),
	(Int
27 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_27),
	(Int
28 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_28),
	(Int
29 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_29),
	(Int
30 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_30),
	(Int
31 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_31),
	(Int
32 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_32),
	(Int
33 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_33),
	(Int
34 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_34),
	(Int
35 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_35),
	(Int
36 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_36),
	(Int
37 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_37),
	(Int
38 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_38),
	(Int
39 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_39),
	(Int
40 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_40),
	(Int
41 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_41),
	(Int
42 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_42),
	(Int
43 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_43),
	(Int
44 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_44),
	(Int
45 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_45),
	(Int
46 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_46),
	(Int
47 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_47),
	(Int
48 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_48),
	(Int
49 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_49),
	(Int
50 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_50),
	(Int
51 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_51),
	(Int
52 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_52),
	(Int
53 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_53),
	(Int
54 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_54),
	(Int
55 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_55),
	(Int
56 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_56),
	(Int
57 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_57),
	(Int
58 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_58),
	(Int
59 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_59),
	(Int
60 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_60),
	(Int
61 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_61),
	(Int
62 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_62),
	(Int
63 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_63),
	(Int
64 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_64),
	(Int
65 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_65),
	(Int
66 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_66),
	(Int
67 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_67),
	(Int
68 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_68),
	(Int
69 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_69),
	(Int
70 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_70),
	(Int
71 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_71),
	(Int
72 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_72),
	(Int
73 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_73),
	(Int
74 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_74),
	(Int
75 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_75),
	(Int
76 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_76),
	(Int
77 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_77),
	(Int
78 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_78),
	(Int
79 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_79),
	(Int
80 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_80),
	(Int
81 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_81),
	(Int
82 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_82),
	(Int
83 , Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_83)
	]

happy_n_terms :: Int
happy_n_terms = Int
63 :: Prelude.Int
happy_n_nonterms :: Int
happy_n_nonterms = Int
26 :: Prelude.Int

#if __GLASGOW_HASKELL__ >= 710
happyReduce_1 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_1 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_1 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
0# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25 t26
       t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_1
happyReduction_1 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_1 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn
  t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
-> [ByteString]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t23
happyOut23 HappyAbsSyn
  t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
happy_x_1 of { [ByteString]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap5
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap5
happyOut5 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap5 Declarations AlexPosn AlexPosn AlexPosn
happy_var_2) -> 
	Module AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Module AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn4
		 ([ByteString]
-> Declarations AlexPosn AlexPosn AlexPosn
-> Module AlexPosn AlexPosn AlexPosn
forall a c b. [ByteString] -> [KempeDecl a c b] -> Module a c b
Module ([ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse [ByteString]
happy_var_1) Declarations AlexPosn AlexPosn AlexPosn
happy_var_2
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_2 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_2 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_2 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
1# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21
       t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_2
happyReduction_2 :: HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_2 HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> Declarations AlexPosn AlexPosn AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t22
happyOut22 HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1 of { Declarations AlexPosn AlexPosn AlexPosn
happy_var_1 -> 
	Declarations AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Declarations AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn5
		 ((Declarations AlexPosn AlexPosn AlexPosn
-> Declarations AlexPosn AlexPosn AlexPosn
forall a. [a] -> [a]
reverse Declarations AlexPosn AlexPosn AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_3 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_3 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_3 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
2# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 p t18 t19
       t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_3
happyReduction_3 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_3 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	p
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (TokModuleStr AlexPosn
_ ByteString
happy_var_2) -> 
	ByteString
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
ByteString
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn6
		 (ByteString
happy_var_2
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_4 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_4 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_4 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
3# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall p t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_4
happyReduction_4 :: p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_4 p
happy_x_1
	 =  ABI -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
ABI -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn7
		 (ABI
Cabi
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_5 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_5 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_5 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
3# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall p t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_5
happyReduction_5 :: p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_5 p
happy_x_1
	 =  ABI -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
ABI -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn7
		 (ABI
Kabi
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_6 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_6 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_6 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
4# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_6
happyReduction_6 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_6 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap9
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap9
happyOut9 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (HappyWrap9 KempeDecl AlexPosn AlexPosn AlexPosn
happy_var_1) -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn8
		 (KempeDecl AlexPosn AlexPosn AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_7 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_7 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_7 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
4# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_7
happyReduction_7 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_7 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap11
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap11
happyOut11 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (HappyWrap11 KempeDecl AlexPosn AlexPosn AlexPosn
happy_var_1) -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn8
		 (KempeDecl AlexPosn AlexPosn AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_8 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_8 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_8 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
4# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25
       t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_8
happyReduction_8 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_8 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokKeyword AlexPosn
happy_var_1 Keyword
KwForeign) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap7
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap7
happyOut7 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap7 ABI
happy_var_2) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3 of { (TokName AlexPosn
_ Name AlexPosn
happy_var_3) -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn8
		 (AlexPosn
-> ABI -> Name AlexPosn -> KempeDecl AlexPosn AlexPosn AlexPosn
forall a c b. b -> ABI -> Name b -> KempeDecl a c b
Export AlexPosn
happy_var_1 ABI
happy_var_2 Name AlexPosn
happy_var_3
	)}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_9 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_9 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_9 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
4# Int#
5# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t20 t21 t22 t23 t24 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn
     t18
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        [(Name AlexPosn, [KempeTy AlexPosn])]
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
happyReduction_9
happyReduction_9 :: HappyStk
  (HappyAbsSyn
     t18
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        [(Name AlexPosn, [KempeTy AlexPosn])]
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
happyReduction_9 (HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     t18
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
happyRest)
	 = case HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_1 of { (TokKeyword AlexPosn
happy_var_1 Keyword
KwType) -> 
	case HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_2 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_2) -> 
	case HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> [Name AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t25
happyOut25 HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_3 of { [Name AlexPosn]
happy_var_3 -> 
	case HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> [(Name AlexPosn, [KempeTy AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t19
happyOut19 HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_4 of { [(Name AlexPosn, [KempeTy AlexPosn])]
happy_var_4 -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn
     t18
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn9
		 (AlexPosn
-> Name AlexPosn
-> [Name AlexPosn]
-> [(Name AlexPosn, [KempeTy AlexPosn])]
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a c b.
a
-> TyName a
-> [TyName a]
-> [(Name b, [KempeTy a])]
-> KempeDecl a c b
TyDecl AlexPosn
happy_var_1 Name AlexPosn
happy_var_2 ([Name AlexPosn] -> [Name AlexPosn]
forall a. [a] -> [a]
reverse [Name AlexPosn]
happy_var_3) ([(Name AlexPosn, [KempeTy AlexPosn])]
-> [(Name AlexPosn, [KempeTy AlexPosn])]
forall a. [a] -> [a]
reverse [(Name AlexPosn, [KempeTy AlexPosn])]
happy_var_4)
	) HappyAbsSyn
  t18
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> HappyStk
     (HappyAbsSyn
        t18
        [(Name AlexPosn, [KempeTy AlexPosn])]
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
-> HappyStk
     (HappyAbsSyn
        t18
        [(Name AlexPosn, [KempeTy AlexPosn])]
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     t18
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
happyRest}}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_10 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_10 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_10 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
4# Int#
5# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t19 t20 t21 t22 t23 t24 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        t19
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
happyReduction_10
happyReduction_10 :: HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        t19
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
happyReduction_10 (HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
happyRest)
	 = case HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_1 of { (TokKeyword AlexPosn
happy_var_1 Keyword
KwType) -> 
	case HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_2 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_2) -> 
	case HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> [Name AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t25
happyOut25 HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_3 of { [Name AlexPosn]
happy_var_3 -> 
	case HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> (Name AlexPosn, [KempeTy AlexPosn])
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t18
happyOut18 HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
happy_x_4 of { (Name AlexPosn, [KempeTy AlexPosn])
happy_var_4 -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn9
		 (AlexPosn
-> Name AlexPosn
-> [Name AlexPosn]
-> [(Name AlexPosn, [KempeTy AlexPosn])]
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a c b.
a
-> TyName a
-> [TyName a]
-> [(Name b, [KempeTy a])]
-> KempeDecl a c b
TyDecl AlexPosn
happy_var_1 Name AlexPosn
happy_var_2 ([Name AlexPosn] -> [Name AlexPosn]
forall a. [a] -> [a]
reverse [Name AlexPosn]
happy_var_3) [(Name AlexPosn, [KempeTy AlexPosn])
happy_var_4]
	) HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  t19
  t20
  t21
  t22
  t23
  t24
  [Name AlexPosn]
  t26
  t27
  t28
  t29
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        t19
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        t19
        t20
        t21
        t22
        t23
        t24
        [Name AlexPosn]
        t26
        t27
        t28
        t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     [Name AlexPosn]
     t26
     t27
     t28
     t29)
happyRest}}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_11 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_11 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_11 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
5# Int#
5# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t21 t22 t23 t24 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
happyReduction_11
happyReduction_11 :: HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
happyReduction_11 (HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_5 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
happyRest)
	 = case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_1 of { (TokKeyword AlexPosn
happy_var_1 Keyword
KwType) -> 
	case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_2 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_2) -> 
	case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> [Name AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t25
happyOut25 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_3 of { [Name AlexPosn]
happy_var_3 -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn9
		 (AlexPosn
-> Name AlexPosn
-> [Name AlexPosn]
-> [(Name AlexPosn, [KempeTy AlexPosn])]
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a c b.
a
-> TyName a
-> [TyName a]
-> [(Name b, [KempeTy a])]
-> KempeDecl a c b
TyDecl AlexPosn
happy_var_1 Name AlexPosn
happy_var_2 ([Name AlexPosn] -> [Name AlexPosn]
forall a. [a] -> [a]
reverse [Name AlexPosn]
happy_var_3) []
	) HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29)
happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_12 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_12 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_12 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
6# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_12
happyReduction_12 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_12 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokName AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn -> Name AlexPosn -> KempeTy AlexPosn
forall a. a -> Name a -> KempeTy a
TyVar (Name AlexPosn -> AlexPosn
forall a. Name a -> a
Name.loc Name AlexPosn
happy_var_1) Name AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_13 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_13 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_13 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
6# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_13
happyReduction_13 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_13 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn -> Name AlexPosn -> KempeTy AlexPosn
forall a. a -> Name a -> KempeTy a
TyNamed (Name AlexPosn -> AlexPosn
forall a. Name a -> a
Name.loc Name AlexPosn
happy_var_1) Name AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_14 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_14 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_14 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
6# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_14
happyReduction_14 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_14 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinBool) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn -> BuiltinTy -> KempeTy AlexPosn
forall a. a -> BuiltinTy -> KempeTy a
TyBuiltin AlexPosn
happy_var_1 BuiltinTy
TyBool
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_15 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_15 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_15 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
6# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_15
happyReduction_15 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_15 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinInt) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn -> BuiltinTy -> KempeTy AlexPosn
forall a. a -> BuiltinTy -> KempeTy a
TyBuiltin AlexPosn
happy_var_1 BuiltinTy
TyInt
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_16 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_16 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_16 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
6# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_16
happyReduction_16 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_16 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinInt8) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn -> BuiltinTy -> KempeTy AlexPosn
forall a. a -> BuiltinTy -> KempeTy a
TyBuiltin AlexPosn
happy_var_1 BuiltinTy
TyInt8
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_17 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_17 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_17 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
6# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_17
happyReduction_17 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_17 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinWord) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn -> BuiltinTy -> KempeTy AlexPosn
forall a. a -> BuiltinTy -> KempeTy a
TyBuiltin AlexPosn
happy_var_1 BuiltinTy
TyWord
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_18 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_18 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_18 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
4# Int#
6# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyReduction_18
happyReduction_18 :: HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyReduction_18 (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_4 `HappyStk`
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3 `HappyStk`
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 `HappyStk`
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyRest)
	 = case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
LParen) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
happyOut10 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap10 KempeTy AlexPosn
happy_var_2) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
happyOut10 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3 of { (HappyWrap10 KempeTy AlexPosn
happy_var_3) -> 
	KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeTy AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn10
		 (AlexPosn
-> KempeTy AlexPosn -> KempeTy AlexPosn -> KempeTy AlexPosn
forall a. a -> KempeTy a -> KempeTy a -> KempeTy a
TyApp AlexPosn
happy_var_1 KempeTy AlexPosn
happy_var_2 KempeTy AlexPosn
happy_var_3
	) HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_19 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_19 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_19 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
7# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25
       t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_19
happyReduction_19 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_19 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap12
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap12
happyOut12 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (HappyWrap12 (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
happy_var_1) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap13
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap13
happyOut13 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap13 [Atom AlexPosn AlexPosn]
happy_var_2) -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn11
		 ((AlexPosn
 -> Name AlexPosn
 -> [KempeTy AlexPosn]
 -> [KempeTy AlexPosn]
 -> [Atom AlexPosn AlexPosn]
 -> KempeDecl AlexPosn AlexPosn AlexPosn)
-> (AlexPosn, Name AlexPosn, [KempeTy AlexPosn],
    [KempeTy AlexPosn])
-> [Atom AlexPosn AlexPosn]
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a b c d e. (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 AlexPosn
-> Name AlexPosn
-> [KempeTy AlexPosn]
-> [KempeTy AlexPosn]
-> [Atom AlexPosn AlexPosn]
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a c b.
b
-> Name b
-> [KempeTy a]
-> [KempeTy a]
-> [Atom c b]
-> KempeDecl a c b
FunDecl (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
happy_var_1 [Atom AlexPosn AlexPosn]
happy_var_2
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_20 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_20 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_20 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
4# Int#
7# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyReduction_20
happyReduction_20 :: HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyReduction_20 (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_4 `HappyStk`
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3 `HappyStk`
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 `HappyStk`
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyRest)
	 = case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap12
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap12
happyOut12 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (HappyWrap12 (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
happy_var_1) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_4 of { (TokForeign AlexPosn
_ ByteString
happy_var_4) -> 
	KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
KempeDecl AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn11
		 ((AlexPosn
 -> Name AlexPosn
 -> [KempeTy AlexPosn]
 -> [KempeTy AlexPosn]
 -> ByteString
 -> KempeDecl AlexPosn AlexPosn AlexPosn)
-> (AlexPosn, Name AlexPosn, [KempeTy AlexPosn],
    [KempeTy AlexPosn])
-> ByteString
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a b c d e. (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 AlexPosn
-> Name AlexPosn
-> [KempeTy AlexPosn]
-> [KempeTy AlexPosn]
-> ByteString
-> KempeDecl AlexPosn AlexPosn AlexPosn
forall a c b.
b
-> Name b
-> [KempeTy a]
-> [KempeTy a]
-> ByteString
-> KempeDecl a c b
ExtFnDecl (AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
happy_var_1 ByteString
happy_var_4
	) HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29)
happyRest}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_21 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_21 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_21 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
5# Int#
8# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t21 t22 t23 t25 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
happyReduction_21
happyReduction_21 :: HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
happyReduction_21 (HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_5 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
happyRest)
	 = case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_1 of { (TokName AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_2 of { (TokSym AlexPosn
happy_var_2 Sym
Colon) -> 
	case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> [KempeTy AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t24
happyOut24 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_3 of { [KempeTy AlexPosn]
happy_var_3 -> 
	case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> [KempeTy AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t24
happyOut24 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_5 of { [KempeTy AlexPosn]
happy_var_5 -> 
	(AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
(AlexPosn, Name AlexPosn, [KempeTy AlexPosn], [KempeTy AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn12
		 ((AlexPosn
happy_var_2, Name AlexPosn
happy_var_1, [KempeTy AlexPosn] -> [KempeTy AlexPosn]
forall a. [a] -> [a]
reverse [KempeTy AlexPosn]
happy_var_3, [KempeTy AlexPosn] -> [KempeTy AlexPosn]
forall a. [a] -> [a]
reverse [KempeTy AlexPosn]
happy_var_5)
	) HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
-> HappyStk
     (HappyAbsSyn
        t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29)
happyRest}}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_22 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_22 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_22 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
9# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t21 t22 t23 t24 t25 t26 t27 t28 t29 p t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn
  t18
  t19
  [Atom AlexPosn AlexPosn]
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_22
happyReduction_22 :: HappyAbsSyn
  t18
  t19
  [Atom AlexPosn AlexPosn]
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> p -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_22 HappyAbsSyn
  t18
  t19
  [Atom AlexPosn AlexPosn]
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_2
	p
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  [Atom AlexPosn AlexPosn]
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> [Atom AlexPosn AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t20
happyOut20 HappyAbsSyn
  t18
  t19
  [Atom AlexPosn AlexPosn]
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_2 of { [Atom AlexPosn AlexPosn]
happy_var_2 -> 
	[Atom AlexPosn AlexPosn]
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
[Atom AlexPosn AlexPosn]
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn13
		 ([Atom AlexPosn AlexPosn] -> [Atom AlexPosn AlexPosn]
forall a. [a] -> [a]
reverse [Atom AlexPosn AlexPosn]
happy_var_2
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_23 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_23 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_23 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_23
happyReduction_23 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_23 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokName AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> Name AlexPosn -> Atom AlexPosn AlexPosn
forall c b. b -> Name b -> Atom c b
AtName (Name AlexPosn -> AlexPosn
forall a. Name a -> a
Name.loc Name AlexPosn
happy_var_1) Name AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_24 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_24 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_24 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_24
happyReduction_24 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_24 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> Name AlexPosn -> Atom AlexPosn AlexPosn
forall c b. c -> TyName c -> Atom c b
AtCons (Name AlexPosn -> AlexPosn
forall a. Name a -> a
Name.loc Name AlexPosn
happy_var_1) Name AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_25 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_25 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_25 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
4# Int#
10# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t29.
HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        t21
        t22
        t23
        t24
        t25
        t26
        t27
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        t29)
happyReduction_25
happyReduction_25 :: HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        t21
        t22
        t23
        t24
        t25
        t26
        t27
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        t29)
happyReduction_25 (HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29)
happyRest)
	 = case HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
happy_x_2 of { (TokKeyword AlexPosn
happy_var_2 Keyword
KwCase) -> 
	case HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
-> NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t28
happyOut28 HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
happy_x_3 of { NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
happy_var_3 -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn
-> NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> Atom AlexPosn AlexPosn
forall c b. b -> NonEmpty (Pattern c b, [Atom c b]) -> Atom c b
Case AlexPosn
happy_var_2 (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
forall a. NonEmpty a -> NonEmpty a
NE.reverse NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
happy_var_3)
	) HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  t29
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        t21
        t22
        t23
        t24
        t25
        t26
        t27
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        t21
        t22
        t23
        t24
        t25
        t26
        t27
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29)
happyRest}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_26 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_26 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_26 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_26
happyReduction_26 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_26 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (happy_var_1 :: Token AlexPosn
happy_var_1@(TokInt AlexPosn
_ Integer
_)) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> Integer -> Atom AlexPosn AlexPosn
forall c b. b -> Integer -> Atom c b
IntLit (Token AlexPosn -> AlexPosn
forall a. Token a -> a
loc Token AlexPosn
happy_var_1) (Token AlexPosn -> Integer
forall a. Token a -> Integer
int Token AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_27 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_27 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_27 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_27
happyReduction_27 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_27 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (happy_var_1 :: Token AlexPosn
happy_var_1@(TokWord AlexPosn
_ Natural
_)) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> Natural -> Atom AlexPosn AlexPosn
forall c b. b -> Natural -> Atom c b
WordLit (Token AlexPosn -> AlexPosn
forall a. Token a -> a
loc Token AlexPosn
happy_var_1) (Token AlexPosn -> Natural
forall a. Token a -> Natural
word Token AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_28 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_28 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_28 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_28
happyReduction_28 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_28 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (happy_var_1 :: Token AlexPosn
happy_var_1@(TokInt8 AlexPosn
_ Int8
_)) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> Int8 -> Atom AlexPosn AlexPosn
forall c b. b -> Int8 -> Atom c b
Int8Lit (Token AlexPosn -> AlexPosn
forall a. Token a -> a
loc Token AlexPosn
happy_var_1) (Token AlexPosn -> Int8
forall a. Token a -> Int8
int8 Token AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_29 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_29 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_29 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t27 t28 t29 t18 t19 t20 t21
       t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25 t26
       t27 t28 t29.
HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  [Atom AlexPosn AlexPosn]
  t27
  t28
  t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_29
happyReduction_29 :: HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  [Atom AlexPosn AlexPosn]
  t27
  t28
  t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_29 HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  [Atom AlexPosn AlexPosn]
  t27
  t28
  t29
happy_x_2
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinDip) -> 
	case HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  [Atom AlexPosn AlexPosn]
  t27
  t28
  t29
-> [Atom AlexPosn AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t26
happyOut26 HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  [Atom AlexPosn AlexPosn]
  t27
  t28
  t29
happy_x_2 of { [Atom AlexPosn AlexPosn]
happy_var_2 -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> [Atom AlexPosn AlexPosn] -> Atom AlexPosn AlexPosn
forall c b. b -> [Atom c b] -> Atom c b
Dip AlexPosn
happy_var_1 ([Atom AlexPosn AlexPosn] -> [Atom AlexPosn AlexPosn]
forall a. [a] -> [a]
reverse [Atom AlexPosn AlexPosn]
happy_var_2)
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_30 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_30 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_30 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
6# Int#
10# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t22 t23 t24 t25 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
happyReduction_30
happyReduction_30 :: HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
happyReduction_30 (HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_6 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_5 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
happyRest)
	 = case HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1 of { (TokKeyword AlexPosn
happy_var_1 Keyword
KwIf) -> 
	case HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> [Atom AlexPosn AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_3 of { [Atom AlexPosn AlexPosn]
happy_var_3 -> 
	case HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> [Atom AlexPosn AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_5 of { [Atom AlexPosn AlexPosn]
happy_var_5 -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn
-> [Atom AlexPosn AlexPosn]
-> [Atom AlexPosn AlexPosn]
-> Atom AlexPosn AlexPosn
forall c b. b -> [Atom c b] -> [Atom c b] -> Atom c b
If AlexPosn
happy_var_1 ([Atom AlexPosn AlexPosn] -> [Atom AlexPosn AlexPosn]
forall a. [a] -> [a]
reverse [Atom AlexPosn AlexPosn]
happy_var_3) ([Atom AlexPosn AlexPosn] -> [Atom AlexPosn AlexPosn]
forall a. [a] -> [a]
reverse [Atom AlexPosn AlexPosn]
happy_var_5)
	) HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_31 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_31 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_31 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_31
happyReduction_31 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_31 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (happy_var_1 :: Token AlexPosn
happy_var_1@(TokBuiltin AlexPosn
_ (BuiltinBoolLit Bool
_))) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> Bool -> Atom AlexPosn AlexPosn
forall c b. b -> Bool -> Atom c b
BoolLit (Token AlexPosn -> AlexPosn
forall a. Token a -> a
loc Token AlexPosn
happy_var_1) (Builtin -> Bool
bool (Builtin -> Bool) -> Builtin -> Bool
forall a b. (a -> b) -> a -> b
$ Token AlexPosn -> Builtin
forall a. Token a -> Builtin
builtin Token AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_32 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_32 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_32 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_32
happyReduction_32 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_32 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinDup) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
Dup
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_33 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_33 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_33 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_33
happyReduction_33 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_33 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinDrop) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
Drop
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_34 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_34 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_34 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_34
happyReduction_34 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_34 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinSwap) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
Swap
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_35 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_35 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_35 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_35
happyReduction_35 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_35 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Plus) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntPlus
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_36 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_36 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_36 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_36
happyReduction_36 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_36 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
PlusU) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
WordPlus
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_37 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_37 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_37 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_37
happyReduction_37 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_37 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Minus) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntMinus
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_38 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_38 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_38 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_38
happyReduction_38 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_38 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Times) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntTimes
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_39 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_39 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_39 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_39
happyReduction_39 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_39 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
TimesU) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
WordTimes
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_40 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_40 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_40 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_40
happyReduction_40 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_40 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Div) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntDiv
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_41 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_41 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_41 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_41
happyReduction_41 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_41 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Percent) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntMod
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_42 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_42 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_42 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_42
happyReduction_42 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_42 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Eq) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntEq
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_43 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_43 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_43 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_43
happyReduction_43 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_43 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Neq) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntNeq
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_44 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_44 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_44 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_44
happyReduction_44 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_44 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Leq) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntLeq
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_45 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_45 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_45 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_45
happyReduction_45 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_45 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Lt) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntLt
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_46 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_46 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_46 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_46
happyReduction_46 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_46 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Geq) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntGeq
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_47 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_47 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_47 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_47
happyReduction_47 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_47 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Gt) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntGt
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_48 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_48 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_48 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_48
happyReduction_48 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_48 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
AndTok) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
And
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_49 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_49 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_49 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_49
happyReduction_49 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_49 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
OrTok) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
Or
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_50 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_50 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_50 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_50
happyReduction_50 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_50 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
NegTok) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntNeg
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_51 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_51 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_51 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_51
happyReduction_51 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_51 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
ShiftL) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntShiftL
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_52 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_52 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_52 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_52
happyReduction_52 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_52 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
ShiftR) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntShiftR
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_53 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_53 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_53 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_53
happyReduction_53 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_53 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
ShiftLU) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
WordShiftL
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_54 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_54 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_54 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_54
happyReduction_54 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_54 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
ShiftRU) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
WordShiftR
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_55 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_55 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_55 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_55
happyReduction_55 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_55 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinIntXor) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
IntXor
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_56 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_56 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_56 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_56
happyReduction_56 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_56 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinWordXor) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
WordXor
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_57 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_57 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_57 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_57
happyReduction_57 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_57 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinBoolXor) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
Xor
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_58 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_58 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_58 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
10# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_58
happyReduction_58 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_58 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokBuiltin AlexPosn
happy_var_1 Builtin
BuiltinPopcount) -> 
	Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Atom AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn14
		 (AlexPosn -> BuiltinFn -> Atom AlexPosn AlexPosn
forall c b. b -> BuiltinFn -> Atom c b
AtBuiltin AlexPosn
happy_var_1 BuiltinFn
Popcount
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_59 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_59 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_59 = Int#
-> Int#
-> (HappyStk
      (HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
    -> HappyStk
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce Int#
4# Int#
11# HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall t18 t19 t20 t22 t23 t24 t25 t26 t27 t28 t29.
HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
happyReduction_59
happyReduction_59 :: HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
happyReduction_59 (HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_4 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_3 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_2 `HappyStk`
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1 `HappyStk`
	HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
happyRest)
	 = case HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> HappyWrap16
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap16
happyOut16 HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_2 of { (HappyWrap16 Pattern AlexPosn AlexPosn
happy_var_2) -> 
	case HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> [Atom AlexPosn AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_4 of { [Atom AlexPosn AlexPosn]
happy_var_4 -> 
	(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn15
		 ((Pattern AlexPosn AlexPosn
happy_var_2, [Atom AlexPosn AlexPosn] -> [Atom AlexPosn AlexPosn]
forall a. [a] -> [a]
reverse [Atom AlexPosn AlexPosn]
happy_var_4)
	) HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
-> HappyStk
     (HappyAbsSyn
        t18
        t19
        t20
        [Atom AlexPosn AlexPosn]
        t22
        t23
        t24
        t25
        t26
        t27
        t28
        t29)
forall a. a -> HappyStk a -> HappyStk a
`HappyStk` HappyStk
  (HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29)
happyRest}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_60 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_60 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_60 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
12# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_60
happyReduction_60 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_60 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn16
		 (AlexPosn -> Name AlexPosn -> Pattern AlexPosn AlexPosn
forall c b. c -> TyName c -> Pattern c b
PatternCons (Name AlexPosn -> AlexPosn
forall a. Name a -> a
Name.loc Name AlexPosn
happy_var_1) Name AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_61 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_61 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_61 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
12# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_61
happyReduction_61 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_61 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokSym AlexPosn
happy_var_1 Sym
Underscore) -> 
	Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn16
		 (AlexPosn -> Pattern AlexPosn AlexPosn
forall c b. b -> Pattern c b
PatternWildcard AlexPosn
happy_var_1
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_62 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_62 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_62 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
12# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_62
happyReduction_62 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_62 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (happy_var_1 :: Token AlexPosn
happy_var_1@(TokInt AlexPosn
_ Integer
_)) -> 
	Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn16
		 (AlexPosn -> Integer -> Pattern AlexPosn AlexPosn
forall c b. b -> Integer -> Pattern c b
PatternInt (Token AlexPosn -> AlexPosn
forall a. Token a -> a
loc Token AlexPosn
happy_var_1) (Token AlexPosn -> Integer
forall a. Token a -> Integer
int Token AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_63 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_63 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_63 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_1  Int#
12# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_63
happyReduction_63 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_63 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (happy_var_1 :: Token AlexPosn
happy_var_1@(TokBuiltin AlexPosn
_ (BuiltinBoolLit Bool
_))) -> 
	Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
Pattern AlexPosn AlexPosn
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn16
		 (AlexPosn -> Bool -> Pattern AlexPosn AlexPosn
forall c b. b -> Bool -> Pattern c b
PatternBool (Token AlexPosn -> AlexPosn
forall a. Token a -> a
loc Token AlexPosn
happy_var_1) (Builtin -> Bool
bool (Builtin -> Bool) -> Builtin -> Bool
forall a b. (a -> b) -> a -> b
$ Token AlexPosn -> Builtin
forall a. Token a -> Builtin
builtin Token AlexPosn
happy_var_1)
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_64 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_64 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_64 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
13# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t25 t26 t27 t28 t29 t18 t19 t20 t21
       t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25 t26
       t27 t28 t29.
HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_64
happyReduction_64 :: HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_64 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (TokTyName  AlexPosn
_ Name AlexPosn
happy_var_1) -> 
	case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> [KempeTy AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t24
happyOut24 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_2 of { [KempeTy AlexPosn]
happy_var_2 -> 
	(Name AlexPosn, [KempeTy AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
(Name AlexPosn, [KempeTy AlexPosn])
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn17
		 ((Name AlexPosn
happy_var_1, [KempeTy AlexPosn] -> [KempeTy AlexPosn]
forall a. [a] -> [a]
reverse [KempeTy AlexPosn]
happy_var_2)
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_65 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_65 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_65 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
14# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall p t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 p t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
happyReduction_65
happyReduction_65 :: p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
happyReduction_65 p
happy_x_3
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	p
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
happyOut17 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap17 (Name AlexPosn, [KempeTy AlexPosn])
happy_var_2) -> 
	(Name AlexPosn, [KempeTy AlexPosn])
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
t18 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn18
		 ((Name AlexPosn, [KempeTy AlexPosn])
happy_var_2
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_66 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_66 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_66 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
15# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall p t18 t19 t20 t21 t22 t23 t24 t25 t26 t19 t28 t29 p t18 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t19 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_66
happyReduction_66 :: p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t19 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_66 p
happy_x_3
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t19 t28 t29
happy_x_2
	p
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t19 t28 t29 -> t19
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t27
happyOut27 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t19 t28 t29
happy_x_2 of { t19
happy_var_2 -> 
	t19 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t19 t18 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
t19 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn19
		 (t19
happy_var_2
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_67 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_67 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_67 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
16# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall p t18 t19 t20 t20 t22 t23 t24 t25 t26 t27 t28 t29 p t18 t19
       t21 t22 t23 t24 t25 t26 t27 t28 t29.
p
-> HappyAbsSyn t18 t19 t20 t20 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_67
happyReduction_67 :: p
-> HappyAbsSyn t18 t19 t20 t20 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_67 p
happy_x_3
	HappyAbsSyn t18 t19 t20 t20 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	p
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t20 t22 t23 t24 t25 t26 t27 t28 t29 -> t20
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn t18 t19 t20 t20 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { t20
happy_var_2 -> 
	t20 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t20 t18 t19 t21 t22 t23 t24 t25 t26 t27 t28 t29.
t20 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn20
		 (t20
happy_var_2
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_68 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_68 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_68 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
17# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t22 t23 t24 t25 t26 t27
       t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
happyReduction_68
happyReduction_68 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
happyReduction_68 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> [Atom AlexPosn AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn
  t18
  t19
  t20
  [Atom AlexPosn AlexPosn]
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1 of { [Atom AlexPosn AlexPosn]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap14
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap14
happyOut14 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap14 Atom AlexPosn AlexPosn
happy_var_2) -> 
	[Atom AlexPosn AlexPosn]
-> HappyAbsSyn
     t18
     t19
     t20
     [Atom AlexPosn AlexPosn]
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     t29
forall t21 t18 t19 t20 t22 t23 t24 t25 t26 t27 t28 t29.
t21 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn21
		 (Atom AlexPosn AlexPosn
happy_var_2 Atom AlexPosn AlexPosn
-> [Atom AlexPosn AlexPosn] -> [Atom AlexPosn AlexPosn]
forall k1. k1 -> [k1] -> [k1]
: [Atom AlexPosn AlexPosn]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_69 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_69 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_69 = Int#
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_0  Int#
17# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 a t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 [a] t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_69
happyReduction_69 :: HappyAbsSyn t18 t19 t20 [a] t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_69  =  [a] -> HappyAbsSyn t18 t19 t20 [a] t22 t23 t24 t25 t26 t27 t28 t29
forall t21 t18 t19 t20 t22 t23 t24 t25 t26 t27 t28 t29.
t21 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn21
		 ([]
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_70 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_70 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_70 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
18# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t23 t24 t25 t26 t27
       t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     (Declarations AlexPosn AlexPosn AlexPosn)
     t23
     t24
     t25
     t26
     t27
     t28
     t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     (Declarations AlexPosn AlexPosn AlexPosn)
     t23
     t24
     t25
     t26
     t27
     t28
     t29
happyReduction_70
happyReduction_70 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     (Declarations AlexPosn AlexPosn AlexPosn)
     t23
     t24
     t25
     t26
     t27
     t28
     t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     (Declarations AlexPosn AlexPosn AlexPosn)
     t23
     t24
     t25
     t26
     t27
     t28
     t29
happyReduction_70 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
-> Declarations AlexPosn AlexPosn AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t22
happyOut22 HappyAbsSyn
  t18
  t19
  t20
  t21
  (Declarations AlexPosn AlexPosn AlexPosn)
  t23
  t24
  t25
  t26
  t27
  t28
  t29
happy_x_1 of { Declarations AlexPosn AlexPosn AlexPosn
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap8
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap8
happyOut8 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap8 KempeDecl AlexPosn AlexPosn AlexPosn
happy_var_2) -> 
	Declarations AlexPosn AlexPosn AlexPosn
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     (Declarations AlexPosn AlexPosn AlexPosn)
     t23
     t24
     t25
     t26
     t27
     t28
     t29
forall t22 t18 t19 t20 t21 t23 t24 t25 t26 t27 t28 t29.
t22 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn22
		 (KempeDecl AlexPosn AlexPosn AlexPosn
happy_var_2 KempeDecl AlexPosn AlexPosn AlexPosn
-> Declarations AlexPosn AlexPosn AlexPosn
-> Declarations AlexPosn AlexPosn AlexPosn
forall k1. k1 -> [k1] -> [k1]
: Declarations AlexPosn AlexPosn AlexPosn
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_71 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_71 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_71 = Int#
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_0  Int#
18# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 a t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 [a] t23 t24 t25 t26 t27 t28 t29
happyReduction_71
happyReduction_71 :: HappyAbsSyn t18 t19 t20 t21 [a] t23 t24 t25 t26 t27 t28 t29
happyReduction_71  =  [a] -> HappyAbsSyn t18 t19 t20 t21 [a] t23 t24 t25 t26 t27 t28 t29
forall t22 t18 t19 t20 t21 t23 t24 t25 t26 t27 t28 t29.
t22 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn22
		 ([]
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_72 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_72 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_72 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
19# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t24 t25 t26 t27
       t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
happyReduction_72
happyReduction_72 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
happyReduction_72 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn
  t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
-> [ByteString]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t23
happyOut23 HappyAbsSyn
  t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
happy_x_1 of { [ByteString]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap6
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap6
happyOut6 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap6 ByteString
happy_var_2) -> 
	[ByteString]
-> HappyAbsSyn
     t18 t19 t20 t21 t22 [ByteString] t24 t25 t26 t27 t28 t29
forall t23 t18 t19 t20 t21 t22 t24 t25 t26 t27 t28 t29.
t23 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn23
		 (ByteString
happy_var_2 ByteString -> [ByteString] -> [ByteString]
forall k1. k1 -> [k1] -> [k1]
: [ByteString]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_73 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_73 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_73 = Int#
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_0  Int#
19# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 a t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 [a] t24 t25 t26 t27 t28 t29
happyReduction_73
happyReduction_73 :: HappyAbsSyn t18 t19 t20 t21 t22 [a] t24 t25 t26 t27 t28 t29
happyReduction_73  =  [a] -> HappyAbsSyn t18 t19 t20 t21 t22 [a] t24 t25 t26 t27 t28 t29
forall t23 t18 t19 t20 t21 t22 t24 t25 t26 t27 t28 t29.
t23 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn23
		 ([]
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_74 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_74 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_74 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
20# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t25 t26 t27
       t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happyReduction_74
happyReduction_74 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happyReduction_74 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
-> [KempeTy AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t24
happyOut24 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
happy_x_1 of { [KempeTy AlexPosn]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap10
happyOut10 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap10 KempeTy AlexPosn
happy_var_2) -> 
	[KempeTy AlexPosn]
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 [KempeTy AlexPosn] t25 t26 t27 t28 t29
forall t24 t18 t19 t20 t21 t22 t23 t25 t26 t27 t28 t29.
t24 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn24
		 (KempeTy AlexPosn
happy_var_2 KempeTy AlexPosn -> [KempeTy AlexPosn] -> [KempeTy AlexPosn]
forall k1. k1 -> [k1] -> [k1]
: [KempeTy AlexPosn]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_75 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_75 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_75 = Int#
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_0  Int#
20# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 a t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 [a] t25 t26 t27 t28 t29
happyReduction_75
happyReduction_75 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 [a] t25 t26 t27 t28 t29
happyReduction_75  =  [a] -> HappyAbsSyn t18 t19 t20 t21 t22 t23 [a] t25 t26 t27 t28 t29
forall t24 t18 t19 t20 t21 t22 t23 t25 t26 t27 t28 t29.
t24 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn24
		 ([]
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_76 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_76 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_76 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
21# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24 t26 t27
       t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happyReduction_76
happyReduction_76 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happyReduction_76 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
-> [Name AlexPosn]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t25
happyOut25 HappyAbsSyn
  t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
happy_x_1 of { [Name AlexPosn]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> Token AlexPosn
happyOutTok HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (TokName AlexPosn
_ Name AlexPosn
happy_var_2) -> 
	[Name AlexPosn]
-> HappyAbsSyn
     t18 t19 t20 t21 t22 t23 t24 [Name AlexPosn] t26 t27 t28 t29
forall t25 t18 t19 t20 t21 t22 t23 t24 t26 t27 t28 t29.
t25 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn25
		 (Name AlexPosn
happy_var_2 Name AlexPosn -> [Name AlexPosn] -> [Name AlexPosn]
forall k1. k1 -> [k1] -> [k1]
: [Name AlexPosn]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_77 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_77 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_77 = Int#
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_0  Int#
21# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 a t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 [a] t26 t27 t28 t29
happyReduction_77
happyReduction_77 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 [a] t26 t27 t28 t29
happyReduction_77  =  [a] -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 [a] t26 t27 t28 t29
forall t25 t18 t19 t20 t21 t22 t23 t24 t26 t27 t28 t29.
t25 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn25
		 ([]
	)

#if __GLASGOW_HASKELL__ >= 710
happyReduce_78 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_78 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_78 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
22# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall p t18 t19 t20 t26 t22 t23 t24 t25 t26 t27 t28 t29 p t18 t19
       t20 t21 t22 t23 t24 t25 t27 t28 t29.
p
-> HappyAbsSyn t18 t19 t20 t26 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_78
happyReduction_78 :: p
-> HappyAbsSyn t18 t19 t20 t26 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyReduction_78 p
happy_x_3
	HappyAbsSyn t18 t19 t20 t26 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	p
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t26 t22 t23 t24 t25 t26 t27 t28 t29 -> t26
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t21
happyOut21 HappyAbsSyn t18 t19 t20 t26 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { t26
happy_var_2 -> 
	t26 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
forall t26 t18 t19 t20 t21 t22 t23 t24 t25 t27 t28 t29.
t26 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn26
		 (t26
happy_var_2
	)}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_79 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_79 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_79 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
23# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 p t18 t19
       t20 t21 t22 t23 t24 t25 t26 t28 t29 t18 t19 t20 t21 t22 t23 t24 t25
       t26 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
happyReduction_79
happyReduction_79 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
happyReduction_79 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3
	p
happy_x_2
	HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t28
  t29
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t28
  t29
-> [(Name AlexPosn, [KempeTy AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t27
happyOut27 HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  [(Name AlexPosn, [KempeTy AlexPosn])]
  t28
  t29
happy_x_1 of { [(Name AlexPosn, [KempeTy AlexPosn])]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
happyOut17 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3 of { (HappyWrap17 (Name AlexPosn, [KempeTy AlexPosn])
happy_var_3) -> 
	[(Name AlexPosn, [KempeTy AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
forall t27 t18 t19 t20 t21 t22 t23 t24 t25 t26 t28 t29.
t27 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn27
		 ((Name AlexPosn, [KempeTy AlexPosn])
happy_var_3 (Name AlexPosn, [KempeTy AlexPosn])
-> [(Name AlexPosn, [KempeTy AlexPosn])]
-> [(Name AlexPosn, [KempeTy AlexPosn])]
forall k1. k1 -> [k1] -> [k1]
: [(Name AlexPosn, [KempeTy AlexPosn])]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_80 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_80 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_80 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_3  Int#
23# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 p t18 t19
       t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20 t21 t22 t23 t24
       t25 t26 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
happyReduction_80
happyReduction_80 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> p
-> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
happyReduction_80 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3
	p
happy_x_2
	HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1
	 =  case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
happyOut17 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_1 of { (HappyWrap17 (Name AlexPosn, [KempeTy AlexPosn])
happy_var_1) -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap17
happyOut17 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_3 of { (HappyWrap17 (Name AlexPosn, [KempeTy AlexPosn])
happy_var_3) -> 
	[(Name AlexPosn, [KempeTy AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     [(Name AlexPosn, [KempeTy AlexPosn])]
     t28
     t29
forall t27 t18 t19 t20 t21 t22 t23 t24 t25 t26 t28 t29.
t27 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn27
		 ((Name AlexPosn, [KempeTy AlexPosn])
happy_var_3 (Name AlexPosn, [KempeTy AlexPosn])
-> [(Name AlexPosn, [KempeTy AlexPosn])]
-> [(Name AlexPosn, [KempeTy AlexPosn])]
forall k1. k1 -> [k1] -> [k1]
: [(Name AlexPosn, [KempeTy AlexPosn])
happy_var_1]
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_81 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_81 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_81 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
24# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t18 t19 t20 t21 t22 t23 t24 t25 t26
       t27 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29
happyReduction_81
happyReduction_81 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29
happyReduction_81 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t29
happyOut29 HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_x_1 of { [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap15
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap15
happyOut15 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap15 (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
happy_var_2) -> 
	NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     t29
forall t28 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t29.
t28 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn28
		 ((Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
happy_var_2 (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
forall a. a -> [a] -> NonEmpty a
:| [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_82 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_82 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_82 = Int#
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> HappyAbsSyn
         (Name AlexPosn, [KempeTy AlexPosn])
         [(Name AlexPosn, [KempeTy AlexPosn])]
         [Atom AlexPosn AlexPosn]
         [Atom AlexPosn AlexPosn]
         (Declarations AlexPosn AlexPosn AlexPosn)
         [ByteString]
         [KempeTy AlexPosn]
         [Name AlexPosn]
         [Atom AlexPosn AlexPosn]
         [(Name AlexPosn, [KempeTy AlexPosn])]
         (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
         [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_2  Int#
25# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t18 t19 t20
       t21 t22 t23 t24 t25 t26 t27 t28 t18 t19 t20 t21 t22 t23 t24 t25 t26
       t27 t28.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happyReduction_82
happyReduction_82 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happyReduction_82 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2
	HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_x_1
	 =  case HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 -> t29
happyOut29 HappyAbsSyn
  t18
  t19
  t20
  t21
  t22
  t23
  t24
  t25
  t26
  t27
  t28
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_x_1 of { [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_var_1 -> 
	case HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap15
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap15
happyOut15 HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happy_x_2 of { (HappyWrap15 (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
happy_var_2) -> 
	[(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyAbsSyn
     t18
     t19
     t20
     t21
     t22
     t23
     t24
     t25
     t26
     t27
     t28
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t29 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28.
t29 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn29
		 ((Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
happy_var_2 (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])
-> [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall k1. k1 -> [k1] -> [k1]
: [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
happy_var_1
	)}}

#if __GLASGOW_HASKELL__ >= 710
happyReduce_83 :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)
#endif
happyReduce_83 :: Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyReduce_83 = Int#
-> HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happySpecReduce_0  Int#
25# HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 a.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 [a]
happyReduction_83
happyReduction_83 :: HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 [a]
happyReduction_83  =  [a] -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 [a]
forall t29 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28.
t29 -> HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
happyIn29
		 ([]
	)

happyNewToken :: Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyNewToken Int#
action Happy_IntList
sts HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
stk
	= Alex (Token AlexPosn)
-> ExceptT (ParseError AlexPosn) Alex (Token AlexPosn)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Alex (Token AlexPosn)
alexMonadScan ExceptT (ParseError AlexPosn) Alex (Token AlexPosn)
-> (Token AlexPosn
    -> Parse
         (HappyAbsSyn
            (Name AlexPosn, [KempeTy AlexPosn])
            [(Name AlexPosn, [KempeTy AlexPosn])]
            [Atom AlexPosn AlexPosn]
            [Atom AlexPosn AlexPosn]
            (Declarations AlexPosn AlexPosn AlexPosn)
            [ByteString]
            [KempeTy AlexPosn]
            [Name AlexPosn]
            [Atom AlexPosn AlexPosn]
            [(Name AlexPosn, [KempeTy AlexPosn])]
            (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
            [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]))
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=(\Token AlexPosn
tk -> 
	let cont :: Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
i = Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyDoAction Int#
i Token AlexPosn
tk Int#
action Happy_IntList
sts HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
stk in
	case Token AlexPosn
tk of {
	EOF AlexPosn
_ -> Int#
-> Token AlexPosn
-> Int#
-> Happy_IntList
-> HappyStk
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyDoAction Int#
62# Token AlexPosn
tk Int#
action Happy_IntList
sts HappyStk
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
stk;
	TokSym AlexPosn
happy_dollar_dollar Sym
Arrow -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
1#;
	TokSym AlexPosn
happy_dollar_dollar Sym
DefEq -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
2#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Colon -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
3#;
	TokSym AlexPosn
happy_dollar_dollar Sym
LBrace -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
4#;
	TokSym AlexPosn
happy_dollar_dollar Sym
RBrace -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
5#;
	TokSym AlexPosn
happy_dollar_dollar Sym
LSqBracket -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
6#;
	TokSym AlexPosn
happy_dollar_dollar Sym
RSqBracket -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
7#;
	TokSym AlexPosn
happy_dollar_dollar Sym
LParen -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
8#;
	TokSym AlexPosn
happy_dollar_dollar Sym
RParen -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
9#;
	TokSym AlexPosn
happy_dollar_dollar Sym
VBar -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
10#;
	TokSym AlexPosn
happy_dollar_dollar Sym
CaseArr -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
11#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Comma -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
12#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Underscore -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
13#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Plus -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
14#;
	TokSym AlexPosn
happy_dollar_dollar Sym
PlusU -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
15#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Minus -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
16#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Times -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
17#;
	TokSym AlexPosn
happy_dollar_dollar Sym
TimesU -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
18#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Div -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
19#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Percent -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
20#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Eq -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
21#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Neq -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
22#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Leq -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
23#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Lt -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
24#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Geq -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
25#;
	TokSym AlexPosn
happy_dollar_dollar Sym
Gt -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
26#;
	TokSym AlexPosn
happy_dollar_dollar Sym
ShiftRU -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
27#;
	TokSym AlexPosn
happy_dollar_dollar Sym
ShiftLU -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
28#;
	TokSym AlexPosn
happy_dollar_dollar Sym
ShiftR -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
29#;
	TokSym AlexPosn
happy_dollar_dollar Sym
ShiftL -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
30#;
	TokSym AlexPosn
happy_dollar_dollar Sym
NegTok -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
31#;
	TokSym AlexPosn
happy_dollar_dollar Sym
AndTok -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
32#;
	TokSym AlexPosn
happy_dollar_dollar Sym
OrTok -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
33#;
	TokName AlexPosn
_ Name AlexPosn
happy_dollar_dollar -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
34#;
	TokTyName  AlexPosn
_ Name AlexPosn
happy_dollar_dollar -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
35#;
	TokForeign AlexPosn
_ ByteString
happy_dollar_dollar -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
36#;
	TokModuleStr AlexPosn
_ ByteString
happy_dollar_dollar -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
37#;
	happy_dollar_dollar :: Token AlexPosn
happy_dollar_dollar@(TokInt AlexPosn
_ Integer
_) -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
38#;
	happy_dollar_dollar :: Token AlexPosn
happy_dollar_dollar@(TokWord AlexPosn
_ Natural
_) -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
39#;
	happy_dollar_dollar :: Token AlexPosn
happy_dollar_dollar@(TokInt8 AlexPosn
_ Int8
_) -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
40#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwType -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
41#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwCase -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
42#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwCfun -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
43#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwIf -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
44#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwForeign -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
45#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwCabi -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
46#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwKabi -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
47#;
	TokKeyword AlexPosn
happy_dollar_dollar Keyword
KwImport -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
48#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinDip -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
49#;
	happy_dollar_dollar :: Token AlexPosn
happy_dollar_dollar@(TokBuiltin AlexPosn
_ (BuiltinBoolLit Bool
_)) -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
50#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinBool -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
51#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinInt -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
52#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinInt8 -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
53#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinWord -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
54#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinDup -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
55#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinSwap -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
56#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinDrop -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
57#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinIntXor -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
58#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinWordXor -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
59#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinBoolXor -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
60#;
	TokBuiltin AlexPosn
happy_dollar_dollar Builtin
BuiltinPopcount -> Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
cont Int#
61#;
	Token AlexPosn
_ -> (Token AlexPosn, [String])
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
forall a. (Token AlexPosn, [String]) -> Parse a
happyError' (Token AlexPosn
tk, [])
	})

happyError_ :: [String] -> Int# -> Token AlexPosn -> Parse a
happyError_ [String]
explist Int#
62# Token AlexPosn
tk = (Token AlexPosn, [String]) -> Parse a
forall a. (Token AlexPosn, [String]) -> Parse a
happyError' (Token AlexPosn
tk, [String]
explist)
happyError_ [String]
explist Int#
_ Token AlexPosn
tk = (Token AlexPosn, [String]) -> Parse a
forall a. (Token AlexPosn, [String]) -> Parse a
happyError' (Token AlexPosn
tk, [String]
explist)

happyThen :: () => Parse a -> (a -> Parse b) -> Parse b
happyThen :: Parse a -> (a -> Parse b) -> Parse b
happyThen = (Parse a -> (a -> Parse b) -> Parse b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(>>=))
happyReturn :: () => a -> Parse a
happyReturn :: a -> Parse a
happyReturn = (a -> Parse a
forall (f :: * -> *) a. Applicative f => a -> f a
pure)
#if __GLASGOW_HASKELL__ >= 710
happyParse :: () => Happy_GHC_Exts.Int# -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)

happyNewToken :: () => Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)

happyDoAction :: () => Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _)

happyReduceArr :: () => Happy_Data_Array.Array Prelude.Int (Happy_GHC_Exts.Int# -> Token AlexPosn -> Happy_GHC_Exts.Int# -> Happy_IntList -> HappyStk (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _) -> Parse (HappyAbsSyn _ _ _ _ _ _ _ _ _ _ _ _))

#endif
happyThen1 :: () => Parse a -> (a -> Parse b) -> Parse b
happyThen1 :: Parse a -> (a -> Parse b) -> Parse b
happyThen1 = Parse a -> (a -> Parse b) -> Parse b
forall a b. Parse a -> (a -> Parse b) -> Parse b
happyThen
happyReturn1 :: () => a -> Parse a
happyReturn1 :: a -> Parse a
happyReturn1 = a -> Parse a
forall a. a -> Parse a
happyReturn
happyError' :: () => ((Token AlexPosn), [Prelude.String]) -> Parse a
happyError' :: (Token AlexPosn, [String]) -> Parse a
happyError' (Token AlexPosn, [String])
tk = (\(Token AlexPosn
tokens, [String]
_) -> Token AlexPosn -> Parse a
forall a. Token AlexPosn -> Parse a
parseError Token AlexPosn
tokens) (Token AlexPosn, [String])
tk
parseModule :: Parse (Module AlexPosn AlexPosn AlexPosn)
parseModule = Parse (Module AlexPosn AlexPosn AlexPosn)
happySomeParser where
 happySomeParser :: Parse (Module AlexPosn AlexPosn AlexPosn)
happySomeParser = Parse
  (HappyAbsSyn
     (Name AlexPosn, [KempeTy AlexPosn])
     [(Name AlexPosn, [KempeTy AlexPosn])]
     [Atom AlexPosn AlexPosn]
     [Atom AlexPosn AlexPosn]
     (Declarations AlexPosn AlexPosn AlexPosn)
     [ByteString]
     [KempeTy AlexPosn]
     [Name AlexPosn]
     [Atom AlexPosn AlexPosn]
     [(Name AlexPosn, [KempeTy AlexPosn])]
     (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
     [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
-> (HappyAbsSyn
      (Name AlexPosn, [KempeTy AlexPosn])
      [(Name AlexPosn, [KempeTy AlexPosn])]
      [Atom AlexPosn AlexPosn]
      [Atom AlexPosn AlexPosn]
      (Declarations AlexPosn AlexPosn AlexPosn)
      [ByteString]
      [KempeTy AlexPosn]
      [Name AlexPosn]
      [Atom AlexPosn AlexPosn]
      [(Name AlexPosn, [KempeTy AlexPosn])]
      (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
      [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
    -> Parse (Module AlexPosn AlexPosn AlexPosn))
-> Parse (Module AlexPosn AlexPosn AlexPosn)
forall a b. Parse a -> (a -> Parse b) -> Parse b
happyThen (Int#
-> Parse
     (HappyAbsSyn
        (Name AlexPosn, [KempeTy AlexPosn])
        [(Name AlexPosn, [KempeTy AlexPosn])]
        [Atom AlexPosn AlexPosn]
        [Atom AlexPosn AlexPosn]
        (Declarations AlexPosn AlexPosn AlexPosn)
        [ByteString]
        [KempeTy AlexPosn]
        [Name AlexPosn]
        [Atom AlexPosn AlexPosn]
        [(Name AlexPosn, [KempeTy AlexPosn])]
        (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
        [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])])
happyParse Int#
0#) (\HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
x -> Module AlexPosn AlexPosn AlexPosn
-> Parse (Module AlexPosn AlexPosn AlexPosn)
forall a. a -> Parse a
happyReturn (let {(HappyWrap4 Module AlexPosn AlexPosn AlexPosn
x') = HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
-> HappyWrap4
forall t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29.
HappyAbsSyn t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29
-> HappyWrap4
happyOut4 HappyAbsSyn
  (Name AlexPosn, [KempeTy AlexPosn])
  [(Name AlexPosn, [KempeTy AlexPosn])]
  [Atom AlexPosn AlexPosn]
  [Atom AlexPosn AlexPosn]
  (Declarations AlexPosn AlexPosn AlexPosn)
  [ByteString]
  [KempeTy AlexPosn]
  [Name AlexPosn]
  [Atom AlexPosn AlexPosn]
  [(Name AlexPosn, [KempeTy AlexPosn])]
  (NonEmpty (Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn]))
  [(Pattern AlexPosn AlexPosn, [Atom AlexPosn AlexPosn])]
x} in Module AlexPosn AlexPosn AlexPosn
x'))

happySeq :: a -> b -> b
happySeq = a -> b -> b
forall a b. a -> b -> b
happyDoSeq


parseError :: Token AlexPosn -> Parse a
parseError :: Token AlexPosn -> Parse a
parseError = ParseError AlexPosn -> Parse a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (ParseError AlexPosn -> Parse a)
-> (Token AlexPosn -> ParseError AlexPosn)
-> Token AlexPosn
-> Parse a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Token AlexPosn -> ParseError AlexPosn
forall a. Token a -> ParseError a
Unexpected

data ParseError a = Unexpected (Token a)
                  | LexErr String
                  | NoImpl (Name a)
                  deriving ((forall x. ParseError a -> Rep (ParseError a) x)
-> (forall x. Rep (ParseError a) x -> ParseError a)
-> Generic (ParseError a)
forall x. Rep (ParseError a) x -> ParseError a
forall x. ParseError a -> Rep (ParseError a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ParseError a) x -> ParseError a
forall a x. ParseError a -> Rep (ParseError a) x
$cto :: forall a x. Rep (ParseError a) x -> ParseError a
$cfrom :: forall a x. ParseError a -> Rep (ParseError a) x
Generic, ParseError a -> ()
(ParseError a -> ()) -> NFData (ParseError a)
forall a. NFData a => ParseError a -> ()
forall a. (a -> ()) -> NFData a
rnf :: ParseError a -> ()
$crnf :: forall a. NFData a => ParseError a -> ()
NFData)

instance Pretty a => Pretty (ParseError a) where
    pretty :: ParseError a -> Doc ann
pretty (Unexpected Token a
tok)  = a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Token a -> a
forall a. Token a -> a
loc Token a
tok) Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"Unexpected" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Token a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Token a
tok
    pretty (LexErr String
str)      = Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Text
T.pack String
str)
    pretty (NoImpl Name a
n)        = a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Name a -> a
forall a. Name a -> a
Name.loc Name a
n) Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"Signature for" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Name a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Name a
n Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"is not accompanied by an implementation"

instance Pretty a => Show (ParseError a) where
    show :: ParseError a -> String
show = Doc Any -> String
forall a. Show a => a -> String
show (Doc Any -> String)
-> (ParseError a -> Doc Any) -> ParseError a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseError a -> Doc Any
forall a ann. Pretty a => a -> Doc ann
pretty

instance (Pretty a, Typeable a) => Exception (ParseError a)

type Parse = ExceptT (ParseError AlexPosn) Alex

parse :: BSL.ByteString -> Either (ParseError AlexPosn) (Module AlexPosn AlexPosn AlexPosn)
parse :: ByteString
-> Either (ParseError AlexPosn) (Module AlexPosn AlexPosn AlexPosn)
parse = ((Int, Module AlexPosn AlexPosn AlexPosn)
 -> Module AlexPosn AlexPosn AlexPosn)
-> Either
     (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
-> Either (ParseError AlexPosn) (Module AlexPosn AlexPosn AlexPosn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Module AlexPosn AlexPosn AlexPosn)
-> Module AlexPosn AlexPosn AlexPosn
forall a b. (a, b) -> b
snd (Either
   (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
 -> Either
      (ParseError AlexPosn) (Module AlexPosn AlexPosn AlexPosn))
-> (ByteString
    -> Either
         (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn))
-> ByteString
-> Either (ParseError AlexPosn) (Module AlexPosn AlexPosn AlexPosn)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString
-> Either
     (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
parseWithMax

parseWithMax :: BSL.ByteString -> Either (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
parseWithMax :: ByteString
-> Either
     (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
parseWithMax = (((Int, Map Text Int, IntMap (Name AlexPosn)),
  Module AlexPosn AlexPosn AlexPosn)
 -> (Int, Module AlexPosn AlexPosn AlexPosn))
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Module AlexPosn AlexPosn AlexPosn)
-> Either
     (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Int, Map Text Int, IntMap (Name AlexPosn)) -> Int)
-> ((Int, Map Text Int, IntMap (Name AlexPosn)),
    Module AlexPosn AlexPosn AlexPosn)
-> (Int, Module AlexPosn AlexPosn AlexPosn)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Int, Map Text Int, IntMap (Name AlexPosn)) -> Int
forall a b c. (a, b, c) -> a
fst3) (Either
   (ParseError AlexPosn)
   ((Int, Map Text Int, IntMap (Name AlexPosn)),
    Module AlexPosn AlexPosn AlexPosn)
 -> Either
      (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn))
-> (ByteString
    -> Either
         (ParseError AlexPosn)
         ((Int, Map Text Int, IntMap (Name AlexPosn)),
          Module AlexPosn AlexPosn AlexPosn))
-> ByteString
-> Either
     (ParseError AlexPosn) (Int, Module AlexPosn AlexPosn AlexPosn)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Module AlexPosn AlexPosn AlexPosn)
parseWithInitCtx

parseWithInitCtx :: BSL.ByteString -> Either (ParseError AlexPosn) (AlexUserState, Module AlexPosn AlexPosn AlexPosn)
parseWithInitCtx :: ByteString
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Module AlexPosn AlexPosn AlexPosn)
parseWithInitCtx ByteString
bsl = ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Module AlexPosn AlexPosn AlexPosn)
parseWithCtx ByteString
bsl (Int, Map Text Int, IntMap (Name AlexPosn))
alexInitUserState

parseWithCtx :: BSL.ByteString -> AlexUserState -> Either (ParseError AlexPosn) (AlexUserState, Module AlexPosn AlexPosn AlexPosn)
parseWithCtx :: ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Module AlexPosn AlexPosn AlexPosn)
parseWithCtx = Parse (Module AlexPosn AlexPosn AlexPosn)
-> ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Module AlexPosn AlexPosn AlexPosn)
forall a.
Parse a
-> ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
parseWithInitSt Parse (Module AlexPosn AlexPosn AlexPosn)
parseModule

runParse :: Parse a -> BSL.ByteString -> Either (ParseError AlexPosn) (AlexUserState, a)
runParse :: Parse a
-> ByteString
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
runParse Parse a
parser ByteString
str = Either
  String
  ((Int, Map Text Int, IntMap (Name AlexPosn)),
   Either (ParseError AlexPosn) a)
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
forall b a c.
Either String (b, Either (ParseError a) c)
-> Either (ParseError a) (b, c)
liftErr (Either
   String
   ((Int, Map Text Int, IntMap (Name AlexPosn)),
    Either (ParseError AlexPosn) a)
 -> Either
      (ParseError AlexPosn)
      ((Int, Map Text Int, IntMap (Name AlexPosn)), a))
-> Either
     String
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Either (ParseError AlexPosn) a)
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
forall a b. (a -> b) -> a -> b
$ ByteString
-> Alex (Either (ParseError AlexPosn) a)
-> Either
     String
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Either (ParseError AlexPosn) a)
forall a.
ByteString
-> Alex a
-> Either String ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
runAlexSt ByteString
str (Parse a -> Alex (Either (ParseError AlexPosn) a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT Parse a
parser)

parseWithInitSt :: Parse a -> BSL.ByteString -> AlexUserState -> Either (ParseError AlexPosn) (AlexUserState, a)
parseWithInitSt :: Parse a
-> ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
parseWithInitSt Parse a
parser ByteString
str (Int, Map Text Int, IntMap (Name AlexPosn))
st = Either
  String
  ((Int, Map Text Int, IntMap (Name AlexPosn)),
   Either (ParseError AlexPosn) a)
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
forall b a c.
Either String (b, Either (ParseError a) c)
-> Either (ParseError a) (b, c)
liftErr (Either
   String
   ((Int, Map Text Int, IntMap (Name AlexPosn)),
    Either (ParseError AlexPosn) a)
 -> Either
      (ParseError AlexPosn)
      ((Int, Map Text Int, IntMap (Name AlexPosn)), a))
-> Either
     String
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Either (ParseError AlexPosn) a)
-> Either
     (ParseError AlexPosn)
     ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
forall a b. (a -> b) -> a -> b
$ ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Alex (Either (ParseError AlexPosn) a)
-> Either
     String
     ((Int, Map Text Int, IntMap (Name AlexPosn)),
      Either (ParseError AlexPosn) a)
forall a.
ByteString
-> (Int, Map Text Int, IntMap (Name AlexPosn))
-> Alex a
-> Either String ((Int, Map Text Int, IntMap (Name AlexPosn)), a)
withAlexSt ByteString
str (Int, Map Text Int, IntMap (Name AlexPosn))
st (Parse a -> Alex (Either (ParseError AlexPosn) a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT Parse a
parser)
    where liftErr :: Either String (a, Either (ParseError a) b)
-> Either (ParseError a) (a, b)
liftErr (Left String
err)            = ParseError a -> Either (ParseError a) (a, b)
forall a b. a -> Either a b
Left (String -> ParseError a
forall a. String -> ParseError a
LexErr String
err)
          liftErr (Right (a
_, Left ParseError a
err)) = ParseError a -> Either (ParseError a) (a, b)
forall a b. a -> Either a b
Left ParseError a
err
          liftErr (Right (a
i, Right b
x))  = (a, b) -> Either (ParseError a) (a, b)
forall a b. b -> Either a b
Right (a
i, b
x)

liftErr :: Either String (b, Either (ParseError a) c) -> Either (ParseError a) (b, c)
liftErr :: Either String (b, Either (ParseError a) c)
-> Either (ParseError a) (b, c)
liftErr (Left String
err)            = ParseError a -> Either (ParseError a) (b, c)
forall a b. a -> Either a b
Left (String -> ParseError a
forall a. String -> ParseError a
LexErr String
err)
liftErr (Right (b
_, Left ParseError a
err)) = ParseError a -> Either (ParseError a) (b, c)
forall a b. a -> Either a b
Left ParseError a
err
liftErr (Right (b
i, Right c
x))  = (b, c) -> Either (ParseError a) (b, c)
forall a b. b -> Either a b
Right (b
i, c
x)

uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 a -> b -> c -> d -> e
f ~(a
x, b
y, c
z, d
w) = a -> b -> c -> d -> e
f a
x b
y c
z d
w
{-# LINE 1 "templates/GenericTemplate.hs" #-}
-- $Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp $













-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#if __GLASGOW_HASKELL__ > 706
#define LT(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# m)) :: Prelude.Bool)
#define GTE(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.>=# m)) :: Prelude.Bool)
#define EQ(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.==# m)) :: Prelude.Bool)
#else
#define LT(n,m) (n Happy_GHC_Exts.<# m)
#define GTE(n,m) (n Happy_GHC_Exts.>=# m)
#define EQ(n,m) (n Happy_GHC_Exts.==# m)
#endif



















data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList








































infixr 9 `HappyStk`
data HappyStk a = HappyStk a (HappyStk a)

-----------------------------------------------------------------------------
-- starting the parse

happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll

-----------------------------------------------------------------------------
-- Accepting the parse

-- If the current token is ERROR_TOK, it means we've just accepted a partial
-- parse (a %partial parser).  We must ignore the saved token on the top of
-- the stack in this case.
happyAccept 0# tk st sts (_ `HappyStk` ans `HappyStk` _) =
        happyReturn1 ans
happyAccept j tk st sts (HappyStk ans _) = 
        (happyTcHack j (happyTcHack st)) (happyReturn1 ans)

-----------------------------------------------------------------------------
-- Arrays only: do the next action



happyDoAction i tk st
        = {- nothing -}
          case action of
                0#           -> {- nothing -}
                                     happyFail (happyExpListPerState ((Happy_GHC_Exts.I# (st)) :: Prelude.Int)) i tk st
                -1#          -> {- nothing -}
                                     happyAccept i tk st
                n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -}
                                                   (happyReduceArr Happy_Data_Array.! rule) i tk st
                                                   where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#))))))
                n                 -> {- nothing -}
                                     happyShift new_state i tk st
                                     where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#))
   where off    = happyAdjustOffset (indexShortOffAddr happyActOffsets st)
         off_i  = (off Happy_GHC_Exts.+# i)
         check  = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#))
                  then EQ(indexShortOffAddr happyCheck off_i, i)
                  else Prelude.False
         action
          | check     = indexShortOffAddr happyTable off_i
          | Prelude.otherwise = indexShortOffAddr happyDefActions st




indexShortOffAddr (HappyA# arr) off =
        Happy_GHC_Exts.narrow16Int# i
  where
        i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low)
        high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#)))
        low  = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off'))
        off' = off Happy_GHC_Exts.*# 2#




{-# INLINE happyLt #-}
happyLt x y = LT(x,y)


readArrayBit arr bit =
    Bits.testBit (Happy_GHC_Exts.I# (indexShortOffAddr arr ((unbox_int bit) `Happy_GHC_Exts.iShiftRA#` 4#))) (bit `Prelude.mod` 16)
  where unbox_int (Happy_GHC_Exts.I# x) = x






data HappyAddr = HappyA# Happy_GHC_Exts.Addr#


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













-----------------------------------------------------------------------------
-- Shifting a token

happyShift new_state 0# tk st sts stk@(x `HappyStk` _) =
     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
--     trace "shifting the error token" $
     happyDoAction i tk new_state (HappyCons (st) (sts)) (stk)

happyShift new_state i tk st sts stk =
     happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk)

-- happyReduce is specialised for the common cases.

happySpecReduce_0 i fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happySpecReduce_0 nt fn j tk st@((action)) sts stk
     = happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk)

happySpecReduce_1 i fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk')
     = let r = fn v1 in
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))

happySpecReduce_2 i fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk')
     = let r = fn v1 v2 in
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))

happySpecReduce_3 i fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk')
     = let r = fn v1 v2 v3 in
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))

happyReduce k i fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happyReduce k nt fn j tk st sts stk
     = case happyDrop (k Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) sts of
         sts1@((HappyCons (st1@(action)) (_))) ->
                let r = fn stk in  -- it doesn't hurt to always seq here...
                happyDoSeq r (happyGoto nt j tk st1 sts1 r)

happyMonadReduce k nt fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happyMonadReduce k nt fn j tk st sts stk =
      case happyDrop k (HappyCons (st) (sts)) of
        sts1@((HappyCons (st1@(action)) (_))) ->
          let drop_stk = happyDropStk k stk in
          happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk))

happyMonad2Reduce k nt fn 0# tk st sts stk
     = happyFail [] 0# tk st sts stk
happyMonad2Reduce k nt fn j tk st sts stk =
      case happyDrop k (HappyCons (st) (sts)) of
        sts1@((HappyCons (st1@(action)) (_))) ->
         let drop_stk = happyDropStk k stk

             off = happyAdjustOffset (indexShortOffAddr happyGotoOffsets st1)
             off_i = (off Happy_GHC_Exts.+# nt)
             new_state = indexShortOffAddr happyTable off_i




          in
          happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))

happyDrop 0# l = l
happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t

happyDropStk 0# l = l
happyDropStk n (x `HappyStk` xs) = happyDropStk (n Happy_GHC_Exts.-# (1#::Happy_GHC_Exts.Int#)) xs

-----------------------------------------------------------------------------
-- Moving to a new state after a reduction


happyGoto nt j tk st = 
   {- nothing -}
   happyDoAction j tk new_state
   where off = happyAdjustOffset (indexShortOffAddr happyGotoOffsets st)
         off_i = (off Happy_GHC_Exts.+# nt)
         new_state = indexShortOffAddr happyTable off_i




-----------------------------------------------------------------------------
-- Error recovery (ERROR_TOK is the error token)

-- parse error if we are in recovery and we fail again
happyFail explist 0# tk old_st _ stk@(x `HappyStk` _) =
     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
--      trace "failing" $ 
        happyError_ explist i tk

{-  We don't need state discarding for our restricted implementation of
    "error".  In fact, it can cause some bogus parses, so I've disabled it
    for now --SDM

-- discard a state
happyFail  ERROR_TOK tk old_st CONS(HAPPYSTATE(action),sts) 
                                                (saved_tok `HappyStk` _ `HappyStk` stk) =
--      trace ("discarding state, depth " ++ show (length stk))  $
        DO_ACTION(action,ERROR_TOK,tk,sts,(saved_tok`HappyStk`stk))
-}

-- Enter error recovery: generate an error token,
--                       save the old token and carry on.
happyFail explist i tk (action) sts stk =
--      trace "entering error recovery" $
        happyDoAction 0# tk action sts ((Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk)

-- Internal happy errors:

notHappyAtAll :: a
notHappyAtAll = Prelude.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 `Prelude.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.