{-# OPTIONS_GHC -w #-}
{-# OPTIONS -XMagicHash -XBangPatterns -XTypeSynonymInstances -XFlexibleInstances -cpp #-}
#if __GLASGOW_HASKELL__ >= 710
{-# OPTIONS_GHC -XPartialTypeSignatures #-}
#endif
module Language.Lua.Annotated.Parser
  ( parseTokens
  , parseText
  , parseNamedText
  , parseFile
  , Parser
  , chunk
  , exp
  , stat
  , SourcePos(..)
  , SourceRange(..)
  ) where

import           Control.Monad (liftM,ap)
import           Prelude hiding (LT,GT,EQ,exp)
import           Data.Maybe(fromMaybe)
import           Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text

import           Language.Lua.Token (Token(..))
import           Language.Lua.Annotated.Lexer
                    (SourcePos(..), SourceRange(..), Lexeme(..), llexNamed)
import           Language.Lua.Annotated.Syntax
import qualified AlexTools
import qualified Data.Array as Happy_Data_Array
import qualified Data.Bits as Bits
import qualified GHC.Exts as Happy_GHC_Exts
import Control.Applicative(Applicative(..))
import Control.Monad (ap)

-- parser produced by Happy Version 1.19.9

newtype HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 = HappyAbsSyn HappyAny
#if __GLASGOW_HASKELL__ >= 607
type HappyAny = Happy_GHC_Exts.Any
#else
type HappyAny = forall a . a
#endif
happyIn6 :: (Block SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn6 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn6 #-}
happyOut6 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Block SourceRange)
happyOut6 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut6 #-}
happyIn7 :: ([Exp SourceRange]) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn7 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn7 #-}
happyOut7 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> ([Exp SourceRange])
happyOut7 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut7 #-}
happyIn8 :: (Stat SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn8 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn8 #-}
happyOut8 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Stat SourceRange)
happyOut8 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut8 #-}
happyIn9 :: t9 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn9 #-}
happyOut9 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t9
happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut9 #-}
happyIn10 :: t10 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn10 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn10 #-}
happyOut10 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t10
happyOut10 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut10 #-}
happyIn11 :: t11 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn11 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn11 #-}
happyOut11 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t11
happyOut11 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut11 #-}
happyIn12 :: t12 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn12 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn12 #-}
happyOut12 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t12
happyOut12 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut12 #-}
happyIn13 :: t13 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn13 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn13 #-}
happyOut13 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t13
happyOut13 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut13 #-}
happyIn14 :: t14 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn14 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn14 #-}
happyOut14 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t14
happyOut14 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut14 #-}
happyIn15 :: t15 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn15 #-}
happyOut15 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t15
happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut15 #-}
happyIn16 :: (PrefixExp SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn16 #-}
happyOut16 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (PrefixExp SourceRange)
happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut16 #-}
happyIn17 :: (FunCall SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn17 #-}
happyOut17 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (FunCall SourceRange)
happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut17 #-}
happyIn18 :: (FunName SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn18 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn18 #-}
happyOut18 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (FunName SourceRange)
happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut18 #-}
happyIn19 :: t19 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn19 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn19 #-}
happyOut19 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t19
happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut19 #-}
happyIn20 :: t20 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn20 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn20 #-}
happyOut20 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t20
happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut20 #-}
happyIn21 :: (Var SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn21 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn21 #-}
happyOut21 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Var SourceRange)
happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut21 #-}
happyIn22 :: (Exp SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn22 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn22 #-}
happyOut22 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Exp SourceRange)
happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut22 #-}
happyIn23 :: (FunArg SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn23 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn23 #-}
happyOut23 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (FunArg SourceRange)
happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut23 #-}
happyIn24 :: (FunDef SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn24 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn24 #-}
happyOut24 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (FunDef SourceRange)
happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut24 #-}
happyIn25 :: (FunBody SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn25 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn25 #-}
happyOut25 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (FunBody SourceRange)
happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut25 #-}
happyIn26 :: (([Name SourceRange],Maybe SourceRange)) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn26 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn26 #-}
happyOut26 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (([Name SourceRange],Maybe SourceRange))
happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut26 #-}
happyIn27 :: ([Name SourceRange]) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn27 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn27 #-}
happyOut27 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> ([Name SourceRange])
happyOut27 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut27 #-}
happyIn28 :: (Table SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn28 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn28 #-}
happyOut28 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Table SourceRange)
happyOut28 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut28 #-}
happyIn29 :: ([TableField SourceRange]) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn29 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn29 #-}
happyOut29 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> ([TableField SourceRange])
happyOut29 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut29 #-}
happyIn30 :: (Lexeme Token) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn30 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn30 #-}
happyOut30 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Lexeme Token)
happyOut30 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut30 #-}
happyIn31 :: (TableField SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn31 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn31 #-}
happyOut31 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (TableField SourceRange)
happyOut31 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut31 #-}
happyIn32 :: (Name SourceRange) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn32 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn32 #-}
happyOut32 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Name SourceRange)
happyOut32 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut32 #-}
happyIn33 :: t33 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn33 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn33 #-}
happyOut33 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t33
happyOut33 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut33 #-}
happyIn34 :: t34 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn34 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn34 #-}
happyOut34 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t34
happyOut34 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut34 #-}
happyIn35 :: t35 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn35 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn35 #-}
happyOut35 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t35
happyOut35 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut35 #-}
happyIn36 :: t36 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn36 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn36 #-}
happyOut36 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t36
happyOut36 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut36 #-}
happyIn37 :: t37 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn37 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn37 #-}
happyOut37 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t37
happyOut37 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut37 #-}
happyIn38 :: t38 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn38 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn38 #-}
happyOut38 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t38
happyOut38 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut38 #-}
happyIn39 :: t39 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn39 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn39 #-}
happyOut39 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t39
happyOut39 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut39 #-}
happyIn40 :: t40 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn40 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn40 #-}
happyOut40 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t40
happyOut40 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut40 #-}
happyIn41 :: t41 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn41 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn41 #-}
happyOut41 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t41
happyOut41 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut41 #-}
happyIn42 :: t42 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn42 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn42 #-}
happyOut42 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t42
happyOut42 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut42 #-}
happyIn43 :: t43 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn43 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn43 #-}
happyOut43 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t43
happyOut43 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut43 #-}
happyIn44 :: t44 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn44 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn44 #-}
happyOut44 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t44
happyOut44 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut44 #-}
happyIn45 :: t45 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn45 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn45 #-}
happyOut45 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t45
happyOut45 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut45 #-}
happyIn46 :: t46 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn46 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn46 #-}
happyOut46 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t46
happyOut46 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut46 #-}
happyIn47 :: t47 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn47 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn47 #-}
happyOut47 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t47
happyOut47 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut47 #-}
happyIn48 :: t48 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn48 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn48 #-}
happyOut48 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t48
happyOut48 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut48 #-}
happyIn49 :: t49 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn49 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn49 #-}
happyOut49 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t49
happyOut49 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut49 #-}
happyIn50 :: t50 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn50 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn50 #-}
happyOut50 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t50
happyOut50 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut50 #-}
happyIn51 :: t51 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn51 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn51 #-}
happyOut51 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t51
happyOut51 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut51 #-}
happyIn52 :: t52 -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyIn52 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn52 #-}
happyOut52 :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> t52
happyOut52 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut52 #-}
happyInTok :: (Lexeme Token) -> (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52)
happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyInTok #-}
happyOutTok :: (HappyAbsSyn t9 t10 t11 t12 t13 t14 t15 t19 t20 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52) -> (Lexeme Token)
happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOutTok #-}


happyExpList :: HappyAddr
happyExpList = HappyA# "\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc1\xc0\xf0\x22\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc1\xc0\xf0\x22\x44\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x05\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\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x05\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\xf0\xf7\x7f\x00\x28\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\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x1d\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x40\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\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\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\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x04\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\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\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\xa8\x00\x10\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\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\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x02\x28\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\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\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x01\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\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x20\x28\x00\x10\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\xf0\xf7\x7f\x00\x28\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x6c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x64\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x60\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x7c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x7c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x7c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x7c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x7c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\x07\x7c\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x04\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\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x20\x28\x00\x10\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x20\x08\x08\x15\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\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\xf0\xf7\x7f\x00\x28\x00\x10\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\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\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\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x2a\x00\x10\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\x00\x10\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x2a\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\x80\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x08\x08\x05\x10\x28\x0c\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\x00\x90\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xf7\x7f\x00\x28\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

{-# NOINLINE happyExpListPerState #-}
happyExpListPerState st =
    token_strs_expected
  where token_strs = ["error","%dummy","%start_chunk_","%start_exp_","%start_stat_","block","retstat","stat","elseif","else","step","assign","varlist","explist","namelist","prefixexp","functioncall","funcname","dottedname","methodname","var","exp","args","functiondef","funcbody","parlist","parnames1","tableconstructor","fieldlist","fieldsep","field","name","many__dottedname__","many__elseif__","many__stat__","opt__';'__","opt__assign__","opt__else__","opt__fieldsep__","opt__methodname__","opt__retstat__","opt__step__","sepBy__exp__','__","sepBy1__exp__','__","sepBy1__name__','__","sepBy1__var__','__","revMany__dottedname__","revMany__elseif__","revMany__stat__","revSepBy1__exp__','__","revSepBy1__name__','__","revSepBy1__var__','__","'+'","'-'","'*'","'/'","'//'","'%'","'^'","'#'","'=='","'~='","'<='","'>='","'<'","'>'","'&'","'~'","'|'","'>>'","'<<'","'='","'('","')'","'{'","'}'","'['","']'","'::'","';'","':'","','","'.'","'..'","'...'","'and'","'break'","'do'","'else'","'elseif'","'end'","'false'","'for'","'function'","'goto'","'if'","'in'","'local'","'nil'","'not'","'or'","'repeat'","'return'","'then'","'true'","'until'","'while'","integer","float","literalString","ident","%eof"]
        bit_start = st * 112
        bit_end = (st + 1) * 112
        read_bit = readArrayBit happyExpList
        bits = map read_bit [bit_start..bit_end - 1]
        bits_indexed = zip bits [0..111]
        token_strs_expected = concatMap f bits_indexed
        f (False, _) = []
        f (True, nr) = [token_strs !! nr]

happyActOffsets :: HappyAddr
happyActOffsets = HappyA# "\x00\x00\x4e\x00\x01\x02\x00\x00\xeb\xff\x01\x02\x1c\x00\x50\x00\x9c\x00\xcb\x00\xcc\x00\x00\x00\x00\x00\x4a\x00\x4e\x00\x68\x00\x00\x00\x00\x00\x00\x00\x68\x00\x68\x00\x68\x00\x4e\x00\xf3\xff\x00\x00\x4e\x00\x00\x00\xf5\x00\x00\x00\x00\x00\x01\x00\x00\x00\x00\x00\x4e\x00\x4e\x00\x4e\x00\x14\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x4e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6a\x00\xa0\x00\x19\x00\x7c\x00\xe7\x01\xbe\x00\x00\x00\xc0\x00\x00\x00\x4e\x00\xca\x00\xca\x00\xca\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x4e\x00\x9b\x00\x00\x00\x00\x00\x4e\x00\x4e\x00\x9e\x00\x9e\x00\x00\x00\xf1\x00\x09\x00\xc7\x00\x00\x00\x00\x00\xc8\x00\xa3\x00\x89\x00\x00\x00\xd2\x00\x00\x00\xbf\x00\xdb\x00\x36\x00\xd5\x00\x1a\x01\xec\xff\x4e\x00\x00\x00\x00\x00\x00\x00\x4e\x00\xe7\x01\xdd\x00\x00\x00\xe9\x00\x00\x00\x00\x00\x1e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x4e\x00\xee\x00\xf0\x00\x38\x00\x00\x00\xfb\x00\xdc\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x4e\x00\x00\x00\x00\x00\x00\x00\x43\x01\x00\x01\x00\x00\xaa\x02\xcc\x02\x65\x01\x65\x01\x65\x01\xf2\x02\x05\x03\x18\x03\xdf\x02\xdf\x02\xdf\x02\xdf\x02\xdf\x02\xdf\x02\x12\x01\x12\x01\x12\x01\x12\x01\x12\x01\x3b\x01\x3b\x01\x6c\x01\x4e\x00\x31\x00\x02\x01\x00\x00\x00\x00\x18\x01\x13\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb2\x00\x00\x00\x00\x00\x00\x00\xe7\x01\x20\x01\x00\x00\x00\x00\x3b\x00\xe7\x01\x00\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf7\x00\x00\x00\x00\x00\x14\x01\x95\x01\x4e\x00\x00\x00\x00\x00\xe7\x01\x4e\x00\x00\x00\x00\x00\x11\x01\x1d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x00\x00\x00\x00\xe7\x01\x00\x00\x4e\x00\x00\x00\x53\x00\x00\x00\x79\x00\xbe\x01\x00\x00\x15\x01\x4e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x00\x00\x00\xe7\x01\x00\x00\x7b\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

happyGotoOffsets :: HappyAddr
happyGotoOffsets = HappyA# "\x17\x00\xc9\x01\xf9\x01\xfb\xff\x39\x00\xfb\x01\x00\x00\x00\x00\x5f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x02\x3d\x01\x00\x00\x00\x00\x1a\x00\xab\x00\x16\x00\x3f\x01\x17\x03\xf3\x01\x2a\x00\x24\x03\x00\x00\x5f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x31\x03\x3a\x03\x43\x03\x79\x01\x00\x00\x00\x00\x47\x01\x00\x00\x4c\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\x00\x00\x07\x00\x00\x00\x00\x00\x00\x00\x55\x03\x00\x00\x00\x00\x00\x00\x5e\x03\x67\x03\x70\x03\x79\x03\x82\x03\x8b\x03\x94\x03\x9d\x03\xa6\x03\xaf\x03\xb8\x03\xc1\x03\xca\x03\xd3\x03\xdc\x03\xe5\x03\xee\x03\xf7\x03\x00\x04\x09\x04\x12\x04\x0f\x00\x00\x00\x00\x00\x60\x02\x1b\x04\x41\x01\x42\x01\x00\x00\x00\x00\x00\x00\x61\x00\x00\x00\x00\x00\x00\x00\x44\x01\x00\x00\x00\x00\x4c\x01\x8d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfe\x00\x2f\x02\x00\x00\x00\x00\x00\x00\x7e\x02\x00\x00\x46\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x24\x04\x38\x02\x0d\x00\x53\x01\x00\x00\x51\x00\x4e\x01\x48\x01\x00\x00\x00\x00\x57\x02\x00\x00\x2d\x04\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x36\x04\xa0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x66\x01\x57\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x00\x00\x00\x00\x00\x00\x67\x01\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x04\x00\x00\x00\x00\x00\x00\x48\x04\x5a\x00\x00\x00\x11\x00\x7f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x51\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x04\x00\x00\x00\x00\x81\x00\x00\x00\xb3\x00\x00\x00\x00\x00\x63\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x00\x00\x91\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

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

happyDefActions :: HappyAddr
happyDefActions = HappyA# "\x7d\xff\x00\x00\x00\x00\x00\x00\x8a\xff\x96\xff\x00\x00\x00\x00\x00\x00\xf8\xff\x78\xff\xd4\xff\xdf\xff\x83\xff\x00\x00\x00\x00\xfa\xff\xf6\xff\x7d\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7d\xff\x00\x00\x99\xff\xc9\xff\xdb\xff\xdc\xff\x00\x00\xca\xff\xc8\xff\x00\x00\x00\x00\x00\x00\x00\x00\xcb\xff\xd0\xff\x00\x00\xd1\xff\x00\x00\xcf\xff\xce\xff\xcd\xff\xcc\xff\x00\x00\xb0\xff\x00\x00\xa5\xff\x9a\xff\x8e\xff\x9f\xff\xd4\xff\xa2\xff\x00\x00\xb1\xff\xaf\xff\xb2\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\xff\xad\xff\x86\xff\x00\x00\x00\x00\x00\x00\xac\xff\x00\x00\x00\x00\x92\xff\x7a\xff\xdd\xff\x84\xff\x00\x00\x00\x00\xf5\xff\x00\x00\x81\xff\x00\x00\x7a\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7e\xff\x8b\xff\xfc\xff\x86\xff\x7c\xff\x94\xff\x87\xff\x85\xff\xf9\xff\xde\xff\x77\xff\xda\xff\xf7\xff\xe8\xff\xf0\xff\x00\x00\x00\x00\x8c\xff\x98\xff\x00\x00\x7d\xff\x00\x00\x00\x00\x93\xff\xf4\xff\x00\x00\xe9\xff\x00\x00\x7d\xff\xd2\xff\xd5\xff\x00\x00\x00\x00\xd8\xff\xb8\xff\xb9\xff\xc0\xff\xb4\xff\xb3\xff\xb6\xff\xb5\xff\xb7\xff\xbd\xff\xbf\xff\xbc\xff\xbe\xff\xba\xff\xbb\xff\xc2\xff\xc1\xff\xc3\xff\xc4\xff\xc5\xff\xc6\xff\xc7\xff\x00\x00\x00\x00\x8f\xff\x00\x00\x9d\xff\x9e\xff\x00\x00\xa7\xff\xa4\xff\xa6\xff\xaa\xff\xab\xff\x00\x00\x7d\xff\xa1\xff\xa0\xff\x9b\xff\x00\x00\xae\xff\xd3\xff\x00\x00\xf1\xff\xe0\xff\x79\xff\x00\x00\x7f\xff\xeb\xff\xf3\xff\x82\xff\x00\x00\x8d\xff\xd7\xff\x00\x00\x00\x00\x00\x00\xfb\xff\x95\xff\x7b\xff\x00\x00\x7d\xff\xd6\xff\x90\xff\x97\xff\xea\xff\xf2\xff\xe7\xff\xef\xff\x00\x00\xa9\xff\xa3\xff\xa8\xff\x9c\xff\x80\xff\x00\x00\x91\xff\x00\x00\x7d\xff\x00\x00\x88\xff\x89\xff\x00\x00\x00\x00\xe4\xff\xec\xff\xe2\xff\xe6\xff\xee\xff\x00\x00\x7d\xff\xe1\xff\x7d\xff\x00\x00\xe3\xff\xe5\xff\xed\xff"#

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

happyTable :: HappyAddr
happyTable = HappyA# "\x00\x00\x0f\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x85\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\xd7\x00\x22\x00\x2e\x00\x04\x00\xac\x00\x65\x00\xbf\x00\x23\x00\x5f\x00\x6e\x00\xa3\x00\x8b\x00\x4e\x00\x61\x00\x4f\x00\x24\x00\x52\x00\x05\x00\x1b\x00\xa4\x00\x0f\x00\x59\x00\x25\x00\x37\x00\x38\x00\x1b\x00\xc0\x00\x62\x00\xd8\x00\x50\x00\x22\x00\x04\x00\x26\x00\x78\x00\x04\x00\xbc\x00\x23\x00\x6b\x00\xcf\x00\x27\x00\xff\xff\x28\x00\x86\x00\xad\x00\x24\x00\x05\x00\x29\x00\x2a\x00\x05\x00\x0f\x00\x04\x00\x25\x00\x2b\x00\x38\x00\xcd\x00\x2c\x00\x2d\x00\x2e\x00\x1b\x00\x22\x00\xba\x00\x26\x00\xe3\x00\xb5\x00\x05\x00\x23\x00\xd1\x00\xff\xff\x27\x00\xda\x00\x28\x00\x6c\x00\x79\x00\x24\x00\xbd\x00\x29\x00\x2a\x00\xd0\x00\x0f\x00\x6a\x00\x25\x00\x2b\x00\x81\x00\x69\x00\x2c\x00\x2d\x00\x2e\x00\x1b\x00\x50\x00\x04\x00\x26\x00\x51\x00\x04\x00\xce\x00\x32\x00\x04\x00\x52\x00\x27\x00\x04\x00\x28\x00\xe0\x00\xe4\x00\xeb\x00\x05\x00\x29\x00\x2a\x00\x05\x00\x82\x00\xe1\x00\x05\x00\x2b\x00\xe9\x00\x05\x00\x2c\x00\x2d\x00\x2e\x00\x1b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\xe8\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\xab\x00\x04\x00\xca\x00\xe1\x00\x04\x00\xec\x00\x1b\x00\xa7\x00\xa8\x00\xff\xff\x42\x00\x7b\x00\x4e\x00\xa9\x00\x4f\x00\x05\x00\xcb\x00\x04\x00\x05\x00\x54\x00\x54\x00\x25\x00\x25\x00\x63\x00\x55\x00\x7c\x00\x1b\x00\xdc\x00\x56\x00\x50\x00\x57\x00\x05\x00\x7f\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x64\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x42\x00\x5c\x00\xd4\x00\xa3\x00\x58\x00\x58\x00\xdd\x00\x5d\x00\x1b\x00\xa6\x00\x84\x00\xa7\x00\x4e\x00\x1b\x00\x4f\x00\xdb\xff\xdc\xff\xdb\xff\xdc\xff\xdb\xff\xdc\xff\x81\x00\x32\x00\xdb\xff\xdc\xff\xdb\xff\xdc\xff\x7b\x00\x1b\x00\x50\x00\x7a\x00\x77\x00\xe6\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\xc6\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\xdb\xff\xdc\xff\xc4\x00\x08\x00\x1c\x00\x54\x00\x56\x00\x25\x00\x74\x00\x55\x00\xbf\x00\x32\x00\x4e\x00\x56\x00\x4f\x00\x57\x00\x87\x00\xb4\x00\x1b\x00\x0b\x00\x42\x00\xb0\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x50\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\xaf\x00\x58\x00\x76\x00\xae\x00\x1b\x00\xdc\xff\xd1\x00\xdc\xff\xda\x00\xdc\xff\xc9\x00\xe8\x00\x4e\x00\xdc\xff\x4f\x00\xdc\xff\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\xd7\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x50\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x66\x00\xdc\xff\x60\x00\x30\x00\x88\x00\x87\x00\xb5\x00\x7f\x00\x7d\x00\xbd\x00\xb9\x00\xb8\x00\x4e\x00\xc4\x00\x4f\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x50\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\xd2\x00\xc9\x00\xd5\x00\x1b\x00\x1c\x00\x4e\x00\xb3\x00\x00\x00\x1d\x00\x32\x00\x00\x00\x1f\x00\x4e\x00\x00\x00\x4f\x00\x20\x00\x33\x00\x00\x00\x34\x00\x35\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x50\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x00\x00\x1b\x00\x1c\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x32\x00\x00\x00\x1f\x00\xc8\x00\x00\x00\x4e\x00\x20\x00\x4f\x00\x00\x00\xb0\x00\x35\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x50\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x00\x00\x1b\x00\x1c\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x1e\x00\x00\x00\x1f\x00\xdf\x00\x00\x00\x4e\x00\x20\x00\x4f\x00\x00\x00\x00\x00\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x50\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x06\x00\x5a\x00\x6a\x00\x00\x00\x00\x00\x07\x00\x00\x00\x07\x00\x08\x00\x09\x00\x08\x00\x09\x00\x4e\x00\x0a\x00\x4f\x00\x0a\x00\x00\x00\x00\x00\x5b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0b\x00\x00\x00\x0b\x00\x0f\x00\x00\x00\x50\x00\x00\x00\x5c\x00\x00\x00\x10\x00\x11\x00\x00\x00\x00\x00\x5d\x00\x0c\x00\x00\x00\x0c\x00\x12\x00\x13\x00\x00\x00\x0d\x00\x00\x00\x0d\x00\x14\x00\x15\x00\x16\x00\x17\x00\x00\x00\x18\x00\x00\x00\x00\x00\x00\x00\x19\x00\x00\x00\x00\x00\x00\x00\x72\x00\x1a\x00\x1b\x00\x1c\x00\x00\x00\x1b\x00\x00\x00\x1d\x00\x6e\x00\xc1\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x6e\x00\x0b\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x0b\x00\x00\x00\x00\x00\x73\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x00\x00\x00\x00\x00\x73\x00\xb7\x00\x00\x00\x1b\x00\x1c\x00\x00\x00\x71\x00\x00\x00\x1d\x00\x6e\x00\x00\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x6e\x00\x0b\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x0b\x00\x00\x00\x00\x00\x73\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x00\x00\x00\x8a\x00\x70\x00\x00\x00\x1b\x00\x1c\x00\x00\x00\x00\x00\x71\x00\x1d\x00\x6e\x00\x00\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x67\x00\x0b\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x0b\x00\x00\x00\x6f\x00\x70\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x71\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x00\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x4f\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x00\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x49\x00\x4a\x00\x00\x00\x4c\x00\x4d\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x49\x00\x00\x00\x00\x00\x4c\x00\x4d\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x00\x00\x1b\x00\x1c\x00\x00\x00\x00\x00\x4e\x00\x1d\x00\x5f\x00\x00\x00\x1f\x00\x4c\x00\x4d\x00\x00\x00\x20\x00\x1b\x00\x1c\x00\x00\x00\x0b\x00\x00\x00\x1d\x00\x58\x00\x00\x00\x1f\x00\x00\x00\x4e\x00\x00\x00\x20\x00\x1b\x00\x1c\x00\x00\x00\x0b\x00\x00\x00\x1d\x00\x3a\x00\x00\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x39\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x38\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x2f\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xa1\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xa0\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x9f\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x9e\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x9d\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x9c\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x9b\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x9a\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x99\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x98\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x97\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x96\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x95\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x94\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x93\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x92\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x91\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x90\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x8f\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x8e\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x8d\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x8c\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\x89\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xc2\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xb6\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xb1\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xc6\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xdb\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xd4\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xe4\x00\x0b\x00\x1f\x00\x1b\x00\x1c\x00\x00\x00\x20\x00\x00\x00\x1d\x00\xe6\x00\x0b\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x00\x00\x00\x00\x0b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

happyReduceArr = Happy_Data_Array.array (3, 136) [
        (3 , happyReduce_3),
        (4 , happyReduce_4),
        (5 , happyReduce_5),
        (6 , happyReduce_6),
        (7 , happyReduce_7),
        (8 , happyReduce_8),
        (9 , happyReduce_9),
        (10 , happyReduce_10),
        (11 , happyReduce_11),
        (12 , happyReduce_12),
        (13 , happyReduce_13),
        (14 , happyReduce_14),
        (15 , happyReduce_15),
        (16 , happyReduce_16),
        (17 , happyReduce_17),
        (18 , happyReduce_18),
        (19 , happyReduce_19),
        (20 , happyReduce_20),
        (21 , happyReduce_21),
        (22 , happyReduce_22),
        (23 , happyReduce_23),
        (24 , happyReduce_24),
        (25 , happyReduce_25),
        (26 , happyReduce_26),
        (27 , happyReduce_27),
        (28 , happyReduce_28),
        (29 , happyReduce_29),
        (30 , happyReduce_30),
        (31 , happyReduce_31),
        (32 , happyReduce_32),
        (33 , happyReduce_33),
        (34 , happyReduce_34),
        (35 , happyReduce_35),
        (36 , happyReduce_36),
        (37 , happyReduce_37),
        (38 , happyReduce_38),
        (39 , happyReduce_39),
        (40 , happyReduce_40),
        (41 , happyReduce_41),
        (42 , happyReduce_42),
        (43 , happyReduce_43),
        (44 , happyReduce_44),
        (45 , happyReduce_45),
        (46 , happyReduce_46),
        (47 , happyReduce_47),
        (48 , happyReduce_48),
        (49 , happyReduce_49),
        (50 , happyReduce_50),
        (51 , happyReduce_51),
        (52 , happyReduce_52),
        (53 , happyReduce_53),
        (54 , happyReduce_54),
        (55 , happyReduce_55),
        (56 , happyReduce_56),
        (57 , happyReduce_57),
        (58 , happyReduce_58),
        (59 , happyReduce_59),
        (60 , happyReduce_60),
        (61 , happyReduce_61),
        (62 , happyReduce_62),
        (63 , happyReduce_63),
        (64 , happyReduce_64),
        (65 , happyReduce_65),
        (66 , happyReduce_66),
        (67 , happyReduce_67),
        (68 , happyReduce_68),
        (69 , happyReduce_69),
        (70 , happyReduce_70),
        (71 , happyReduce_71),
        (72 , happyReduce_72),
        (73 , happyReduce_73),
        (74 , happyReduce_74),
        (75 , happyReduce_75),
        (76 , happyReduce_76),
        (77 , happyReduce_77),
        (78 , happyReduce_78),
        (79 , happyReduce_79),
        (80 , happyReduce_80),
        (81 , happyReduce_81),
        (82 , happyReduce_82),
        (83 , happyReduce_83),
        (84 , happyReduce_84),
        (85 , happyReduce_85),
        (86 , happyReduce_86),
        (87 , happyReduce_87),
        (88 , happyReduce_88),
        (89 , happyReduce_89),
        (90 , happyReduce_90),
        (91 , happyReduce_91),
        (92 , happyReduce_92),
        (93 , happyReduce_93),
        (94 , happyReduce_94),
        (95 , happyReduce_95),
        (96 , happyReduce_96),
        (97 , happyReduce_97),
        (98 , happyReduce_98),
        (99 , happyReduce_99),
        (100 , happyReduce_100),
        (101 , happyReduce_101),
        (102 , happyReduce_102),
        (103 , happyReduce_103),
        (104 , happyReduce_104),
        (105 , happyReduce_105),
        (106 , happyReduce_106),
        (107 , happyReduce_107),
        (108 , happyReduce_108),
        (109 , happyReduce_109),
        (110 , happyReduce_110),
        (111 , happyReduce_111),
        (112 , happyReduce_112),
        (113 , happyReduce_113),
        (114 , happyReduce_114),
        (115 , happyReduce_115),
        (116 , happyReduce_116),
        (117 , happyReduce_117),
        (118 , happyReduce_118),
        (119 , happyReduce_119),
        (120 , happyReduce_120),
        (121 , happyReduce_121),
        (122 , happyReduce_122),
        (123 , happyReduce_123),
        (124 , happyReduce_124),
        (125 , happyReduce_125),
        (126 , happyReduce_126),
        (127 , happyReduce_127),
        (128 , happyReduce_128),
        (129 , happyReduce_129),
        (130 , happyReduce_130),
        (131 , happyReduce_131),
        (132 , happyReduce_132),
        (133 , happyReduce_133),
        (134 , happyReduce_134),
        (135 , happyReduce_135),
        (136 , happyReduce_136)
        ]

happy_n_terms = 61 :: Int
happy_n_nonterms = 47 :: Int

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_3 = happySpecReduce_2  0# happyReduction_3
happyReduction_3 happy_x_2
        happy_x_1
         =  case happyOut35 happy_x_1 of { happy_var_1 ->
        case happyOut41 happy_x_2 of { happy_var_2 ->
        happyIn6
                 (at (happy_var_1,happy_var_2) Block happy_var_1 happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_4 = happySpecReduce_3  1# happyReduction_4
happyReduction_4 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut43 happy_x_2 of { happy_var_2 ->
        happyIn7
                 (happy_var_2
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_5 = happySpecReduce_1  2# happyReduction_5
happyReduction_5 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn8
                 (at happy_var_1 EmptyStat
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_6 = happySpecReduce_3  2# happyReduction_6
happyReduction_6 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut13 happy_x_1 of { happy_var_1 ->
        case happyOut14 happy_x_3 of { happy_var_3 ->
        happyIn8
                 (at (head happy_var_1,last happy_var_3) Assign happy_var_1 happy_var_3
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_7 = happySpecReduce_1  2# happyReduction_7
happyReduction_7 happy_x_1
         =  case happyOut17 happy_x_1 of { happy_var_1 ->
        happyIn8
                 (at happy_var_1 FunCall happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_8 = happySpecReduce_3  2# happyReduction_8
happyReduction_8 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_2 of { happy_var_2 ->
        case happyOutTok happy_x_3 of { happy_var_3 ->
        happyIn8
                 (at (happy_var_1,happy_var_3) Label happy_var_2
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_9 = happySpecReduce_1  2# happyReduction_9
happyReduction_9 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn8
                 (at happy_var_1 Break
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_10 = happySpecReduce_2  2# happyReduction_10
happyReduction_10 happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_2 of { happy_var_2 ->
        happyIn8
                 (at (happy_var_1,happy_var_2) Goto happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_11 = happySpecReduce_3  2# happyReduction_11
happyReduction_11 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut15 happy_x_2 of { happy_var_2 ->
        case happyOut37 happy_x_3 of { happy_var_3 ->
        happyIn8
                 (at (happy_var_1,(happy_var_2,happy_var_3)) LocalAssign happy_var_2 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_12 = happyReduce 4# 2# happyReduction_12
happyReduction_12 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut18 happy_x_2 of { happy_var_2 ->
        case happyOut25 happy_x_3 of { happy_var_3 ->
        case happyOutTok happy_x_4 of { happy_var_4 ->
        happyIn8
                 (at (happy_var_1,happy_var_4)  FunAssign happy_var_2 happy_var_3
        ) `HappyStk` happyRest}}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_13 = happyReduce 5# 2# happyReduction_13
happyReduction_13 (happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_3 of { happy_var_3 ->
        case happyOut25 happy_x_4 of { happy_var_4 ->
        case happyOutTok happy_x_5 of { happy_var_5 ->
        happyIn8
                 (at (happy_var_1,happy_var_5)  LocalFunAssign happy_var_3 happy_var_4
        ) `HappyStk` happyRest}}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_14 = happyReduce 4# 2# happyReduction_14
happyReduction_14 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut6 happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_4 of { happy_var_4 ->
        happyIn8
                 (at (happy_var_1,happy_var_4)  Repeat happy_var_2 happy_var_4
        ) `HappyStk` happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_15 = happySpecReduce_3  2# happyReduction_15
happyReduction_15 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut6 happy_x_2 of { happy_var_2 ->
        case happyOutTok happy_x_3 of { happy_var_3 ->
        happyIn8
                 (at (happy_var_1,happy_var_3)  Do happy_var_2
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_16 = happyReduce 5# 2# happyReduction_16
happyReduction_16 (happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        case happyOut6 happy_x_4 of { happy_var_4 ->
        case happyOutTok happy_x_5 of { happy_var_5 ->
        happyIn8
                 (at (happy_var_1,happy_var_5)  While happy_var_2 happy_var_4
        ) `HappyStk` happyRest}}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_17 = happyReduce 7# 2# happyReduction_17
happyReduction_17 (happy_x_7 `HappyStk`
        happy_x_6 `HappyStk`
        happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        case happyOut6 happy_x_4 of { happy_var_4 ->
        case happyOut34 happy_x_5 of { happy_var_5 ->
        case happyOut38 happy_x_6 of { happy_var_6 ->
        case happyOutTok happy_x_7 of { happy_var_7 ->
        happyIn8
                 (at (happy_var_1,happy_var_7)  If ((happy_var_2,happy_var_4):happy_var_5) happy_var_6
        ) `HappyStk` happyRest}}}}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_18 = happyReduce 10# 2# happyReduction_18
happyReduction_18 (happy_x_10 `HappyStk`
        happy_x_9 `HappyStk`
        happy_x_8 `HappyStk`
        happy_x_7 `HappyStk`
        happy_x_6 `HappyStk`
        happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_4 of { happy_var_4 ->
        case happyOut22 happy_x_6 of { happy_var_6 ->
        case happyOut42 happy_x_7 of { happy_var_7 ->
        case happyOut6 happy_x_9 of { happy_var_9 ->
        case happyOutTok happy_x_10 of { happy_var_10 ->
        happyIn8
                 (at (happy_var_1,happy_var_10) ForRange happy_var_2 happy_var_4 happy_var_6 happy_var_7 happy_var_9
        ) `HappyStk` happyRest}}}}}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_19 = happyReduce 7# 2# happyReduction_19
happyReduction_19 (happy_x_7 `HappyStk`
        happy_x_6 `HappyStk`
        happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut15 happy_x_2 of { happy_var_2 ->
        case happyOut14 happy_x_4 of { happy_var_4 ->
        case happyOut6 happy_x_6 of { happy_var_6 ->
        case happyOutTok happy_x_7 of { happy_var_7 ->
        happyIn8
                 (at (happy_var_1,happy_var_7)  ForIn happy_var_2 happy_var_4 happy_var_6
        ) `HappyStk` happyRest}}}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_20 = happyMonadReduce 4# 2# happyReduction_20
happyReduction_20 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_21 = happyMonadReduce 5# 2# happyReduction_21
happyReduction_21 (happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_22 = happyMonadReduce 3# 2# happyReduction_22
happyReduction_22 (happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_23 = happyMonadReduce 3# 2# happyReduction_23
happyReduction_23 (happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_24 = happyMonadReduce 5# 2# happyReduction_24
happyReduction_24 (happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_25 = happyMonadReduce 7# 2# happyReduction_25
happyReduction_25 (happy_x_7 `HappyStk`
        happy_x_6 `HappyStk`
        happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_26 = happyMonadReduce 10# 2# happyReduction_26
happyReduction_26 (happy_x_10 `HappyStk`
        happy_x_9 `HappyStk`
        happy_x_8 `HappyStk`
        happy_x_7 `HappyStk`
        happy_x_6 `HappyStk`
        happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_27 = happyMonadReduce 7# 2# happyReduction_27
happyReduction_27 (happy_x_7 `HappyStk`
        happy_x_6 `HappyStk`
        happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn8 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_28 = happyReduce 4# 3# happyReduction_28
happyReduction_28 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOut22 happy_x_2 of { happy_var_2 ->
        case happyOut6 happy_x_4 of { happy_var_4 ->
        happyIn9
                 ((happy_var_2,happy_var_4)
        ) `HappyStk` happyRest}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_29 = happySpecReduce_2  4# happyReduction_29
happyReduction_29 happy_x_2
        happy_x_1
         =  case happyOut6 happy_x_2 of { happy_var_2 ->
        happyIn10
                 (happy_var_2
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_30 = happySpecReduce_2  5# happyReduction_30
happyReduction_30 happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_2 of { happy_var_2 ->
        happyIn11
                 (happy_var_2
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_31 = happySpecReduce_2  6# happyReduction_31
happyReduction_31 happy_x_2
        happy_x_1
         =  case happyOut14 happy_x_2 of { happy_var_2 ->
        happyIn12
                 (happy_var_2
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_32 = happySpecReduce_1  7# happyReduction_32
happyReduction_32 happy_x_1
         =  case happyOut46 happy_x_1 of { happy_var_1 ->
        happyIn13
                 (happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_33 = happySpecReduce_1  8# happyReduction_33
happyReduction_33 happy_x_1
         =  case happyOut44 happy_x_1 of { happy_var_1 ->
        happyIn14
                 (happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_34 = happySpecReduce_1  9# happyReduction_34
happyReduction_34 happy_x_1
         =  case happyOut45 happy_x_1 of { happy_var_1 ->
        happyIn15
                 (happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_35 = happySpecReduce_1  10# happyReduction_35
happyReduction_35 happy_x_1
         =  case happyOut21 happy_x_1 of { happy_var_1 ->
        happyIn16
                 (at happy_var_1 PEVar happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_36 = happySpecReduce_1  10# happyReduction_36
happyReduction_36 happy_x_1
         =  case happyOut17 happy_x_1 of { happy_var_1 ->
        happyIn16
                 (at happy_var_1 PEFunCall happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_37 = happySpecReduce_3  10# happyReduction_37
happyReduction_37 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        case happyOutTok happy_x_3 of { happy_var_3 ->
        happyIn16
                 (at (happy_var_1,happy_var_3) Paren happy_var_2
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_38 = happySpecReduce_2  11# happyReduction_38
happyReduction_38 happy_x_2
        happy_x_1
         =  case happyOut16 happy_x_1 of { happy_var_1 ->
        case happyOut23 happy_x_2 of { happy_var_2 ->
        happyIn17
                 (at (happy_var_1,happy_var_2) NormalFunCall happy_var_1 happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_39 = happySpecReduce_3  11# happyReduction_39
happyReduction_39 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut16 happy_x_1 of { happy_var_1 ->
        case happyOut20 happy_x_2 of { happy_var_2 ->
        case happyOut23 happy_x_3 of { happy_var_3 ->
        happyIn17
                 (at (happy_var_1,happy_var_3) MethodCall happy_var_1 happy_var_2 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_40 = happySpecReduce_3  12# happyReduction_40
happyReduction_40 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut32 happy_x_1 of { happy_var_1 ->
        case happyOut33 happy_x_2 of { happy_var_2 ->
        case happyOut40 happy_x_3 of { happy_var_3 ->
        happyIn18
                 (at (happy_var_1,(happy_var_2,happy_var_3)) FunName happy_var_1 happy_var_2 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_41 = happySpecReduce_2  13# happyReduction_41
happyReduction_41 happy_x_2
        happy_x_1
         =  case happyOut32 happy_x_2 of { happy_var_2 ->
        happyIn19
                 (happy_var_2
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_42 = happySpecReduce_2  14# happyReduction_42
happyReduction_42 happy_x_2
        happy_x_1
         =  case happyOut32 happy_x_2 of { happy_var_2 ->
        happyIn20
                 (happy_var_2
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_43 = happySpecReduce_1  15# happyReduction_43
happyReduction_43 happy_x_1
         =  case happyOut32 happy_x_1 of { happy_var_1 ->
        happyIn21
                 (at happy_var_1 VarName happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_44 = happyReduce 4# 15# happyReduction_44
happyReduction_44 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOut16 happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        case happyOutTok happy_x_4 of { happy_var_4 ->
        happyIn21
                 (at (happy_var_1,happy_var_4) Select happy_var_1 happy_var_3
        ) `HappyStk` happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_45 = happySpecReduce_3  15# happyReduction_45
happyReduction_45 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut16 happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_3 of { happy_var_3 ->
        happyIn21
                 (at (happy_var_1,happy_var_3) SelectName happy_var_1 happy_var_3
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_46 = happySpecReduce_1  16# happyReduction_46
happyReduction_46 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 Nil
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_47 = happySpecReduce_1  16# happyReduction_47
happyReduction_47 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 Bool False
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_48 = happySpecReduce_1  16# happyReduction_48
happyReduction_48 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 Bool True
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_49 = happySpecReduce_1  16# happyReduction_49
happyReduction_49 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 Number IntNum (lexemeText happy_var_1)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_50 = happySpecReduce_1  16# happyReduction_50
happyReduction_50 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 Number FloatNum (lexemeText happy_var_1)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_51 = happySpecReduce_1  16# happyReduction_51
happyReduction_51 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 String (lexemeText happy_var_1)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_52 = happySpecReduce_1  16# happyReduction_52
happyReduction_52 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 Vararg
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_53 = happySpecReduce_1  16# happyReduction_53
happyReduction_53 happy_x_1
         =  case happyOut24 happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 EFunDef happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_54 = happySpecReduce_1  16# happyReduction_54
happyReduction_54 happy_x_1
         =  case happyOut16 happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 PrefixExp happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_55 = happySpecReduce_1  16# happyReduction_55
happyReduction_55 happy_x_1
         =  case happyOut28 happy_x_1 of { happy_var_1 ->
        happyIn22
                 (at happy_var_1 TableConst happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_56 = happySpecReduce_3  16# happyReduction_56
happyReduction_56 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Add   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_57 = happySpecReduce_3  16# happyReduction_57
happyReduction_57 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Sub   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_58 = happySpecReduce_3  16# happyReduction_58
happyReduction_58 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Mul   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_59 = happySpecReduce_3  16# happyReduction_59
happyReduction_59 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Div   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_60 = happySpecReduce_3  16# happyReduction_60
happyReduction_60 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 IDiv  ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_61 = happySpecReduce_3  16# happyReduction_61
happyReduction_61 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Exp   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_62 = happySpecReduce_3  16# happyReduction_62
happyReduction_62 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Mod   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_63 = happySpecReduce_3  16# happyReduction_63
happyReduction_63 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Concat) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_64 = happySpecReduce_3  16# happyReduction_64
happyReduction_64 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 LT    ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_65 = happySpecReduce_3  16# happyReduction_65
happyReduction_65 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 LTE   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_66 = happySpecReduce_3  16# happyReduction_66
happyReduction_66 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 GT    ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_67 = happySpecReduce_3  16# happyReduction_67
happyReduction_67 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 GTE   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_68 = happySpecReduce_3  16# happyReduction_68
happyReduction_68 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 EQ    ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_69 = happySpecReduce_3  16# happyReduction_69
happyReduction_69 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 NEQ   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_70 = happySpecReduce_3  16# happyReduction_70
happyReduction_70 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 And   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_71 = happySpecReduce_3  16# happyReduction_71
happyReduction_71 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 Or    ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_72 = happySpecReduce_3  16# happyReduction_72
happyReduction_72 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 BAnd  ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_73 = happySpecReduce_3  16# happyReduction_73
happyReduction_73 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 BOr   ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_74 = happySpecReduce_3  16# happyReduction_74
happyReduction_74 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 BXor  ) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_75 = happySpecReduce_3  16# happyReduction_75
happyReduction_75 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 ShiftL) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_76 = happySpecReduce_3  16# happyReduction_76
happyReduction_76 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn22
                 (at (happy_var_1,happy_var_3) Binop (at happy_var_2 ShiftR) happy_var_1 happy_var_3
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_77 = happySpecReduce_2  16# happyReduction_77
happyReduction_77 happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        happyIn22
                 (at (happy_var_1,happy_var_2) Unop (at happy_var_1 Neg)        happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_78 = happySpecReduce_2  16# happyReduction_78
happyReduction_78 happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        happyIn22
                 (at (happy_var_1,happy_var_2) Unop (at happy_var_1 Complement) happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_79 = happySpecReduce_2  16# happyReduction_79
happyReduction_79 happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        happyIn22
                 (at (happy_var_1,happy_var_2) Unop (at happy_var_1 Not)        happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_80 = happySpecReduce_2  16# happyReduction_80
happyReduction_80 happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        happyIn22
                 (at (happy_var_1,happy_var_2) Unop (at happy_var_1 Len)        happy_var_2
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_81 = happySpecReduce_3  17# happyReduction_81
happyReduction_81 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut43 happy_x_2 of { happy_var_2 ->
        case happyOutTok happy_x_3 of { happy_var_3 ->
        happyIn23
                 (at (happy_var_1,happy_var_3) Args happy_var_2
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_82 = happySpecReduce_1  17# happyReduction_82
happyReduction_82 happy_x_1
         =  case happyOut28 happy_x_1 of { happy_var_1 ->
        happyIn23
                 (at happy_var_1 TableArg happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_83 = happySpecReduce_1  17# happyReduction_83
happyReduction_83 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn23
                 (at happy_var_1 StringArg (lexemeText happy_var_1)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_84 = happySpecReduce_3  18# happyReduction_84
happyReduction_84 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut25 happy_x_2 of { happy_var_2 ->
        case happyOutTok happy_x_3 of { happy_var_3 ->
        happyIn24
                 (at (happy_var_1,happy_var_3) FunDef happy_var_2
        )}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_85 = happyMonadReduce 3# 18# happyReduction_85
happyReduction_85 (happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk
         = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 ->
        ( noEndP happy_var_1)})
        ) (\r -> happyReturn (happyIn24 r))

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_86 = happyReduce 4# 19# happyReduction_86
happyReduction_86 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut26 happy_x_2 of { happy_var_2 ->
        case happyOut6 happy_x_4 of { happy_var_4 ->
        happyIn25
                 (at (happy_var_1,happy_var_4) FunBody (fst happy_var_2) (snd happy_var_2) happy_var_4
        ) `HappyStk` happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_87 = happySpecReduce_3  20# happyReduction_87
happyReduction_87 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut27 happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_3 of { happy_var_3 ->
        happyIn26
                 ((reverse happy_var_1,getRange happy_var_3)
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_88 = happySpecReduce_1  20# happyReduction_88
happyReduction_88 happy_x_1
         =  case happyOut27 happy_x_1 of { happy_var_1 ->
        happyIn26
                 ((reverse happy_var_1,Nothing)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_89 = happySpecReduce_1  20# happyReduction_89
happyReduction_89 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn26
                 (([], getRange happy_var_1)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_90 = happySpecReduce_0  20# happyReduction_90
happyReduction_90  =  happyIn26
                 (([], Nothing)
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_91 = happySpecReduce_1  21# happyReduction_91
happyReduction_91 happy_x_1
         =  case happyOut32 happy_x_1 of { happy_var_1 ->
        happyIn27
                 ([happy_var_1]
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_92 = happySpecReduce_3  21# happyReduction_92
happyReduction_92 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut27 happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_3 of { happy_var_3 ->
        happyIn27
                 (happy_var_3 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_93 = happySpecReduce_2  22# happyReduction_93
happyReduction_93 happy_x_2
        happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOutTok happy_x_2 of { happy_var_2 ->
        happyIn28
                 (at (happy_var_1,happy_var_2) Table []
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_94 = happyReduce 4# 22# happyReduction_94
happyReduction_94 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut29 happy_x_2 of { happy_var_2 ->
        case happyOut39 happy_x_3 of { happy_var_3 ->
        happyIn28
                 (at (happy_var_1,happy_var_3) Table (reverse happy_var_2)
        ) `HappyStk` happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_95 = happySpecReduce_3  23# happyReduction_95
happyReduction_95 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut29 happy_x_1 of { happy_var_1 ->
        case happyOut31 happy_x_3 of { happy_var_3 ->
        happyIn29
                 (happy_var_3 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_96 = happySpecReduce_1  23# happyReduction_96
happyReduction_96 happy_x_1
         =  case happyOut31 happy_x_1 of { happy_var_1 ->
        happyIn29
                 ([happy_var_1]
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_97 = happySpecReduce_1  24# happyReduction_97
happyReduction_97 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn30
                 (happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_98 = happySpecReduce_1  24# happyReduction_98
happyReduction_98 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn30
                 (happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_99 = happyReduce 5# 25# happyReduction_99
happyReduction_99 (happy_x_5 `HappyStk`
        happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest)
         = case happyOutTok happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_2 of { happy_var_2 ->
        case happyOut22 happy_x_5 of { happy_var_5 ->
        happyIn31
                 (at (happy_var_1,happy_var_5) ExpField happy_var_2 happy_var_5
        ) `HappyStk` happyRest}}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_100 = happySpecReduce_3  25# happyReduction_100
happyReduction_100 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut32 happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn31
                 (at (happy_var_1,happy_var_3) NamedField happy_var_1 happy_var_3
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_101 = happySpecReduce_1  25# happyReduction_101
happyReduction_101 happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        happyIn31
                 (at happy_var_1      Field happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_102 = happySpecReduce_1  26# happyReduction_102
happyReduction_102 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn32
                 (at happy_var_1 Name (lexemeText happy_var_1)
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_103 = happySpecReduce_1  27# happyReduction_103
happyReduction_103 happy_x_1
         =  case happyOut47 happy_x_1 of { happy_var_1 ->
        happyIn33
                 (reverse happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_104 = happySpecReduce_1  28# happyReduction_104
happyReduction_104 happy_x_1
         =  case happyOut48 happy_x_1 of { happy_var_1 ->
        happyIn34
                 (reverse happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_105 = happySpecReduce_1  29# happyReduction_105
happyReduction_105 happy_x_1
         =  case happyOut49 happy_x_1 of { happy_var_1 ->
        happyIn35
                 (reverse happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_106 = happySpecReduce_1  30# happyReduction_106
happyReduction_106 happy_x_1
         =  case happyOutTok happy_x_1 of { happy_var_1 ->
        happyIn36
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_107 = happySpecReduce_0  30# happyReduction_107
happyReduction_107  =  happyIn36
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_108 = happySpecReduce_1  31# happyReduction_108
happyReduction_108 happy_x_1
         =  case happyOut12 happy_x_1 of { happy_var_1 ->
        happyIn37
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_109 = happySpecReduce_0  31# happyReduction_109
happyReduction_109  =  happyIn37
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_110 = happySpecReduce_1  32# happyReduction_110
happyReduction_110 happy_x_1
         =  case happyOut10 happy_x_1 of { happy_var_1 ->
        happyIn38
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_111 = happySpecReduce_0  32# happyReduction_111
happyReduction_111  =  happyIn38
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_112 = happySpecReduce_1  33# happyReduction_112
happyReduction_112 happy_x_1
         =  case happyOut30 happy_x_1 of { happy_var_1 ->
        happyIn39
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_113 = happySpecReduce_0  33# happyReduction_113
happyReduction_113  =  happyIn39
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_114 = happySpecReduce_1  34# happyReduction_114
happyReduction_114 happy_x_1
         =  case happyOut20 happy_x_1 of { happy_var_1 ->
        happyIn40
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_115 = happySpecReduce_0  34# happyReduction_115
happyReduction_115  =  happyIn40
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_116 = happySpecReduce_1  35# happyReduction_116
happyReduction_116 happy_x_1
         =  case happyOut7 happy_x_1 of { happy_var_1 ->
        happyIn41
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_117 = happySpecReduce_0  35# happyReduction_117
happyReduction_117  =  happyIn41
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_118 = happySpecReduce_1  36# happyReduction_118
happyReduction_118 happy_x_1
         =  case happyOut11 happy_x_1 of { happy_var_1 ->
        happyIn42
                 (Just happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_119 = happySpecReduce_0  36# happyReduction_119
happyReduction_119  =  happyIn42
                 (Nothing
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_120 = happySpecReduce_1  37# happyReduction_120
happyReduction_120 happy_x_1
         =  case happyOut44 happy_x_1 of { happy_var_1 ->
        happyIn43
                 (happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_121 = happySpecReduce_0  37# happyReduction_121
happyReduction_121  =  happyIn43
                 ([]
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_122 = happySpecReduce_1  38# happyReduction_122
happyReduction_122 happy_x_1
         =  case happyOut50 happy_x_1 of { happy_var_1 ->
        happyIn44
                 (reverse happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_123 = happySpecReduce_1  39# happyReduction_123
happyReduction_123 happy_x_1
         =  case happyOut51 happy_x_1 of { happy_var_1 ->
        happyIn45
                 (reverse happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_124 = happySpecReduce_1  40# happyReduction_124
happyReduction_124 happy_x_1
         =  case happyOut52 happy_x_1 of { happy_var_1 ->
        happyIn46
                 (reverse happy_var_1
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_125 = happySpecReduce_2  41# happyReduction_125
happyReduction_125 happy_x_2
        happy_x_1
         =  case happyOut47 happy_x_1 of { happy_var_1 ->
        case happyOut19 happy_x_2 of { happy_var_2 ->
        happyIn47
                 (happy_var_2 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_126 = happySpecReduce_0  41# happyReduction_126
happyReduction_126  =  happyIn47
                 ([]
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_127 = happySpecReduce_2  42# happyReduction_127
happyReduction_127 happy_x_2
        happy_x_1
         =  case happyOut48 happy_x_1 of { happy_var_1 ->
        case happyOut9 happy_x_2 of { happy_var_2 ->
        happyIn48
                 (happy_var_2 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_128 = happySpecReduce_0  42# happyReduction_128
happyReduction_128  =  happyIn48
                 ([]
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_129 = happySpecReduce_2  43# happyReduction_129
happyReduction_129 happy_x_2
        happy_x_1
         =  case happyOut49 happy_x_1 of { happy_var_1 ->
        case happyOut8 happy_x_2 of { happy_var_2 ->
        happyIn49
                 (happy_var_2 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_130 = happySpecReduce_0  43# happyReduction_130
happyReduction_130  =  happyIn49
                 ([]
        )

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_131 = happySpecReduce_1  44# happyReduction_131
happyReduction_131 happy_x_1
         =  case happyOut22 happy_x_1 of { happy_var_1 ->
        happyIn50
                 ([happy_var_1]
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_132 = happySpecReduce_3  44# happyReduction_132
happyReduction_132 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut50 happy_x_1 of { happy_var_1 ->
        case happyOut22 happy_x_3 of { happy_var_3 ->
        happyIn50
                 (happy_var_3 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_133 = happySpecReduce_1  45# happyReduction_133
happyReduction_133 happy_x_1
         =  case happyOut32 happy_x_1 of { happy_var_1 ->
        happyIn51
                 ([happy_var_1]
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_134 = happySpecReduce_3  45# happyReduction_134
happyReduction_134 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut51 happy_x_1 of { happy_var_1 ->
        case happyOut32 happy_x_3 of { happy_var_3 ->
        happyIn51
                 (happy_var_3 : happy_var_1
        )}}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_135 = happySpecReduce_1  46# happyReduction_135
happyReduction_135 happy_x_1
         =  case happyOut21 happy_x_1 of { happy_var_1 ->
        happyIn52
                 ([happy_var_1]
        )}

#if __GLASGOW_HASKELL__ >= 710
#endif
happyReduce_136 = happySpecReduce_3  46# happyReduction_136
happyReduction_136 happy_x_3
        happy_x_2
        happy_x_1
         =  case happyOut52 happy_x_1 of { happy_var_1 ->
        case happyOut21 happy_x_3 of { happy_var_3 ->
        happyIn52
                 (happy_var_3 : happy_var_1
        )}}

happyNewToken action sts stk [] =
        happyDoAction 60# notHappyAtAll action sts stk []

happyNewToken action sts stk (tk:tks) =
        let cont i = happyDoAction i tk action sts stk tks in
        case tk of {
        Lexeme { lexemeToken = TokPlus      } -> cont 1#;
        Lexeme { lexemeToken = TokMinus     } -> cont 2#;
        Lexeme { lexemeToken = TokStar      } -> cont 3#;
        Lexeme { lexemeToken = TokSlash     } -> cont 4#;
        Lexeme { lexemeToken = TokDSlash    } -> cont 5#;
        Lexeme { lexemeToken = TokPercent   } -> cont 6#;
        Lexeme { lexemeToken = TokExp       } -> cont 7#;
        Lexeme { lexemeToken = TokSh        } -> cont 8#;
        Lexeme { lexemeToken = TokEqual     } -> cont 9#;
        Lexeme { lexemeToken = TokNotequal  } -> cont 10#;
        Lexeme { lexemeToken = TokLEq       } -> cont 11#;
        Lexeme { lexemeToken = TokGEq       } -> cont 12#;
        Lexeme { lexemeToken = TokLT        } -> cont 13#;
        Lexeme { lexemeToken = TokGT        } -> cont 14#;
        Lexeme { lexemeToken = TokAmpersand } -> cont 15#;
        Lexeme { lexemeToken = TokTilde     } -> cont 16#;
        Lexeme { lexemeToken = TokPipe      } -> cont 17#;
        Lexeme { lexemeToken = TokDGT       } -> cont 18#;
        Lexeme { lexemeToken = TokDLT       } -> cont 19#;
        Lexeme { lexemeToken = TokAssign    } -> cont 20#;
        Lexeme { lexemeToken = TokLParen    } -> cont 21#;
        Lexeme { lexemeToken = TokRParen    } -> cont 22#;
        Lexeme { lexemeToken = TokLBrace    } -> cont 23#;
        Lexeme { lexemeToken = TokRBrace    } -> cont 24#;
        Lexeme { lexemeToken = TokLBracket  } -> cont 25#;
        Lexeme { lexemeToken = TokRBracket  } -> cont 26#;
        Lexeme { lexemeToken = TokDColon    } -> cont 27#;
        Lexeme { lexemeToken = TokSemic     } -> cont 28#;
        Lexeme { lexemeToken = TokColon     } -> cont 29#;
        Lexeme { lexemeToken = TokComma     } -> cont 30#;
        Lexeme { lexemeToken = TokDot       } -> cont 31#;
        Lexeme { lexemeToken = TokDDot      } -> cont 32#;
        Lexeme { lexemeToken = TokEllipsis  } -> cont 33#;
        Lexeme { lexemeToken = TokAnd       } -> cont 34#;
        Lexeme { lexemeToken = TokBreak     } -> cont 35#;
        Lexeme { lexemeToken = TokDo        } -> cont 36#;
        Lexeme { lexemeToken = TokElse      } -> cont 37#;
        Lexeme { lexemeToken = TokElseIf    } -> cont 38#;
        Lexeme { lexemeToken = TokEnd       } -> cont 39#;
        Lexeme { lexemeToken = TokFalse     } -> cont 40#;
        Lexeme { lexemeToken = TokFor       } -> cont 41#;
        Lexeme { lexemeToken = TokFunction  } -> cont 42#;
        Lexeme { lexemeToken = TokGoto      } -> cont 43#;
        Lexeme { lexemeToken = TokIf        } -> cont 44#;
        Lexeme { lexemeToken = TokIn        } -> cont 45#;
        Lexeme { lexemeToken = TokLocal     } -> cont 46#;
        Lexeme { lexemeToken = TokNil       } -> cont 47#;
        Lexeme { lexemeToken = TokNot       } -> cont 48#;
        Lexeme { lexemeToken = TokOr        } -> cont 49#;
        Lexeme { lexemeToken = TokRepeat    } -> cont 50#;
        Lexeme { lexemeToken = TokReturn    } -> cont 51#;
        Lexeme { lexemeToken = TokThen      } -> cont 52#;
        Lexeme { lexemeToken = TokTrue      } -> cont 53#;
        Lexeme { lexemeToken = TokUntil     } -> cont 54#;
        Lexeme { lexemeToken = TokWhile     } -> cont 55#;
        Lexeme { lexemeToken = TokInt       } -> cont 56#;
        Lexeme { lexemeToken = TokFloat     } -> cont 57#;
        Lexeme { lexemeToken = TokSLit      } -> cont 58#;
        Lexeme { lexemeToken = TokIdent     } -> cont 59#;
        _ -> happyError' ((tk:tks), [])
        }

happyError_ explist 60# tk tks = happyError' (tks, explist)
happyError_ explist _ tk tks = happyError' ((tk:tks), explist)

happyThen :: () => Either (SourceRange, String) a -> (a -> Either (SourceRange, String) b) -> Either (SourceRange, String) b
happyThen = (>>=)
happyReturn :: () => a -> Either (SourceRange, String) a
happyReturn = (return)
happyThen1 m k tks = (>>=) m (\a -> k a tks)
happyReturn1 :: () => a -> b -> Either (SourceRange, String) a
happyReturn1 = \a tks -> (return) a
happyError' :: () => ([(Lexeme Token)], [String]) -> Either (SourceRange, String) a
happyError' = (\(tokens, _) -> errorP tokens)
chunk_ tks = happySomeParser where
 happySomeParser = happyThen (happyParse 0# tks) (\x -> happyReturn (happyOut6 x))

exp_ tks = happySomeParser where
 happySomeParser = happyThen (happyParse 1# tks) (\x -> happyReturn (happyOut22 x))

stat_ tks = happySomeParser where
 happySomeParser = happyThen (happyParse 2# tks) (\x -> happyReturn (happyOut8 x))

happySeq = happyDontSeq


newtype Parser a = Parser ([Lexeme Token] -> Either (SourceRange,String) a)

-- | Parse a stream of tokens.
parseTokens :: Parser a -> [Lexeme Token] -> Either (SourceRange,String) a
parseTokens (Parser p) = p

chunk :: Parser (Block SourceRange)
chunk = Parser chunk_

stat :: Parser (Stat SourceRange)
stat = Parser stat_

exp :: Parser (Exp SourceRange)
exp = Parser exp_

instance Functor Parser where
  fmap f (Parser p) = Parser (fmap (fmap f) p)

errorP :: [Lexeme Token] -> Either (SourceRange,String) a
errorP ts =
  case ts of
    [] -> Left (fakeRng, "unexpected end of file")
      where fake = SourcePos (-1)(-1)(-1) (Text.pack "(fake pos)")
            fakeRng = SourceRange fake fake
    Lexeme { lexemeRange = rng, lexemeToken = t }:_ ->
      Left (rng, "unexpected " ++ show t)

noEndP :: Lexeme Token -> Either (SourceRange,String) a
noEndP Lexeme { lexemeRange = pos, lexemeToken = t } =
  Left (pos, "unterminated " ++ show t)

-- | Runs Lua lexer before parsing. Use @parseNamedText stat "name"@ to parse
-- statements, and @parseText exp "name"@ to parse expressions.
parseNamedText ::
  Parser a ->
  String {- ^ name -} ->
  Text {- ^ chunk -} ->
  Either (SourceRange, String) a
parseNamedText p n xs = parseTokens p (llexNamed n xs)

-- | Runs Lua lexer before parsing. Use @parseText stat@ to parse
-- statements, and @parseText exp@ to parse expressions.
parseText ::
  Parser a ->
  Text {- ^ chunk -} ->
  Either (SourceRange, String) a
parseText p = parseNamedText p "=<string>"

-- | Parse a Lua file. You can use @parseText chunk@ to parse a file from a string.
parseFile :: FilePath -> IO (Either (SourceRange, String) (Block SourceRange))
parseFile fp = fmap (parseNamedText chunk fp) (Text.readFile fp)



--------------------------------------------------------------------------------

at :: HasRange a => a -> (SourceRange -> b) -> b
at rng mk = mk $ fromMaybe fake $ getRange rng
  where
  none = SourcePos 0 1 1 (Text.pack "(nowehere)")
  fake = SourceRange { sourceFrom = none, sourceTo = none }

class HasRange a where
  getRange :: a -> Maybe SourceRange

instance HasRange SourceRange where
  getRange = Just

instance HasRange (Lexeme a) where
  getRange = Just . AlexTools.range

instance HasRange a => HasRange (Maybe a) where
  getRange x = getRange =<< x

instance (HasRange a, HasRange b) => HasRange (a,b) where
  getRange (x,y) =
    case (getRange x, getRange y) of
      (Nothing,Nothing) -> Nothing
      (Just a, Nothing) -> Just a
      (Nothing, Just a) -> Just a
      (Just a, Just b)  ->
        Just $! SourceRange { sourceFrom = sourceFrom a, sourceTo = sourceTo b }

instance HasRange a => HasRange [a] where
  getRange (x : xs) = getRange (x,xs)
  getRange []       = Nothing

instance HasRange a => HasRange (Stat  a)       where getRange = getRange . ann
instance HasRange a => HasRange (Exp   a)       where getRange = getRange . ann
instance HasRange a => HasRange (Var   a)       where getRange = getRange . ann
instance HasRange a => HasRange (Binop a)       where getRange = getRange . ann
instance HasRange a => HasRange (Unop  a)       where getRange = getRange . ann
instance HasRange a => HasRange (PrefixExp a)   where getRange = getRange . ann
instance HasRange a => HasRange (Table a)       where getRange = getRange . ann
instance HasRange a => HasRange (TableField a)  where getRange = getRange . ann
instance HasRange a => HasRange (Block a     )  where getRange = getRange . ann
instance HasRange a => HasRange (FunName a)     where getRange = getRange . ann
instance HasRange a => HasRange (FunDef a)      where getRange = getRange . ann
instance HasRange a => HasRange (FunBody a)     where getRange = getRange . ann
instance HasRange a => HasRange (FunCall a)     where getRange = getRange . ann
instance HasRange a => HasRange (FunArg a)      where getRange = getRange . ann
instance HasRange a => HasRange (Name a)        where getRange = getRange . ann
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "<built-in>" #-}
{-# LINE 1 "<command-line>" #-}
{-# LINE 10 "<command-line>" #-}
# 1 "/usr/include/stdc-predef.h" 1 3 4

# 17 "/usr/include/stdc-predef.h" 3 4














































{-# LINE 10 "<command-line>" #-}
{-# LINE 1 "/opt/ghc/8.6.3/lib/ghc-8.6.3/include/ghcversion.h" #-}















{-# LINE 10 "<command-line>" #-}
{-# LINE 1 "/tmp/ghc780_0/ghc_2.h" #-}






































































































































































































{-# LINE 10 "<command-line>" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
-- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp 













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

data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList







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

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

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

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

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

happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll

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

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

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



happyDoAction i tk st
        = {- nothing -}


          case action of
                0#           -> {- nothing -}
                                     happyFail (happyExpListPerState ((Happy_GHC_Exts.I# (st)) :: Int)) i tk st
                -1#          -> {- nothing -}
                                     happyAccept i tk st
                n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -}

                                                   (happyReduceArr Happy_Data_Array.! rule) i tk st
                                                   where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#))))))
                n                 -> {- nothing -}


                                     happyShift new_state i tk st
                                     where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#))
   where off    = happyAdjustOffset (indexShortOffAddr happyActOffsets st)
         off_i  = (off Happy_GHC_Exts.+#  i)
         check  = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#))
                  then EQ(indexShortOffAddr happyCheck off_i, i)
                  else False
         action
          | check     = indexShortOffAddr happyTable off_i
          | otherwise = indexShortOffAddr happyDefActions st




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




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


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






data HappyAddr = HappyA# Happy_GHC_Exts.Addr#


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

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

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

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

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

-- happyReduce is specialised for the common cases.

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

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

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

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

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

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

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

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




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

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

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

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


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




-----------------------------------------------------------------------------
-- Error recovery (0# is the error token)

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

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

-- discard a state
happyFail  0# tk old_st (HappyCons ((action)) (sts)) 
                                                (saved_tok `HappyStk` _ `HappyStk` stk) =
--      trace ("discarding state, depth " ++ show (length stk))  $
        happyDoAction 0# tk action sts ((saved_tok`HappyStk`stk))
-}

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

-- Internal happy errors:

notHappyAtAll :: a
notHappyAtAll = error "Internal Happy error\n"

-----------------------------------------------------------------------------
-- Hack to get the typechecker to accept our action functions


happyTcHack :: Happy_GHC_Exts.Int# -> a -> a
happyTcHack x y = y
{-# INLINE happyTcHack #-}


-----------------------------------------------------------------------------
-- Seq-ing.  If the --strict flag is given, then Happy emits 
--      happySeq = happyDoSeq
-- otherwise it emits
--      happySeq = happyDontSeq

happyDoSeq, happyDontSeq :: a -> b -> b
happyDoSeq   a b = a `seq` b
happyDontSeq a b = b

-----------------------------------------------------------------------------
-- Don't inline any functions from the template.  GHC has a nasty habit
-- of deciding to inline happyGoto everywhere, which increases the size of
-- the generated parser quite a bit.


{-# NOINLINE happyDoAction #-}
{-# NOINLINE happyTable #-}
{-# NOINLINE happyCheck #-}
{-# NOINLINE happyActOffsets #-}
{-# NOINLINE happyGotoOffsets #-}
{-# NOINLINE happyDefActions #-}

{-# NOINLINE happyShift #-}
{-# NOINLINE happySpecReduce_0 #-}
{-# NOINLINE happySpecReduce_1 #-}
{-# NOINLINE happySpecReduce_2 #-}
{-# NOINLINE happySpecReduce_3 #-}
{-# NOINLINE happyReduce #-}
{-# NOINLINE happyMonadReduce #-}
{-# NOINLINE happyGoto #-}
{-# NOINLINE happyFail #-}

-- end of Happy Template.