summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/backpack/DriverBkp.hs8
-rw-r--r--compiler/basicTypes/Module.hs17
-rw-r--r--compiler/ghc.cabal.in6
-rw-r--r--compiler/hieFile/HieAst.hs1713
-rw-r--r--compiler/hieFile/HieBin.hs271
-rw-r--r--compiler/hieFile/HieDebug.hs143
-rw-r--r--compiler/hieFile/HieTypes.hs503
-rw-r--r--compiler/hieFile/HieUtils.hs455
-rw-r--r--compiler/iface/MkIface.hs20
-rw-r--r--compiler/main/DriverPipeline.hs38
-rw-r--r--compiler/main/DynFlags.hs22
-rw-r--r--compiler/main/Finder.hs23
-rw-r--r--compiler/main/GhcMake.hs13
-rw-r--r--compiler/main/HscMain.hs68
-rw-r--r--compiler/main/HscTypes.hs4
-rw-r--r--compiler/typecheck/TcRnMonad.hs2
-rw-r--r--compiler/utils/Binary.hs41
-rw-r--r--docs/users_guide/8.8.1-notes.rst4
-rw-r--r--docs/users_guide/separate_compilation.rst54
-rw-r--r--docs/users_guide/using.rst3
-rw-r--r--hadrian/src/Settings/Builders/Ghc.hs4
-rw-r--r--rules/distdir-way-opts.mk2
-rw-r--r--testsuite/tests/driver/recomp018/A.hs7
-rw-r--r--testsuite/tests/driver/recomp018/B.hs6
-rw-r--r--testsuite/tests/driver/recomp018/C.hs6
-rw-r--r--testsuite/tests/driver/recomp018/Makefile30
-rw-r--r--testsuite/tests/driver/recomp018/all.T5
-rw-r--r--testsuite/tests/driver/recomp018/recomp018.stdout7
-rw-r--r--testsuite/tests/hiefile/Makefile3
-rw-r--r--testsuite/tests/hiefile/should_compile/CPP.hs26
-rw-r--r--testsuite/tests/hiefile/should_compile/CPP.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/Constructors.hs35
-rw-r--r--testsuite/tests/hiefile/should_compile/Constructors.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/all.T12
-rw-r--r--testsuite/tests/hiefile/should_compile/hie001.hs9
-rw-r--r--testsuite/tests/hiefile/should_compile/hie001.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie002.hs3869
-rw-r--r--testsuite/tests/hiefile/should_compile/hie003.hs38
-rw-r--r--testsuite/tests/hiefile/should_compile/hie003.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie004.hs28
-rw-r--r--testsuite/tests/hiefile/should_compile/hie004.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie005.hs17
-rw-r--r--testsuite/tests/hiefile/should_compile/hie005.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie006.hs22
-rw-r--r--testsuite/tests/hiefile/should_compile/hie006.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie007.hs66
-rw-r--r--testsuite/tests/hiefile/should_compile/hie007.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie008.hs34
-rw-r--r--testsuite/tests/hiefile/should_compile/hie008.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie009.hs42
-rw-r--r--testsuite/tests/hiefile/should_compile/hie009.stderr2
-rw-r--r--testsuite/tests/hiefile/should_compile/hie010.hs23
-rw-r--r--testsuite/tests/hiefile/should_compile/hie010.stderr2
-rw-r--r--testsuite/tests/regalloc/regalloc_unit_tests.hs2
-rw-r--r--utils/ghc-in-ghci/settings.ghci1
55 files changed, 7667 insertions, 57 deletions
diff --git a/compiler/backpack/DriverBkp.hs b/compiler/backpack/DriverBkp.hs
index 7784df2ff5..e10d6d1de1 100644
--- a/compiler/backpack/DriverBkp.hs
+++ b/compiler/backpack/DriverBkp.hs
@@ -677,6 +677,7 @@ summariseRequirement pn mod_name = do
env <- getBkpEnv
time <- liftIO $ getModificationUTCTime (bkp_filename env)
hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
+ hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
mod <- liftIO $ addHomeModuleToFinder hsc_env mod_name location
@@ -690,6 +691,7 @@ summariseRequirement pn mod_name = do
ms_hs_date = time,
ms_obj_date = Nothing,
ms_iface_date = hi_timestamp,
+ ms_hie_date = hie_timestamp,
ms_srcimps = [],
ms_textual_imps = extra_sig_imports,
ms_parsed_mod = Just (HsParsedModule {
@@ -765,12 +767,13 @@ hsModuleToModSummary pn hsc_src modname
HsSrcFile -> "hs")
-- DANGEROUS: bootifying can POISON the module finder cache
let location = case hsc_src of
- HsBootFile -> addBootSuffixLocn location0
+ HsBootFile -> addBootSuffixLocnOut location0
_ -> location0
-- This duplicates a pile of logic in GhcMake
env <- getBkpEnv
time <- liftIO $ getModificationUTCTime (bkp_filename env)
hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
+ hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
-- Also copied from 'getImports'
let (src_idecls, ord_idecls) = partition (ideclSource.unLoc) imps
@@ -815,7 +818,8 @@ hsModuleToModSummary pn hsc_src modname
}),
ms_hs_date = time,
ms_obj_date = Nothing, -- TODO do this, but problem: hi_timestamp is BOGUS
- ms_iface_date = hi_timestamp
+ ms_iface_date = hi_timestamp,
+ ms_hie_date = hie_timestamp
}
-- | Create a new, externally provided hashed unit id from
diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs
index 98476a3131..45fd4c19b5 100644
--- a/compiler/basicTypes/Module.hs
+++ b/compiler/basicTypes/Module.hs
@@ -112,7 +112,8 @@ module Module
-- * The ModuleLocation type
ModLocation(..),
- addBootSuffix, addBootSuffix_maybe, addBootSuffixLocn,
+ addBootSuffix, addBootSuffix_maybe,
+ addBootSuffixLocn, addBootSuffixLocnOut,
-- * Module mappings
ModuleEnv,
@@ -267,11 +268,12 @@ data ModLocation
-- yet. Always of form foo.hi, even if there is an
-- hi-boot file (we add the -boot suffix later)
- ml_obj_file :: FilePath
+ ml_obj_file :: FilePath,
-- Where the .o file is, whether or not it exists yet.
-- (might not exist either because the module hasn't
-- been compiled yet, or because it is part of a
-- package with a .a file)
+ ml_hie_file :: FilePath
} deriving Show
instance Outputable ModLocation where
@@ -302,7 +304,16 @@ addBootSuffixLocn :: ModLocation -> ModLocation
addBootSuffixLocn locn
= locn { ml_hs_file = fmap addBootSuffix (ml_hs_file locn)
, ml_hi_file = addBootSuffix (ml_hi_file locn)
- , ml_obj_file = addBootSuffix (ml_obj_file locn) }
+ , ml_obj_file = addBootSuffix (ml_obj_file locn)
+ , ml_hie_file = addBootSuffix (ml_hie_file locn) }
+
+addBootSuffixLocnOut :: ModLocation -> ModLocation
+-- ^ Add the @-boot@ suffix to all output file paths associated with the
+-- module, not including the input file itself
+addBootSuffixLocnOut locn
+ = locn { ml_hi_file = addBootSuffix (ml_hi_file locn)
+ , ml_obj_file = addBootSuffix (ml_obj_file locn)
+ , ml_hie_file = addBootSuffix (ml_hie_file locn) }
{-
************************************************************************
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index a99c6e7526..7f84cac192 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -170,6 +170,7 @@ Library
typecheck
types
utils
+ hieFile
-- we use an explicit Prelude
Default-Extensions:
@@ -179,6 +180,11 @@ Library
GhcPrelude
Exposed-Modules:
+ HieTypes
+ HieDebug
+ HieBin
+ HieUtils
+ HieAst
Ar
FileCleanup
DriverBkp
diff --git a/compiler/hieFile/HieAst.hs b/compiler/hieFile/HieAst.hs
new file mode 100644
index 0000000000..6fcc9243f8
--- /dev/null
+++ b/compiler/hieFile/HieAst.hs
@@ -0,0 +1,1713 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+module HieAst ( mkHieFile ) where
+
+import GhcPrelude
+
+import Avail ( Avails )
+import Bag ( Bag, bagToList )
+import BasicTypes
+import BooleanFormula
+import Class ( FunDep )
+import CoreUtils ( exprType )
+import ConLike ( conLikeName )
+import Config ( cProjectVersion )
+import Desugar ( deSugarExpr )
+import FieldLabel
+import HsSyn
+import HscTypes
+import Module ( ModuleName, ml_hs_file )
+import MonadUtils ( concatMapM, liftIO )
+import Name ( Name, nameSrcSpan, setNameLoc )
+import SrcLoc
+import TcHsSyn ( hsPatType )
+import Type ( Type )
+import Var ( Id, Var, setVarName, varName, varType )
+
+import HieTypes
+import HieUtils
+
+import qualified Data.Array as A
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Char8 as BSC
+import qualified Data.Map as M
+import qualified Data.Set as S
+import Data.Data ( Data, Typeable )
+import Data.List ( foldl1' )
+import Data.Maybe ( listToMaybe )
+import Control.Monad.Trans.Reader
+import Control.Monad.Trans.Class ( lift )
+
+-- These synonyms match those defined in main/GHC.hs
+type RenamedSource = ( HsGroup GhcRn, [LImportDecl GhcRn]
+ , Maybe [(LIE GhcRn, Avails)]
+ , Maybe LHsDocString )
+type TypecheckedSource = LHsBinds GhcTc
+
+
+{- Note [Name Remapping]
+The Typechecker introduces new names for mono names in AbsBinds.
+We don't care about the distinction between mono and poly bindings,
+so we replace all occurrences of the mono name with the poly name.
+-}
+newtype HieState = HieState
+ { name_remapping :: M.Map Name Id
+ }
+
+initState :: HieState
+initState = HieState M.empty
+
+class ModifyState a where -- See Note [Name Remapping]
+ addSubstitution :: a -> a -> HieState -> HieState
+
+instance ModifyState Name where
+ addSubstitution _ _ hs = hs
+
+instance ModifyState Id where
+ addSubstitution mono poly hs =
+ hs{name_remapping = M.insert (varName mono) poly (name_remapping hs)}
+
+modifyState :: ModifyState (IdP p) => [ABExport p] -> HieState -> HieState
+modifyState = foldr go id
+ where
+ go ABE{abe_poly=poly,abe_mono=mono} f = addSubstitution mono poly . f
+ go _ f = f
+
+type HieM = ReaderT HieState Hsc
+
+-- | Construct an 'HieFile' from the outputs of the typechecker.
+mkHieFile :: ModSummary -> TypecheckedSource -> RenamedSource -> Hsc HieFile
+mkHieFile ms ts rs = do
+ (asts', arr) <- getCompressedAsts ts rs
+ let Just src_file = ml_hs_file $ ms_location ms
+ src <- liftIO $ BS.readFile src_file
+ return $ HieFile
+ { hie_version = curHieVersion
+ , hie_ghc_version = BSC.pack cProjectVersion
+ , hie_hs_file = src_file
+ , hie_types = arr
+ , hie_asts = asts'
+ , hie_hs_src = src
+ }
+
+getCompressedAsts :: TypecheckedSource -> RenamedSource
+ -> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
+getCompressedAsts ts rs = do
+ asts <- enrichHie ts rs
+ return $ compressTypes asts
+
+enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
+enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
+ tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
+ rasts <- processGrp hsGrp
+ imps <- toHie $ filter (not . ideclImplicit . unLoc) imports
+ exps <- toHie $ fmap (map $ IEC Export . fst) exports
+ let spanFile children = case children of
+ [] -> mkRealSrcSpan (mkRealSrcLoc "" 1 1) (mkRealSrcLoc "" 1 1)
+ _ -> mkRealSrcSpan (realSrcSpanStart $ nodeSpan $ head children)
+ (realSrcSpanEnd $ nodeSpan $ last children)
+
+ modulify xs =
+ Node (simpleNodeInfo "Module" "Module") (spanFile xs) xs
+
+ asts = HieASTs
+ $ resolveTyVarScopes
+ $ M.map (modulify . mergeSortAsts)
+ $ M.fromListWith (++)
+ $ map (\x -> (srcSpanFile (nodeSpan x),[x])) flat_asts
+
+ flat_asts = concat
+ [ tasts
+ , rasts
+ , imps
+ , exps
+ ]
+ return asts
+ where
+ processGrp grp = concatM
+ [ toHie $ fmap (RS ModuleScope ) hs_valds grp
+ , toHie $ hs_splcds grp
+ , toHie $ hs_tyclds grp
+ , toHie $ hs_derivds grp
+ , toHie $ hs_fixds grp
+ , toHie $ hs_defds grp
+ , toHie $ hs_fords grp
+ , toHie $ hs_warnds grp
+ , toHie $ hs_annds grp
+ , toHie $ hs_ruleds grp
+ ]
+
+getRealSpan :: SrcSpan -> Maybe Span
+getRealSpan (RealSrcSpan sp) = Just sp
+getRealSpan _ = Nothing
+
+grhss_span :: GRHSs p body -> SrcSpan
+grhss_span (GRHSs _ xs bs) = foldl' combineSrcSpans (getLoc bs) (map getLoc xs)
+grhss_span (XGRHSs _) = error "XGRHS has no span"
+
+bindingsOnly :: [Context Name] -> [HieAST a]
+bindingsOnly [] = []
+bindingsOnly (C c n : xs) = case nameSrcSpan n of
+ RealSrcSpan span -> Node nodeinfo span [] : bindingsOnly xs
+ where nodeinfo = NodeInfo S.empty [] (M.singleton (Right n) info)
+ info = mempty{identInfo = S.singleton c}
+ _ -> bindingsOnly xs
+
+concatM :: Monad m => [m [a]] -> m [a]
+concatM xs = concat <$> sequence xs
+
+{- Note [Capturing Scopes and other non local information]
+toHie is a local tranformation, but scopes of bindings cannot be known locally,
+hence we have to push the relevant info down into the binding nodes.
+We use the following types (*Context and *Scoped) to wrap things and
+carry the required info
+(Maybe Span) always carries the span of the entire binding, including rhs
+-}
+data Context a = C ContextInfo a -- Used for names and bindings
+
+data RContext a = RC RecFieldContext a
+data RFContext a = RFC RecFieldContext (Maybe Span) a
+-- ^ context for record fields
+
+data IEContext a = IEC IEType a
+-- ^ context for imports/exports
+
+data BindContext a = BC BindType Scope a
+-- ^ context for imports/exports
+
+data PatSynFieldContext a = PSC (Maybe Span) a
+-- ^ context for pattern synonym fields.
+
+data SigContext a = SC SigInfo a
+-- ^ context for type signatures
+
+data SigInfo = SI SigType (Maybe Span)
+
+data SigType = BindSig | ClassSig | InstSig
+
+data RScoped a = RS Scope a
+-- ^ Scope spans over everything to the right of a, (mostly) not
+-- including a itself
+-- (Includes a in a few special cases like recursive do bindings) or
+-- let/where bindings
+
+-- | Pattern scope
+data PScoped a = PS (Maybe Span)
+ Scope -- ^ use site of the pattern
+ Scope -- ^ pattern to the right of a, not including a
+ a
+ deriving (Typeable, Data) -- Pattern Scope
+
+{- Note [TyVar Scopes]
+Due to -XScopedTypeVariables, type variables can be in scope quite far from
+their original binding. We resolve the scope of these type variables
+in a seperate pass
+-}
+data TScoped a = TS TyVarScope a -- TyVarScope
+
+data TVScoped a = TVS TyVarScope Scope a -- TyVarScope
+-- ^ First scope remains constant
+-- Second scope is used to build up the scope of a tyvar over
+-- things to its right, ala RScoped
+
+-- | Each element scopes over the elements to the right
+listScopes :: Scope -> [Located a] -> [RScoped (Located a)]
+listScopes _ [] = []
+listScopes rhsScope [pat] = [RS rhsScope pat]
+listScopes rhsScope (pat : pats) = RS sc pat : pats'
+ where
+ pats'@((RS scope p):_) = listScopes rhsScope pats
+ sc = combineScopes scope $ mkScope $ getLoc p
+
+-- | 'listScopes' specialised to 'PScoped' things
+patScopes
+ :: Maybe Span
+ -> Scope
+ -> Scope
+ -> [LPat (GhcPass p)]
+ -> [PScoped (LPat (GhcPass p))]
+patScopes rsp useScope patScope xs =
+ map (\(RS sc a) -> PS rsp useScope sc (unLoc a)) $
+ listScopes patScope (map dL xs)
+
+-- | 'listScopes' specialised to 'TVScoped' things
+tvScopes
+ :: TyVarScope
+ -> Scope
+ -> [LHsTyVarBndr a]
+ -> [TVScoped (LHsTyVarBndr a)]
+tvScopes tvScope rhsScope xs =
+ map (\(RS sc a)-> TVS tvScope sc a) $ listScopes rhsScope xs
+
+{- Note [Scoping Rules for SigPat]
+Explicitly quantified variables in pattern type signatures are not
+brought into scope in the rhs, but implicitly quantified variables
+are (HsWC and HsIB).
+This is unlike other signatures, where explicitly quantified variables
+are brought into the RHS Scope
+For example
+foo :: forall a. ...;
+foo = ... -- a is in scope here
+
+bar (x :: forall a. a -> a) = ... -- a is not in scope here
+-- ^ a is in scope here (pattern body)
+
+bax (x :: a) = ... -- a is in scope here
+Because of HsWC and HsIB pass on their scope to their children
+we must wrap the LHsType in pattern signatures in a
+Shielded explictly, so that the HsWC/HsIB scope is not passed
+on the the LHsType
+-}
+
+data Shielded a = SH Scope a -- Ignores its TScope, uses its own scope instead
+
+type family ProtectedSig a where
+ ProtectedSig GhcRn = HsWildCardBndrs GhcRn (HsImplicitBndrs
+ GhcRn
+ (Shielded (LHsType GhcRn)))
+ ProtectedSig GhcTc = NoExt
+
+class ProtectSig a where
+ protectSig :: Scope -> LHsSigWcType (NoGhcTc a) -> ProtectedSig a
+
+instance (HasLoc a) => HasLoc (Shielded a) where
+ loc (SH _ a) = loc a
+
+instance (ToHie (TScoped a)) => ToHie (TScoped (Shielded a)) where
+ toHie (TS _ (SH sc a)) = toHie (TS (ResolvedScopes [sc]) a)
+
+instance ProtectSig GhcTc where
+ protectSig _ _ = NoExt
+
+instance ProtectSig GhcRn where
+ protectSig sc (HsWC a (HsIB b sig)) =
+ HsWC a (HsIB b (SH sc sig))
+ protectSig _ _ = error "protectSig not given HsWC (HsIB)"
+
+class HasLoc a where
+ -- ^ defined so that HsImplicitBndrs and HsWildCardBndrs can
+ -- know what their implicit bindings are scoping over
+ loc :: a -> SrcSpan
+
+instance HasLoc thing => HasLoc (TScoped thing) where
+ loc (TS _ a) = loc a
+
+instance HasLoc thing => HasLoc (PScoped thing) where
+ loc (PS _ _ _ a) = loc a
+
+instance HasLoc (LHsQTyVars GhcRn) where
+ loc (HsQTvs _ vs) = loc vs
+ loc _ = noSrcSpan
+
+instance HasLoc thing => HasLoc (HsImplicitBndrs a thing) where
+ loc (HsIB _ a) = loc a
+ loc _ = noSrcSpan
+
+instance HasLoc thing => HasLoc (HsWildCardBndrs a thing) where
+ loc (HsWC _ a) = loc a
+ loc _ = noSrcSpan
+
+instance HasLoc (Located a) where
+ loc (L l _) = l
+
+instance HasLoc a => HasLoc [a] where
+ loc [] = noSrcSpan
+ loc xs = foldl1' combineSrcSpans $ map loc xs
+
+instance (HasLoc a, HasLoc b) => HasLoc (FamEqn s a b) where
+ loc (FamEqn _ a Nothing b _ c) = foldl1' combineSrcSpans [loc a, loc b, loc c]
+ loc (FamEqn _ a (Just tvs) b _ c) = foldl1' combineSrcSpans
+ [loc a, loc tvs, loc b, loc c]
+ loc _ = noSrcSpan
+
+instance HasLoc (HsDataDefn GhcRn) where
+ loc def@(HsDataDefn{}) = loc $ dd_cons def
+ -- Only used for data family instances, so we only need rhs
+ -- Most probably the rest will be unhelpful anyway
+ loc _ = noSrcSpan
+
+instance HasLoc (Pat (GhcPass a)) where
+ loc (dL -> L l _) = l
+
+-- | The main worker class
+class ToHie a where
+ toHie :: a -> HieM [HieAST Type]
+
+-- | Used to collect type info
+class Data a => HasType a where
+ getTypeNode :: a -> HieM [HieAST Type]
+
+instance (ToHie a) => ToHie [a] where
+ toHie = concatMapM toHie
+
+instance (ToHie a) => ToHie (Bag a) where
+ toHie = toHie . bagToList
+
+instance (ToHie a) => ToHie (Maybe a) where
+ toHie = maybe (pure []) toHie
+
+instance ToHie (Context (Located NoExt)) where
+ toHie _ = pure []
+
+instance ToHie (TScoped NoExt) where
+ toHie _ = pure []
+
+instance ToHie (IEContext (Located ModuleName)) where
+ toHie (IEC c (L (RealSrcSpan span) mname)) =
+ pure $ [Node (NodeInfo S.empty [] idents) span []]
+ where details = mempty{identInfo = S.singleton (IEThing c)}
+ idents = M.singleton (Left mname) details
+ toHie _ = pure []
+
+instance ToHie (Context (Located Var)) where
+ toHie c = case c of
+ C context (L (RealSrcSpan span) name')
+ -> do
+ m <- asks name_remapping
+ let name = M.findWithDefault name' (varName name') m
+ pure
+ [Node
+ (NodeInfo S.empty [] $
+ M.singleton (Right $ varName name)
+ (IdentifierDetails (Just $ varType name')
+ (S.singleton context)))
+ span
+ []]
+ _ -> pure []
+
+instance ToHie (Context (Located Name)) where
+ toHie c = case c of
+ C context (L (RealSrcSpan span) name') -> do
+ m <- asks name_remapping
+ let name = case M.lookup name' m of
+ Just var -> varName var
+ Nothing -> name'
+ pure
+ [Node
+ (NodeInfo S.empty [] $
+ M.singleton (Right name)
+ (IdentifierDetails Nothing
+ (S.singleton context)))
+ span
+ []]
+ _ -> pure []
+
+-- | Dummy instances - never called
+instance ToHie (TScoped (LHsSigWcType GhcTc)) where
+ toHie _ = pure []
+instance ToHie (TScoped (LHsWcType GhcTc)) where
+ toHie _ = pure []
+instance ToHie (SigContext (LSig GhcTc)) where
+ toHie _ = pure []
+instance ToHie (TScoped Type) where
+ toHie _ = pure []
+
+instance HasType (LHsBind GhcRn) where
+ getTypeNode (L spn bind) = makeNode bind spn
+
+instance HasType (LHsBind GhcTc) where
+ getTypeNode (L spn bind) = case bind of
+ FunBind{fun_id = name} -> makeTypeNode bind spn (varType $ unLoc name)
+ _ -> makeNode bind spn
+
+instance HasType (LPat GhcRn) where
+ getTypeNode (dL -> L spn pat) = makeNode pat spn
+
+instance HasType (LPat GhcTc) where
+ getTypeNode (dL -> L spn opat) = makeTypeNode opat spn (hsPatType opat)
+
+instance HasType (LHsExpr GhcRn) where
+ getTypeNode (L spn e) = makeNode e spn
+
+instance HasType (LHsExpr GhcTc) where
+ getTypeNode e@(L spn e') = lift $ do
+ hs_env <- Hsc $ \e w -> return (e,w)
+ (_,mbe) <- liftIO $ deSugarExpr hs_env e
+ case mbe of
+ Just te -> makeTypeNode e' spn (exprType te)
+ Nothing -> makeNode e' spn
+
+instance ( ToHie (Context (Located (IdP a)))
+ , ToHie (MatchGroup a (LHsExpr a))
+ , ToHie (PScoped (LPat a))
+ , ToHie (GRHSs a (LHsExpr a))
+ , ToHie (LHsExpr a)
+ , ToHie (Located (PatSynBind a a))
+ , HasType (LHsBind a)
+ , ModifyState (IdP a)
+ , Data (HsBind a)
+ ) => ToHie (BindContext (LHsBind a)) where
+ toHie (BC context scope b@(L span bind)) =
+ concatM $ getTypeNode b : case bind of
+ FunBind{fun_id = name, fun_matches = matches} ->
+ [ toHie $ C (ValBind context scope $ getRealSpan span) name
+ , toHie matches
+ ]
+ PatBind{pat_lhs = lhs, pat_rhs = rhs} ->
+ [ toHie $ PS (getRealSpan span) scope NoScope lhs
+ , toHie rhs
+ ]
+ VarBind{var_rhs = expr} ->
+ [ toHie expr
+ ]
+ AbsBinds{abs_exports = xs, abs_binds = binds} ->
+ [ local (modifyState xs) $ -- Note [Name Remapping]
+ toHie $ fmap (BC context scope) binds
+ ]
+ PatSynBind _ psb ->
+ [ toHie $ L span psb -- PatSynBinds only occur at the top level
+ ]
+ XHsBindsLR _ -> []
+
+instance ( ToHie (LMatch a body)
+ ) => ToHie (MatchGroup a body) where
+ toHie mg = concatM $ case mg of
+ MG{ mg_alts = (L span alts) , mg_origin = FromSource } ->
+ [ pure $ locOnly span
+ , toHie alts
+ ]
+ MG{} -> []
+ XMatchGroup _ -> []
+
+instance ( ToHie (Context (Located (IdP a)))
+ , ToHie (PScoped (LPat a))
+ , ToHie (HsPatSynDir a)
+ ) => ToHie (Located (PatSynBind a a)) where
+ toHie (L sp psb) = concatM $ case psb of
+ PSB{psb_id=var, psb_args=dets, psb_def=pat, psb_dir=dir} ->
+ [ toHie $ C (Decl PatSynDec $ getRealSpan sp) var
+ , toHie $ toBind dets
+ , toHie $ PS Nothing lhsScope NoScope pat
+ , toHie dir
+ ]
+ where
+ lhsScope = combineScopes varScope detScope
+ varScope = mkLScope var
+ detScope = case dets of
+ (PrefixCon args) -> foldr combineScopes NoScope $ map mkLScope args
+ (InfixCon a b) -> combineScopes (mkLScope a) (mkLScope b)
+ (RecCon r) -> foldr go NoScope r
+ go (RecordPatSynField a b) c = combineScopes c
+ $ combineScopes (mkLScope a) (mkLScope b)
+ detSpan = case detScope of
+ LocalScope a -> Just a
+ _ -> Nothing
+ toBind (PrefixCon args) = PrefixCon $ map (C Use) args
+ toBind (InfixCon a b) = InfixCon (C Use a) (C Use b)
+ toBind (RecCon r) = RecCon $ map (PSC detSpan) r
+ XPatSynBind _ -> []
+
+instance ( ToHie (MatchGroup a (LHsExpr a))
+ ) => ToHie (HsPatSynDir a) where
+ toHie dir = case dir of
+ ExplicitBidirectional mg -> toHie mg
+ _ -> pure []
+
+instance ( a ~ GhcPass p
+ , ToHie body
+ , ToHie (HsMatchContext (NameOrRdrName (IdP a)))
+ , ToHie (PScoped (LPat a))
+ , ToHie (GRHSs a body)
+ , Data (Match a body)
+ ) => ToHie (LMatch (GhcPass p) body) where
+ toHie (L span m ) = concatM $ makeNode m span : case m of
+ Match{m_ctxt=mctx, m_pats = pats, m_grhss = grhss } ->
+ [ toHie mctx
+ , let rhsScope = mkScope $ grhss_span grhss
+ in toHie $ patScopes Nothing rhsScope NoScope pats
+ , toHie grhss
+ ]
+ XMatch _ -> []
+
+instance ( ToHie (Context (Located a))
+ ) => ToHie (HsMatchContext a) where
+ toHie (FunRhs{mc_fun=name}) = toHie $ C MatchBind name
+ toHie (StmtCtxt a) = toHie a
+ toHie _ = pure []
+
+instance ( ToHie (HsMatchContext a)
+ ) => ToHie (HsStmtContext a) where
+ toHie (PatGuard a) = toHie a
+ toHie (ParStmtCtxt a) = toHie a
+ toHie (TransStmtCtxt a) = toHie a
+ toHie _ = pure []
+
+instance ( a ~ GhcPass p
+ , ToHie (Context (Located (IdP a)))
+ , ToHie (RContext (HsRecFields a (PScoped (LPat a))))
+ , ToHie (LHsExpr a)
+ , ToHie (TScoped (LHsSigWcType a))
+ , ProtectSig a
+ , ToHie (TScoped (ProtectedSig a))
+ , HasType (LPat a)
+ , Data (HsSplice a)
+ ) => ToHie (PScoped (LPat (GhcPass p))) where
+ toHie (PS rsp scope pscope lpat@(dL -> L ospan opat)) =
+ concatM $ getTypeNode lpat : case opat of
+ WildPat _ ->
+ []
+ VarPat _ lname ->
+ [ toHie $ C (PatternBind scope pscope rsp) lname
+ ]
+ LazyPat _ p ->
+ [ toHie $ PS rsp scope pscope p
+ ]
+ AsPat _ lname pat ->
+ [ toHie $ C (PatternBind scope
+ (combineScopes (mkLScope (dL pat)) pscope)
+ rsp)
+ lname
+ , toHie $ PS rsp scope pscope pat
+ ]
+ ParPat _ pat ->
+ [ toHie $ PS rsp scope pscope pat
+ ]
+ BangPat _ pat ->
+ [ toHie $ PS rsp scope pscope pat
+ ]
+ ListPat _ pats ->
+ [ toHie $ patScopes rsp scope pscope pats
+ ]
+ TuplePat _ pats _ ->
+ [ toHie $ patScopes rsp scope pscope pats
+ ]
+ SumPat _ pat _ _ ->
+ [ toHie $ PS rsp scope pscope pat
+ ]
+ ConPatIn c dets ->
+ [ toHie $ C Use c
+ , toHie $ contextify dets
+ ]
+ ConPatOut {pat_con = con, pat_args = dets}->
+ [ toHie $ C Use $ fmap conLikeName con
+ , toHie $ contextify dets
+ ]
+ ViewPat _ expr pat ->
+ [ toHie expr
+ , toHie $ PS rsp scope pscope pat
+ ]
+ SplicePat _ sp ->
+ [ toHie $ L ospan sp
+ ]
+ LitPat _ _ ->
+ []
+ NPat _ _ _ _ ->
+ []
+ NPlusKPat _ n _ _ _ _ ->
+ [ toHie $ C (PatternBind scope pscope rsp) n
+ ]
+ SigPat _ pat sig ->
+ [ toHie $ PS rsp scope pscope pat
+ , let cscope = mkLScope (dL pat) in
+ toHie $ TS (ResolvedScopes [cscope, scope, pscope])
+ (protectSig @a cscope sig)
+ -- See Note [Scoping Rules for SigPat]
+ ]
+ CoPat _ _ _ _ ->
+ []
+ XPat _ -> []
+ where
+ contextify (PrefixCon args) = PrefixCon $ patScopes rsp scope pscope args
+ contextify (InfixCon a b) = InfixCon a' b'
+ where [a', b'] = patScopes rsp scope pscope [a,b]
+ contextify (RecCon r) = RecCon $ RC RecFieldMatch $ contextify_rec r
+ contextify_rec (HsRecFields fds a) = HsRecFields (map go scoped_fds) a
+ where
+ go (RS fscope (L spn (HsRecField lbl pat pun))) =
+ L spn $ HsRecField lbl (PS rsp scope fscope pat) pun
+ scoped_fds = listScopes pscope fds
+
+instance ( ToHie body
+ , ToHie (LGRHS a body)
+ , ToHie (RScoped (LHsLocalBinds a))
+ ) => ToHie (GRHSs a body) where
+ toHie grhs = concatM $ case grhs of
+ GRHSs _ grhss binds ->
+ [ toHie grhss
+ , toHie $ RS (mkScope $ grhss_span grhs) binds
+ ]
+ XGRHSs _ -> []
+
+instance ( ToHie (Located body)
+ , ToHie (RScoped (GuardLStmt a))
+ , Data (GRHS a (Located body))
+ ) => ToHie (LGRHS a (Located body)) where
+ toHie (L span g) = concatM $ makeNode g span : case g of
+ GRHS _ guards body ->
+ [ toHie $ listScopes (mkLScope body) guards
+ , toHie body
+ ]
+ XGRHS _ -> []
+
+instance ( a ~ GhcPass p
+ , ToHie (Context (Located (IdP a)))
+ , HasType (LHsExpr a)
+ , ToHie (PScoped (LPat a))
+ , ToHie (MatchGroup a (LHsExpr a))
+ , ToHie (LGRHS a (LHsExpr a))
+ , ToHie (RContext (HsRecordBinds a))
+ , ToHie (RFContext (Located (AmbiguousFieldOcc a)))
+ , ToHie (ArithSeqInfo a)
+ , ToHie (LHsCmdTop a)
+ , ToHie (RScoped (GuardLStmt a))
+ , ToHie (RScoped (LHsLocalBinds a))
+ , ToHie (TScoped (LHsWcType (NoGhcTc a)))
+ , ToHie (TScoped (LHsSigWcType (NoGhcTc a)))
+ , Data (HsExpr a)
+ , Data (HsSplice a)
+ , Data (HsTupArg a)
+ , Data (AmbiguousFieldOcc a)
+ ) => ToHie (LHsExpr (GhcPass p)) where
+ toHie e@(L mspan oexpr) = concatM $ getTypeNode e : case oexpr of
+ HsVar _ (L _ var) ->
+ [ toHie $ C Use (L mspan var)
+ -- Patch up var location since typechecker removes it
+ ]
+ HsUnboundVar _ _ ->
+ []
+ HsConLikeOut _ con ->
+ [ toHie $ C Use $ L mspan $ conLikeName con
+ ]
+ HsRecFld _ fld ->
+ [ toHie $ RFC RecFieldOcc Nothing (L mspan fld)
+ ]
+ HsOverLabel _ _ _ -> []
+ HsIPVar _ _ -> []
+ HsOverLit _ _ -> []
+ HsLit _ _ -> []
+ HsLam _ mg ->
+ [ toHie mg
+ ]
+ HsLamCase _ mg ->
+ [ toHie mg
+ ]
+ HsApp _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ HsAppType _ expr sig ->
+ [ toHie expr
+ , toHie $ TS (ResolvedScopes []) sig
+ ]
+ OpApp _ a b c ->
+ [ toHie a
+ , toHie b
+ , toHie c
+ ]
+ NegApp _ a _ ->
+ [ toHie a
+ ]
+ HsPar _ a ->
+ [ toHie a
+ ]
+ SectionL _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ SectionR _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ ExplicitTuple _ args _ ->
+ [ toHie args
+ ]
+ ExplicitSum _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsCase _ expr matches ->
+ [ toHie expr
+ , toHie matches
+ ]
+ HsIf _ _ a b c ->
+ [ toHie a
+ , toHie b
+ , toHie c
+ ]
+ HsMultiIf _ grhss ->
+ [ toHie grhss
+ ]
+ HsLet _ binds expr ->
+ [ toHie $ RS (mkLScope expr) binds
+ , toHie expr
+ ]
+ HsDo _ _ (L ispan stmts) ->
+ [ pure $ locOnly ispan
+ , toHie $ listScopes NoScope stmts
+ ]
+ ExplicitList _ _ exprs ->
+ [ toHie exprs
+ ]
+ RecordCon {rcon_con_name = name, rcon_flds = binds}->
+ [ toHie $ C Use name
+ , toHie $ RC RecFieldAssign $ binds
+ ]
+ RecordUpd {rupd_expr = expr, rupd_flds = upds}->
+ [ toHie expr
+ , toHie $ map (RC RecFieldAssign) upds
+ ]
+ ExprWithTySig _ expr sig ->
+ [ toHie expr
+ , toHie $ TS (ResolvedScopes [mkLScope expr]) sig
+ ]
+ ArithSeq _ _ info ->
+ [ toHie info
+ ]
+ HsSCC _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsCoreAnn _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsProc _ pat cmdtop ->
+ [ toHie $ PS Nothing (mkLScope cmdtop) NoScope pat
+ , toHie cmdtop
+ ]
+ HsStatic _ expr ->
+ [ toHie expr
+ ]
+ HsArrApp _ a b _ _ ->
+ [ toHie a
+ , toHie b
+ ]
+ HsArrForm _ expr _ cmds ->
+ [ toHie expr
+ , toHie cmds
+ ]
+ HsTick _ _ expr ->
+ [ toHie expr
+ ]
+ HsBinTick _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsTickPragma _ _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsWrap _ _ a ->
+ [ toHie $ L mspan a
+ ]
+ HsBracket _ b ->
+ [ toHie b
+ ]
+ HsRnBracketOut _ b p ->
+ [ toHie b
+ , toHie p
+ ]
+ HsTcBracketOut _ b p ->
+ [ toHie b
+ , toHie p
+ ]
+ HsSpliceE _ x ->
+ [ toHie $ L mspan x
+ ]
+ EWildPat _ -> []
+ EAsPat _ a b ->
+ [ toHie $ C Use a
+ , toHie b
+ ]
+ EViewPat _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ ELazyPat _ a ->
+ [ toHie a
+ ]
+ XExpr _ -> []
+
+instance ( a ~ GhcPass p
+ , ToHie (LHsExpr a)
+ , Data (HsTupArg a)
+ ) => ToHie (LHsTupArg (GhcPass p)) where
+ toHie (L span arg) = concatM $ makeNode arg span : case arg of
+ Present _ expr ->
+ [ toHie expr
+ ]
+ Missing _ -> []
+ XTupArg _ -> []
+
+instance ( a ~ GhcPass p
+ , ToHie (PScoped (LPat a))
+ , ToHie (LHsExpr a)
+ , ToHie (SigContext (LSig a))
+ , ToHie (RScoped (LHsLocalBinds a))
+ , ToHie (RScoped (ApplicativeArg a))
+ , ToHie (Located body)
+ , Data (StmtLR a a (Located body))
+ , Data (StmtLR a a (Located (HsExpr a)))
+ ) => ToHie (RScoped (LStmt (GhcPass p) (Located body))) where
+ toHie (RS scope (L span stmt)) = concatM $ makeNode stmt span : case stmt of
+ LastStmt _ body _ _ ->
+ [ toHie body
+ ]
+ BindStmt _ pat body _ _ ->
+ [ toHie $ PS (getRealSpan $ getLoc body) scope NoScope pat
+ , toHie body
+ ]
+ ApplicativeStmt _ stmts _ ->
+ [ concatMapM (toHie . RS scope . snd) stmts
+ ]
+ BodyStmt _ body _ _ ->
+ [ toHie body
+ ]
+ LetStmt _ binds ->
+ [ toHie $ RS scope binds
+ ]
+ ParStmt _ parstmts _ _ ->
+ [ concatMapM (\(ParStmtBlock _ stmts _ _) ->
+ toHie $ listScopes NoScope stmts)
+ parstmts
+ ]
+ TransStmt {trS_stmts = stmts, trS_using = using, trS_by = by} ->
+ [ toHie $ listScopes scope stmts
+ , toHie using
+ , toHie by
+ ]
+ RecStmt {recS_stmts = stmts} ->
+ [ toHie $ map (RS $ combineScopes scope (mkScope span)) stmts
+ ]
+ XStmtLR _ -> []
+
+instance ( ToHie (LHsExpr a)
+ , ToHie (PScoped (LPat a))
+ , ToHie (BindContext (LHsBind a))
+ , ToHie (SigContext (LSig a))
+ , ToHie (RScoped (HsValBindsLR a a))
+ , Data (HsLocalBinds a)
+ ) => ToHie (RScoped (LHsLocalBinds a)) where
+ toHie (RS scope (L sp binds)) = concatM $ makeNode binds sp : case binds of
+ EmptyLocalBinds _ -> []
+ HsIPBinds _ _ -> []
+ HsValBinds _ valBinds ->
+ [ toHie $ RS (combineScopes scope $ mkScope sp)
+ valBinds
+ ]
+ XHsLocalBindsLR _ -> []
+
+instance ( ToHie (BindContext (LHsBind a))
+ , ToHie (SigContext (LSig a))
+ , ToHie (RScoped (XXValBindsLR a a))
+ ) => ToHie (RScoped (HsValBindsLR a a)) where
+ toHie (RS sc v) = concatM $ case v of
+ ValBinds _ binds sigs ->
+ [ toHie $ fmap (BC RegularBind sc) binds
+ , toHie $ fmap (SC (SI BindSig Nothing)) sigs
+ ]
+ XValBindsLR x -> [ toHie $ RS sc x ]
+
+instance ToHie (RScoped (NHsValBindsLR GhcTc)) where
+ toHie (RS sc (NValBinds binds sigs)) = concatM $
+ [ toHie (concatMap (map (BC RegularBind sc) . bagToList . snd) binds)
+ , toHie $ fmap (SC (SI BindSig Nothing)) sigs
+ ]
+instance ToHie (RScoped (NHsValBindsLR GhcRn)) where
+ toHie (RS sc (NValBinds binds sigs)) = concatM $
+ [ toHie (concatMap (map (BC RegularBind sc) . bagToList . snd) binds)
+ , toHie $ fmap (SC (SI BindSig Nothing)) sigs
+ ]
+
+instance ( ToHie (RContext (LHsRecField a arg))
+ ) => ToHie (RContext (HsRecFields a arg)) where
+ toHie (RC c (HsRecFields fields _)) = toHie $ map (RC c) fields
+
+instance ( ToHie (RFContext (Located label))
+ , ToHie arg
+ , HasLoc arg
+ , Data label
+ , Data arg
+ ) => ToHie (RContext (LHsRecField' label arg)) where
+ toHie (RC c (L span recfld)) = concatM $ makeNode recfld span : case recfld of
+ HsRecField label expr _ ->
+ [ toHie $ RFC c (getRealSpan $ loc expr) label
+ , toHie expr
+ ]
+
+removeDefSrcSpan :: Name -> Name
+removeDefSrcSpan n = setNameLoc n noSrcSpan
+
+instance ToHie (RFContext (LFieldOcc GhcRn)) where
+ toHie (RFC c rhs (L nspan f)) = concatM $ case f of
+ FieldOcc name _ ->
+ [ toHie $ C (RecField c rhs) (L nspan $ removeDefSrcSpan name)
+ ]
+ XFieldOcc _ -> []
+
+instance ToHie (RFContext (LFieldOcc GhcTc)) where
+ toHie (RFC c rhs (L nspan f)) = concatM $ case f of
+ FieldOcc var _ ->
+ let var' = setVarName var (removeDefSrcSpan $ varName var)
+ in [ toHie $ C (RecField c rhs) (L nspan var')
+ ]
+ XFieldOcc _ -> []
+
+instance ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) where
+ toHie (RFC c rhs (L nspan afo)) = concatM $ case afo of
+ Unambiguous name _ ->
+ [ toHie $ C (RecField c rhs) $ L nspan $ removeDefSrcSpan name
+ ]
+ Ambiguous _name _ ->
+ [ ]
+ XAmbiguousFieldOcc _ -> []
+
+instance ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) where
+ toHie (RFC c rhs (L nspan afo)) = concatM $ case afo of
+ Unambiguous var _ ->
+ let var' = setVarName var (removeDefSrcSpan $ varName var)
+ in [ toHie $ C (RecField c rhs) (L nspan var')
+ ]
+ Ambiguous var _ ->
+ let var' = setVarName var (removeDefSrcSpan $ varName var)
+ in [ toHie $ C (RecField c rhs) (L nspan var')
+ ]
+ XAmbiguousFieldOcc _ -> []
+
+instance ( a ~ GhcPass p
+ , ToHie (PScoped (LPat a))
+ , ToHie (BindContext (LHsBind a))
+ , ToHie (LHsExpr a)
+ , ToHie (SigContext (LSig a))
+ , ToHie (RScoped (HsValBindsLR a a))
+ , Data (StmtLR a a (Located (HsExpr a)))
+ , Data (HsLocalBinds a)
+ ) => ToHie (RScoped (ApplicativeArg (GhcPass p))) where
+ toHie (RS sc (ApplicativeArgOne _ pat expr _)) = concatM
+ [ toHie $ PS Nothing sc NoScope pat
+ , toHie expr
+ ]
+ toHie (RS sc (ApplicativeArgMany _ stmts _ pat)) = concatM
+ [ toHie $ listScopes NoScope stmts
+ , toHie $ PS Nothing sc NoScope pat
+ ]
+ toHie (RS _ (XApplicativeArg _)) = pure []
+
+instance (ToHie arg, ToHie rec) => ToHie (HsConDetails arg rec) where
+ toHie (PrefixCon args) = toHie args
+ toHie (RecCon rec) = toHie rec
+ toHie (InfixCon a b) = concatM [ toHie a, toHie b]
+
+instance ( ToHie (LHsCmd a)
+ , Data (HsCmdTop a)
+ ) => ToHie (LHsCmdTop a) where
+ toHie (L span top) = concatM $ makeNode top span : case top of
+ HsCmdTop _ cmd ->
+ [ toHie cmd
+ ]
+ XCmdTop _ -> []
+
+instance ( a ~ GhcPass p
+ , ToHie (PScoped (LPat a))
+ , ToHie (BindContext (LHsBind a))
+ , ToHie (LHsExpr a)
+ , ToHie (MatchGroup a (LHsCmd a))
+ , ToHie (SigContext (LSig a))
+ , ToHie (RScoped (HsValBindsLR a a))
+ , Data (HsCmd a)
+ , Data (HsCmdTop a)
+ , Data (StmtLR a a (Located (HsCmd a)))
+ , Data (HsLocalBinds a)
+ , Data (StmtLR a a (Located (HsExpr a)))
+ ) => ToHie (LHsCmd (GhcPass p)) where
+ toHie (L span cmd) = concatM $ makeNode cmd span : case cmd of
+ HsCmdArrApp _ a b _ _ ->
+ [ toHie a
+ , toHie b
+ ]
+ HsCmdArrForm _ a _ _ cmdtops ->
+ [ toHie a
+ , toHie cmdtops
+ ]
+ HsCmdApp _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ HsCmdLam _ mg ->
+ [ toHie mg
+ ]
+ HsCmdPar _ a ->
+ [ toHie a
+ ]
+ HsCmdCase _ expr alts ->
+ [ toHie expr
+ , toHie alts
+ ]
+ HsCmdIf _ _ a b c ->
+ [ toHie a
+ , toHie b
+ , toHie c
+ ]
+ HsCmdLet _ binds cmd' ->
+ [ toHie $ RS (mkLScope cmd') binds
+ , toHie cmd'
+ ]
+ HsCmdDo _ (L ispan stmts) ->
+ [ pure $ locOnly ispan
+ , toHie $ listScopes NoScope stmts
+ ]
+ HsCmdWrap _ _ _ -> []
+ XCmd _ -> []
+
+instance ToHie (TyClGroup GhcRn) where
+ toHie (TyClGroup _ classes roles instances) = concatM
+ [ toHie classes
+ , toHie roles
+ , toHie instances
+ ]
+ toHie (XTyClGroup _) = pure []
+
+instance ToHie (LTyClDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ FamDecl {tcdFam = fdecl} ->
+ [ toHie (L span fdecl)
+ ]
+ SynDecl {tcdLName = name, tcdTyVars = vars, tcdRhs = typ} ->
+ [ toHie $ C (Decl SynDec $ getRealSpan span) name
+ , toHie $ TS (ResolvedScopes [mkScope $ getLoc typ]) vars
+ , toHie typ
+ ]
+ DataDecl {tcdLName = name, tcdTyVars = vars, tcdDataDefn = defn} ->
+ [ toHie $ C (Decl DataDec $ getRealSpan span) name
+ , toHie $ TS (ResolvedScopes [quant_scope, rhs_scope]) vars
+ , toHie defn
+ ]
+ where
+ quant_scope = mkLScope $ dd_ctxt defn
+ rhs_scope = sig_sc `combineScopes` con_sc `combineScopes` deriv_sc
+ sig_sc = maybe NoScope mkLScope $ dd_kindSig defn
+ con_sc = foldr combineScopes NoScope $ map mkLScope $ dd_cons defn
+ deriv_sc = mkLScope $ dd_derivs defn
+ ClassDecl { tcdCtxt = context
+ , tcdLName = name
+ , tcdTyVars = vars
+ , tcdFDs = deps
+ , tcdSigs = sigs
+ , tcdMeths = meths
+ , tcdATs = typs
+ , tcdATDefs = deftyps
+ } ->
+ [ toHie $ C (Decl ClassDec $ getRealSpan span) name
+ , toHie context
+ , toHie $ TS (ResolvedScopes [context_scope, rhs_scope]) vars
+ , toHie deps
+ , toHie $ map (SC $ SI ClassSig $ getRealSpan span) sigs
+ , toHie $ fmap (BC InstanceBind ModuleScope) meths
+ , toHie typs
+ , concatMapM (pure . locOnly . getLoc) deftyps
+ , toHie $ map (go . unLoc) deftyps
+ ]
+ where
+ context_scope = mkLScope context
+ rhs_scope = foldl1' combineScopes $ map mkScope
+ [ loc deps, loc sigs, loc (bagToList meths), loc typs, loc deftyps]
+
+ go :: TyFamDefltEqn GhcRn
+ -> FamEqn GhcRn (TScoped (LHsQTyVars GhcRn)) (LHsType GhcRn)
+ go (FamEqn a var bndrs pat b rhs) =
+ FamEqn a var bndrs (TS (ResolvedScopes [mkLScope rhs]) pat) b rhs
+ go (XFamEqn NoExt) = XFamEqn NoExt
+ XTyClDecl _ -> []
+
+instance ToHie (LFamilyDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ FamilyDecl _ info name vars _ sig inj ->
+ [ toHie $ C (Decl FamDec $ getRealSpan span) name
+ , toHie $ TS (ResolvedScopes [rhsSpan]) vars
+ , toHie info
+ , toHie $ RS injSpan sig
+ , toHie inj
+ ]
+ where
+ rhsSpan = sigSpan `combineScopes` injSpan
+ sigSpan = mkScope $ getLoc sig
+ injSpan = maybe NoScope (mkScope . getLoc) inj
+ XFamilyDecl _ -> []
+
+instance ToHie (FamilyInfo GhcRn) where
+ toHie (ClosedTypeFamily (Just eqns)) = concatM $
+ [ concatMapM (pure . locOnly . getLoc) eqns
+ , toHie $ map go eqns
+ ]
+ where
+ go (L l ib) = TS (ResolvedScopes [mkScope l]) ib
+ toHie _ = pure []
+
+instance ToHie (RScoped (LFamilyResultSig GhcRn)) where
+ toHie (RS sc (L span sig)) = concatM $ makeNode sig span : case sig of
+ NoSig _ ->
+ []
+ KindSig _ k ->
+ [ toHie k
+ ]
+ TyVarSig _ bndr ->
+ [ toHie $ TVS (ResolvedScopes [sc]) NoScope bndr
+ ]
+ XFamilyResultSig _ -> []
+
+instance ToHie (Located (FunDep (Located Name))) where
+ toHie (L span fd@(lhs, rhs)) = concatM $
+ [ makeNode fd span
+ , toHie $ map (C Use) lhs
+ , toHie $ map (C Use) rhs
+ ]
+
+instance (ToHie pats, ToHie rhs, HasLoc pats, HasLoc rhs)
+ => ToHie (TScoped (FamEqn GhcRn pats rhs)) where
+ toHie (TS _ f) = toHie f
+
+instance ( ToHie pats
+ , ToHie rhs
+ , HasLoc pats
+ , HasLoc rhs
+ ) => ToHie (FamEqn GhcRn pats rhs) where
+ toHie fe@(FamEqn _ var tybndrs pats _ rhs) = concatM $
+ [ toHie $ C (Decl InstDec $ getRealSpan $ loc fe) var
+ , toHie $ fmap (tvScopes (ResolvedScopes []) scope) tybndrs
+ , toHie pats
+ , toHie rhs
+ ]
+ where scope = combineScopes patsScope rhsScope
+ patsScope = mkScope (loc pats)
+ rhsScope = mkScope (loc rhs)
+ toHie (XFamEqn _) = pure []
+
+instance ToHie (LInjectivityAnn GhcRn) where
+ toHie (L span ann) = concatM $ makeNode ann span : case ann of
+ InjectivityAnn lhs rhs ->
+ [ toHie $ C Use lhs
+ , toHie $ map (C Use) rhs
+ ]
+
+instance ToHie (HsDataDefn GhcRn) where
+ toHie (HsDataDefn _ _ ctx _ mkind cons derivs) = concatM
+ [ toHie ctx
+ , toHie mkind
+ , toHie cons
+ , toHie derivs
+ ]
+ toHie (XHsDataDefn _) = pure []
+
+instance ToHie (HsDeriving GhcRn) where
+ toHie (L span clauses) = concatM
+ [ pure $ locOnly span
+ , toHie clauses
+ ]
+
+instance ToHie (LHsDerivingClause GhcRn) where
+ toHie (L span cl) = concatM $ makeNode cl span : case cl of
+ HsDerivingClause _ strat (L ispan tys) ->
+ [ toHie strat
+ , pure $ locOnly ispan
+ , toHie $ map (TS (ResolvedScopes [])) tys
+ ]
+ XHsDerivingClause _ -> []
+
+instance ToHie (Located (DerivStrategy GhcRn)) where
+ toHie (L span strat) = concatM $ makeNode strat span : case strat of
+ StockStrategy -> []
+ AnyclassStrategy -> []
+ NewtypeStrategy -> []
+ ViaStrategy s -> [ toHie $ TS (ResolvedScopes []) s ]
+
+instance ToHie (Located OverlapMode) where
+ toHie (L span _) = pure $ locOnly span
+
+instance ToHie (LConDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ ConDeclGADT { con_names = names, con_qvars = qvars
+ , con_mb_cxt = ctx, con_args = args, con_res_ty = typ } ->
+ [ toHie $ map (C (Decl ConDec $ getRealSpan span)) names
+ , toHie $ TS (ResolvedScopes [ctxScope, rhsScope]) qvars
+ , toHie ctx
+ , toHie args
+ , toHie typ
+ ]
+ where
+ rhsScope = combineScopes argsScope tyScope
+ ctxScope = maybe NoScope mkLScope ctx
+ argsScope = condecl_scope args
+ tyScope = mkLScope typ
+ ConDeclH98 { con_name = name, con_ex_tvs = qvars
+ , con_mb_cxt = ctx, con_args = dets } ->
+ [ toHie $ C (Decl ConDec $ getRealSpan span) name
+ , toHie $ tvScopes (ResolvedScopes []) rhsScope qvars
+ , toHie ctx
+ , toHie dets
+ ]
+ where
+ rhsScope = combineScopes ctxScope argsScope
+ ctxScope = maybe NoScope mkLScope ctx
+ argsScope = condecl_scope dets
+ XConDecl _ -> []
+ where condecl_scope args = case args of
+ PrefixCon xs -> foldr combineScopes NoScope $ map mkLScope xs
+ InfixCon a b -> combineScopes (mkLScope a) (mkLScope b)
+ RecCon x -> mkLScope x
+
+instance ToHie (Located [LConDeclField GhcRn]) where
+ toHie (L span decls) = concatM $
+ [ pure $ locOnly span
+ , toHie decls
+ ]
+
+instance ( HasLoc thing
+ , ToHie (TScoped thing)
+ ) => ToHie (TScoped (HsImplicitBndrs GhcRn thing)) where
+ toHie (TS sc (HsIB ibrn a)) = concatM $
+ [ pure $ bindingsOnly $ map (C $ TyVarBind (mkScope span) sc) ibrn
+ , toHie $ TS sc a
+ ]
+ where span = loc a
+ toHie (TS _ (XHsImplicitBndrs _)) = pure []
+
+instance ( HasLoc thing
+ , ToHie (TScoped thing)
+ ) => ToHie (TScoped (HsWildCardBndrs GhcRn thing)) where
+ toHie (TS sc (HsWC names a)) = concatM $
+ [ pure $ bindingsOnly $ map (C $ TyVarBind (mkScope span) sc) names
+ , toHie $ TS sc a
+ ]
+ where span = loc a
+ toHie (TS _ (XHsWildCardBndrs _)) = pure []
+
+instance ToHie (SigContext (LSig GhcRn)) where
+ toHie (SC (SI styp msp) (L sp sig)) = concatM $ makeNode sig sp : case sig of
+ TypeSig _ names typ ->
+ [ toHie $ map (C TyDecl) names
+ , toHie $ TS (UnresolvedScope (map unLoc names) Nothing) typ
+ ]
+ PatSynSig _ names typ ->
+ [ toHie $ map (C TyDecl) names
+ , toHie $ TS (UnresolvedScope (map unLoc names) Nothing) typ
+ ]
+ ClassOpSig _ _ names typ ->
+ [ case styp of
+ ClassSig -> toHie $ map (C $ ClassTyDecl $ getRealSpan sp) names
+ _ -> toHie $ map (C $ TyDecl) names
+ , toHie $ TS (UnresolvedScope (map unLoc names) msp) typ
+ ]
+ IdSig _ _ -> []
+ FixSig _ fsig ->
+ [ toHie $ L sp fsig
+ ]
+ InlineSig _ name _ ->
+ [ toHie $ (C Use) name
+ ]
+ SpecSig _ name typs _ ->
+ [ toHie $ (C Use) name
+ , toHie $ map (TS (ResolvedScopes [])) typs
+ ]
+ SpecInstSig _ _ typ ->
+ [ toHie $ TS (ResolvedScopes []) typ
+ ]
+ MinimalSig _ _ form ->
+ [ toHie form
+ ]
+ SCCFunSig _ _ name mtxt ->
+ [ toHie $ (C Use) name
+ , pure $ maybe [] (locOnly . getLoc) mtxt
+ ]
+ CompleteMatchSig _ _ (L ispan names) typ ->
+ [ pure $ locOnly ispan
+ , toHie $ map (C Use) names
+ , toHie $ fmap (C Use) typ
+ ]
+ XSig _ -> []
+
+instance ToHie (LHsType GhcRn) where
+ toHie x = toHie $ TS (ResolvedScopes []) x
+
+instance ToHie (TScoped (LHsType GhcRn)) where
+ toHie (TS tsc (L span t)) = concatM $ makeNode t span : case t of
+ HsForAllTy _ bndrs body ->
+ [ toHie $ tvScopes tsc (mkScope $ getLoc body) bndrs
+ , toHie body
+ ]
+ HsQualTy _ ctx body ->
+ [ toHie ctx
+ , toHie body
+ ]
+ HsTyVar _ _ var ->
+ [ toHie $ C Use var
+ ]
+ HsAppTy _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ HsFunTy _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ HsListTy _ a ->
+ [ toHie a
+ ]
+ HsTupleTy _ _ tys ->
+ [ toHie tys
+ ]
+ HsSumTy _ tys ->
+ [ toHie tys
+ ]
+ HsOpTy _ a op b ->
+ [ toHie a
+ , toHie $ C Use op
+ , toHie b
+ ]
+ HsParTy _ a ->
+ [ toHie a
+ ]
+ HsIParamTy _ ip ty ->
+ [ toHie ip
+ , toHie ty
+ ]
+ HsKindSig _ a b ->
+ [ toHie a
+ , toHie b
+ ]
+ HsSpliceTy _ a ->
+ [ toHie $ L span a
+ ]
+ HsDocTy _ a _ ->
+ [ toHie a
+ ]
+ HsBangTy _ _ ty ->
+ [ toHie ty
+ ]
+ HsRecTy _ fields ->
+ [ toHie fields
+ ]
+ HsExplicitListTy _ _ tys ->
+ [ toHie tys
+ ]
+ HsExplicitTupleTy _ tys ->
+ [ toHie tys
+ ]
+ HsTyLit _ _ -> []
+ HsWildCardTy e ->
+ [ toHie e
+ ]
+ HsStarTy _ _ -> []
+ XHsType _ -> []
+
+instance ToHie HsWildCardInfo where
+ toHie (AnonWildCard name) = toHie $ C Use name
+
+instance ToHie (TVScoped (LHsTyVarBndr GhcRn)) where
+ toHie (TVS tsc sc (L span bndr)) = concatM $ makeNode bndr span : case bndr of
+ UserTyVar _ var ->
+ [ toHie $ C (TyVarBind sc tsc) var
+ ]
+ KindedTyVar _ var kind ->
+ [ toHie $ C (TyVarBind sc tsc) var
+ , toHie kind
+ ]
+ XTyVarBndr _ -> []
+
+instance ToHie (TScoped (LHsQTyVars GhcRn)) where
+ toHie (TS sc (HsQTvs (HsQTvsRn implicits _) vars)) = concatM $
+ [ pure $ bindingsOnly bindings
+ , toHie $ tvScopes sc NoScope vars
+ ]
+ where
+ varLoc = loc vars
+ bindings = map (C $ TyVarBind (mkScope varLoc) sc) implicits
+ toHie (TS _ (XLHsQTyVars _)) = pure []
+
+instance ToHie (LHsContext GhcRn) where
+ toHie (L span tys) = concatM $
+ [ pure $ locOnly span
+ , toHie tys
+ ]
+
+instance ToHie (LConDeclField GhcRn) where
+ toHie (L span field) = concatM $ makeNode field span : case field of
+ ConDeclField _ fields typ _ ->
+ [ toHie $ map (RFC RecFieldDecl (getRealSpan $ loc typ)) fields
+ , toHie typ
+ ]
+ XConDeclField _ -> []
+
+instance ToHie (LHsExpr a) => ToHie (ArithSeqInfo a) where
+ toHie (From expr) = toHie expr
+ toHie (FromThen a b) = concatM $
+ [ toHie a
+ , toHie b
+ ]
+ toHie (FromTo a b) = concatM $
+ [ toHie a
+ , toHie b
+ ]
+ toHie (FromThenTo a b c) = concatM $
+ [ toHie a
+ , toHie b
+ , toHie c
+ ]
+
+instance ToHie (LSpliceDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ SpliceDecl _ splice _ ->
+ [ toHie splice
+ ]
+ XSpliceDecl _ -> []
+
+instance ToHie (HsBracket a) where
+ toHie _ = pure []
+
+instance ToHie PendingRnSplice where
+ toHie _ = pure []
+
+instance ToHie PendingTcSplice where
+ toHie _ = pure []
+
+instance ToHie (LBooleanFormula (Located Name)) where
+ toHie (L span form) = concatM $ makeNode form span : case form of
+ Var a ->
+ [ toHie $ C Use a
+ ]
+ And forms ->
+ [ toHie forms
+ ]
+ Or forms ->
+ [ toHie forms
+ ]
+ Parens f ->
+ [ toHie f
+ ]
+
+instance ToHie (Located HsIPName) where
+ toHie (L span e) = makeNode e span
+
+instance ( ToHie (LHsExpr a)
+ , Data (HsSplice a)
+ ) => ToHie (Located (HsSplice a)) where
+ toHie (L span sp) = concatM $ makeNode sp span : case sp of
+ HsTypedSplice _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsUntypedSplice _ _ _ expr ->
+ [ toHie expr
+ ]
+ HsQuasiQuote _ _ _ ispan _ ->
+ [ pure $ locOnly ispan
+ ]
+ HsSpliced _ _ _ ->
+ []
+ XSplice _ -> []
+
+instance ToHie (LRoleAnnotDecl GhcRn) where
+ toHie (L span annot) = concatM $ makeNode annot span : case annot of
+ RoleAnnotDecl _ var roles ->
+ [ toHie $ C Use var
+ , concatMapM (pure . locOnly . getLoc) roles
+ ]
+ XRoleAnnotDecl _ -> []
+
+instance ToHie (LInstDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ ClsInstD _ d ->
+ [ toHie $ L span d
+ ]
+ DataFamInstD _ d ->
+ [ toHie $ L span d
+ ]
+ TyFamInstD _ d ->
+ [ toHie $ L span d
+ ]
+ XInstDecl _ -> []
+
+instance ToHie (LClsInstDecl GhcRn) where
+ toHie (L span decl) = concatM
+ [ toHie $ TS (ResolvedScopes [mkScope span]) $ cid_poly_ty decl
+ , toHie $ fmap (BC InstanceBind ModuleScope) $ cid_binds decl
+ , toHie $ map (SC $ SI InstSig $ getRealSpan span) $ cid_sigs decl
+ , pure $ concatMap (locOnly . getLoc) $ cid_tyfam_insts decl
+ , toHie $ cid_tyfam_insts decl
+ , pure $ concatMap (locOnly . getLoc) $ cid_datafam_insts decl
+ , toHie $ cid_datafam_insts decl
+ , toHie $ cid_overlap_mode decl
+ ]
+
+instance ToHie (LDataFamInstDecl GhcRn) where
+ toHie (L sp (DataFamInstDecl d)) = toHie $ TS (ResolvedScopes [mkScope sp]) d
+
+instance ToHie (LTyFamInstDecl GhcRn) where
+ toHie (L sp (TyFamInstDecl d)) = toHie $ TS (ResolvedScopes [mkScope sp]) d
+
+instance ToHie (Context a)
+ => ToHie (PatSynFieldContext (RecordPatSynField a)) where
+ toHie (PSC sp (RecordPatSynField a b)) = concatM $
+ [ toHie $ C (RecField RecFieldDecl sp) a
+ , toHie $ C Use b
+ ]
+
+instance ToHie (LDerivDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ DerivDecl _ typ strat overlap ->
+ [ toHie $ TS (ResolvedScopes []) typ
+ , toHie strat
+ , toHie overlap
+ ]
+ XDerivDecl _ -> []
+
+instance ToHie (LFixitySig GhcRn) where
+ toHie (L span sig) = concatM $ makeNode sig span : case sig of
+ FixitySig _ vars _ ->
+ [ toHie $ map (C Use) vars
+ ]
+ XFixitySig _ -> []
+
+instance ToHie (LDefaultDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ DefaultDecl _ typs ->
+ [ toHie typs
+ ]
+ XDefaultDecl _ -> []
+
+instance ToHie (LForeignDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ ForeignImport {fd_name = name, fd_sig_ty = sig, fd_fi = fi} ->
+ [ toHie $ C (ValBind RegularBind ModuleScope $ getRealSpan span) name
+ , toHie $ TS (ResolvedScopes []) sig
+ , toHie fi
+ ]
+ ForeignExport {fd_name = name, fd_sig_ty = sig, fd_fe = fe} ->
+ [ toHie $ C Use name
+ , toHie $ TS (ResolvedScopes []) sig
+ , toHie fe
+ ]
+ XForeignDecl _ -> []
+
+instance ToHie ForeignImport where
+ toHie (CImport (L a _) (L b _) _ _ (L c _)) = pure $ concat $
+ [ locOnly a
+ , locOnly b
+ , locOnly c
+ ]
+
+instance ToHie ForeignExport where
+ toHie (CExport (L a _) (L b _)) = pure $ concat $
+ [ locOnly a
+ , locOnly b
+ ]
+
+instance ToHie (LWarnDecls GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ Warnings _ _ warnings ->
+ [ toHie warnings
+ ]
+ XWarnDecls _ -> []
+
+instance ToHie (LWarnDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ Warning _ vars _ ->
+ [ toHie $ map (C Use) vars
+ ]
+ XWarnDecl _ -> []
+
+instance ToHie (LAnnDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ HsAnnotation _ _ prov expr ->
+ [ toHie prov
+ , toHie expr
+ ]
+ XAnnDecl _ -> []
+
+instance ToHie (Context (Located a)) => ToHie (AnnProvenance a) where
+ toHie (ValueAnnProvenance a) = toHie $ C Use a
+ toHie (TypeAnnProvenance a) = toHie $ C Use a
+ toHie ModuleAnnProvenance = pure []
+
+instance ToHie (LRuleDecls GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ HsRules _ _ rules ->
+ [ toHie rules
+ ]
+ XRuleDecls _ -> []
+
+instance ToHie (LRuleDecl GhcRn) where
+ toHie (L _ (XRuleDecl _)) = pure []
+ toHie (L span r@(HsRule _ rname _ tybndrs bndrs exprA exprB)) = concatM
+ [ makeNode r span
+ , pure $ locOnly $ getLoc rname
+ , toHie $ fmap (tvScopes (ResolvedScopes []) scope) tybndrs
+ , toHie $ map (RS $ mkScope span) bndrs
+ , toHie exprA
+ , toHie exprB
+ ]
+ where scope = bndrs_sc `combineScopes` exprA_sc `combineScopes` exprB_sc
+ bndrs_sc = maybe NoScope mkLScope (listToMaybe bndrs)
+ exprA_sc = mkLScope exprA
+ exprB_sc = mkLScope exprB
+
+instance ToHie (RScoped (LRuleBndr GhcRn)) where
+ toHie (RS sc (L span bndr)) = concatM $ makeNode bndr span : case bndr of
+ RuleBndr _ var ->
+ [ toHie $ C (ValBind RegularBind sc Nothing) var
+ ]
+ RuleBndrSig _ var typ ->
+ [ toHie $ C (ValBind RegularBind sc Nothing) var
+ , toHie $ TS (ResolvedScopes [sc]) typ
+ ]
+ XRuleBndr _ -> []
+
+instance ToHie (LImportDecl GhcRn) where
+ toHie (L span decl) = concatM $ makeNode decl span : case decl of
+ ImportDecl { ideclName = name, ideclAs = as, ideclHiding = hidden } ->
+ [ toHie $ IEC Import name
+ , toHie $ fmap (IEC ImportAs) as
+ , maybe (pure []) goIE hidden
+ ]
+ XImportDecl _ -> []
+ where
+ goIE (hiding, (L sp liens)) = concatM $
+ [ pure $ locOnly sp
+ , toHie $ map (IEC c) liens
+ ]
+ where
+ c = if hiding then ImportHiding else Import
+
+instance ToHie (IEContext (LIE GhcRn)) where
+ toHie (IEC c (L span ie)) = concatM $ makeNode ie span : case ie of
+ IEVar _ n ->
+ [ toHie $ IEC c n
+ ]
+ IEThingAbs _ n ->
+ [ toHie $ IEC c n
+ ]
+ IEThingAll _ n ->
+ [ toHie $ IEC c n
+ ]
+ IEThingWith _ n _ ns flds ->
+ [ toHie $ IEC c n
+ , toHie $ map (IEC c) ns
+ , toHie $ map (IEC c) flds
+ ]
+ IEModuleContents _ n ->
+ [ toHie $ IEC c n
+ ]
+ IEGroup _ _ _ -> []
+ IEDoc _ _ -> []
+ IEDocNamed _ _ -> []
+ XIE _ -> []
+
+instance ToHie (IEContext (LIEWrappedName Name)) where
+ toHie (IEC c (L span iewn)) = concatM $ makeNode iewn span : case iewn of
+ IEName n ->
+ [ toHie $ C (IEThing c) n
+ ]
+ IEPattern p ->
+ [ toHie $ C (IEThing c) p
+ ]
+ IEType n ->
+ [ toHie $ C (IEThing c) n
+ ]
+
+instance ToHie (IEContext (Located (FieldLbl Name))) where
+ toHie (IEC c (L span lbl)) = concatM $ makeNode lbl span : case lbl of
+ FieldLabel _ _ n ->
+ [ toHie $ C (IEThing c) $ L span n
+ ]
diff --git a/compiler/hieFile/HieBin.hs b/compiler/hieFile/HieBin.hs
new file mode 100644
index 0000000000..fa33936f40
--- /dev/null
+++ b/compiler/hieFile/HieBin.hs
@@ -0,0 +1,271 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module HieBin ( readHieFile, writeHieFile, HieName(..), toHieName ) where
+
+import GhcPrelude
+
+import Binary
+import BinIface ( getDictFastString )
+import FastMutInt
+import FastString ( FastString )
+import Module ( Module )
+import Name
+import NameCache
+import Outputable
+import PrelInfo
+import SrcLoc
+import UniqSupply ( takeUniqFromSupply )
+import Unique
+import UniqFM
+
+import qualified Data.Array as A
+import Data.IORef
+import Data.List ( mapAccumR )
+import Data.Word ( Word32 )
+import Control.Monad ( replicateM )
+
+
+-- | `Name`'s get converted into `HieName`'s before being written into @.hie@
+-- files. See 'toHieName' and 'fromHieName' for logic on how to convert between
+-- these two types.
+data HieName
+ = ExternalName !Module !OccName !SrcSpan
+ | LocalName !OccName !SrcSpan
+ | KnownKeyName !Unique
+ deriving (Eq)
+
+instance Ord HieName where
+ compare (ExternalName a b c) (ExternalName d e f) = compare (a,b,c) (d,e,f)
+ compare (LocalName a b) (LocalName c d) = compare (a,b) (c,d)
+ compare (KnownKeyName a) (KnownKeyName b) = nonDetCmpUnique a b
+ -- Not actually non determinstic as it is a KnownKey
+ compare ExternalName{} _ = LT
+ compare LocalName{} ExternalName{} = GT
+ compare LocalName{} _ = LT
+ compare KnownKeyName{} _ = GT
+
+instance Outputable HieName where
+ ppr (ExternalName m n sp) = text "ExternalName" <+> ppr m <+> ppr n <+> ppr sp
+ ppr (LocalName n sp) = text "LocalName" <+> ppr n <+> ppr sp
+ ppr (KnownKeyName u) = text "KnownKeyName" <+> ppr u
+
+
+data HieSymbolTable = HieSymbolTable
+ { hie_symtab_next :: !FastMutInt
+ , hie_symtab_map :: !(IORef (UniqFM (Int, HieName)))
+ }
+
+data HieDictionary = HieDictionary
+ { hie_dict_next :: !FastMutInt -- The next index to use
+ , hie_dict_map :: !(IORef (UniqFM (Int,FastString))) -- indexed by FastString
+ }
+
+initBinMemSize :: Int
+initBinMemSize = 1024*1024
+
+writeHieFile :: Binary a => FilePath -> a -> IO ()
+writeHieFile filename hiefile = do
+ bh0 <- openBinMem initBinMemSize
+
+ -- remember where the dictionary pointer will go
+ dict_p_p <- tellBin bh0
+ put_ bh0 dict_p_p
+
+ -- remember where the symbol table pointer will go
+ symtab_p_p <- tellBin bh0
+ put_ bh0 symtab_p_p
+
+ -- Make some intial state
+ symtab_next <- newFastMutInt
+ writeFastMutInt symtab_next 0
+ symtab_map <- newIORef emptyUFM
+ let hie_symtab = HieSymbolTable {
+ hie_symtab_next = symtab_next,
+ hie_symtab_map = symtab_map }
+ dict_next_ref <- newFastMutInt
+ writeFastMutInt dict_next_ref 0
+ dict_map_ref <- newIORef emptyUFM
+ let hie_dict = HieDictionary {
+ hie_dict_next = dict_next_ref,
+ hie_dict_map = dict_map_ref }
+
+ -- put the main thing
+ let bh = setUserData bh0 $ newWriteState (putName hie_symtab)
+ (putName hie_symtab)
+ (putFastString hie_dict)
+ put_ bh hiefile
+
+ -- write the symtab pointer at the front of the file
+ symtab_p <- tellBin bh
+ putAt bh symtab_p_p symtab_p
+ seekBin bh symtab_p
+
+ -- write the symbol table itself
+ symtab_next' <- readFastMutInt symtab_next
+ symtab_map' <- readIORef symtab_map
+ putSymbolTable bh symtab_next' symtab_map'
+
+ -- write the dictionary pointer at the fornt of the file
+ dict_p <- tellBin bh
+ putAt bh dict_p_p dict_p
+ seekBin bh dict_p
+
+ -- write the dictionary itself
+ dict_next <- readFastMutInt dict_next_ref
+ dict_map <- readIORef dict_map_ref
+ putDictionary bh dict_next dict_map
+
+ -- and send the result to the file
+ writeBinMem bh filename
+ return ()
+
+readHieFile :: Binary a => NameCache -> FilePath -> IO (a, NameCache)
+readHieFile nc file = do
+ bh0 <- readBinMem file
+
+ dict <- get_dictionary bh0
+
+ -- read the symbol table so we are capable of reading the actual data
+ (bh1, nc') <- do
+ let bh1 = setUserData bh0 $ newReadState (error "getSymtabName")
+ (getDictFastString dict)
+ (nc', symtab) <- get_symbol_table bh1
+ let bh1' = setUserData bh1
+ $ newReadState (getSymTabName symtab)
+ (getDictFastString dict)
+ return (bh1', nc')
+
+ -- load the actual data
+ hiefile <- get bh1
+ return (hiefile, nc')
+ where
+ get_dictionary bin_handle = do
+ dict_p <- get bin_handle
+ data_p <- tellBin bin_handle
+ seekBin bin_handle dict_p
+ dict <- getDictionary bin_handle
+ seekBin bin_handle data_p
+ return dict
+
+ get_symbol_table bh1 = do
+ symtab_p <- get bh1
+ data_p' <- tellBin bh1
+ seekBin bh1 symtab_p
+ (nc', symtab) <- getSymbolTable bh1 nc
+ seekBin bh1 data_p'
+ return (nc', symtab)
+
+putFastString :: HieDictionary -> BinHandle -> FastString -> IO ()
+putFastString HieDictionary { hie_dict_next = j_r,
+ hie_dict_map = out_r} bh f
+ = do
+ out <- readIORef out_r
+ let unique = getUnique f
+ case lookupUFM out unique of
+ Just (j, _) -> put_ bh (fromIntegral j :: Word32)
+ Nothing -> do
+ j <- readFastMutInt j_r
+ put_ bh (fromIntegral j :: Word32)
+ writeFastMutInt j_r (j + 1)
+ writeIORef out_r $! addToUFM out unique (j, f)
+
+putSymbolTable :: BinHandle -> Int -> UniqFM (Int,HieName) -> IO ()
+putSymbolTable bh next_off symtab = do
+ put_ bh next_off
+ let names = A.elems (A.array (0,next_off-1) (nonDetEltsUFM symtab))
+ mapM_ (putHieName bh) names
+
+getSymbolTable :: BinHandle -> NameCache -> IO (NameCache, SymbolTable)
+getSymbolTable bh namecache = do
+ sz <- get bh
+ od_names <- replicateM sz (getHieName bh)
+ let arr = A.listArray (0,sz-1) names
+ (namecache', names) = mapAccumR fromHieName namecache od_names
+ return (namecache', arr)
+
+getSymTabName :: SymbolTable -> BinHandle -> IO Name
+getSymTabName st bh = do
+ i :: Word32 <- get bh
+ return $ st A.! (fromIntegral i)
+
+putName :: HieSymbolTable -> BinHandle -> Name -> IO ()
+putName (HieSymbolTable next ref) bh name = do
+ symmap <- readIORef ref
+ case lookupUFM symmap name of
+ Just (off, ExternalName mod occ (UnhelpfulSpan _))
+ | isGoodSrcSpan (nameSrcSpan name) -> do
+ let hieName = ExternalName mod occ (nameSrcSpan name)
+ writeIORef ref $! addToUFM symmap name (off, hieName)
+ put_ bh (fromIntegral off :: Word32)
+ Just (off, LocalName _occ span)
+ | notLocal (toHieName name) || nameSrcSpan name /= span -> do
+ writeIORef ref $! addToUFM symmap name (off, toHieName name)
+ put_ bh (fromIntegral off :: Word32)
+ Just (off, _) -> put_ bh (fromIntegral off :: Word32)
+ Nothing -> do
+ off <- readFastMutInt next
+ writeFastMutInt next (off+1)
+ writeIORef ref $! addToUFM symmap name (off, toHieName name)
+ put_ bh (fromIntegral off :: Word32)
+
+ where
+ notLocal :: HieName -> Bool
+ notLocal LocalName{} = False
+ notLocal _ = True
+
+
+-- ** Converting to and from `HieName`'s
+
+toHieName :: Name -> HieName
+toHieName name
+ | isKnownKeyName name = KnownKeyName (nameUnique name)
+ | isExternalName name = ExternalName (nameModule name)
+ (nameOccName name)
+ (nameSrcSpan name)
+ | otherwise = LocalName (nameOccName name) (nameSrcSpan name)
+
+fromHieName :: NameCache -> HieName -> (NameCache, Name)
+fromHieName nc (ExternalName mod occ span) =
+ let cache = nsNames nc
+ in case lookupOrigNameCache cache mod occ of
+ Just name -> (nc, name)
+ Nothing ->
+ let (uniq, us) = takeUniqFromSupply (nsUniqs nc)
+ name = mkExternalName uniq mod occ span
+ new_cache = extendNameCache cache mod occ name
+ in ( nc{ nsUniqs = us, nsNames = new_cache }, name )
+fromHieName nc (LocalName occ span) =
+ let (uniq, us) = takeUniqFromSupply (nsUniqs nc)
+ name = mkInternalName uniq occ span
+ in ( nc{ nsUniqs = us }, name )
+fromHieName nc (KnownKeyName u) = case lookupKnownKeyName u of
+ Nothing -> pprPanic "fromHieName:unknown known-key unique"
+ (ppr (unpkUnique u))
+ Just n -> (nc, n)
+
+-- ** Reading and writing `HieName`'s
+
+putHieName :: BinHandle -> HieName -> IO ()
+putHieName bh (ExternalName mod occ span) = do
+ putByte bh 0
+ put_ bh (mod, occ, span)
+putHieName bh (LocalName occName span) = do
+ putByte bh 1
+ put_ bh (occName, span)
+putHieName bh (KnownKeyName uniq) = do
+ putByte bh 2
+ put_ bh $ unpkUnique uniq
+
+getHieName :: BinHandle -> IO HieName
+getHieName bh = do
+ t <- getByte bh
+ case t of
+ 0 -> do
+ (modu, occ, span) <- get bh
+ return $ ExternalName modu occ span
+ 1 -> do
+ (occ, span) <- get bh
+ return $ LocalName occ span
+ 2 -> do
+ (c,i) <- get bh
+ return $ KnownKeyName $ mkUnique c i
+ _ -> panic "HieBin.getHieName: invalid tag"
diff --git a/compiler/hieFile/HieDebug.hs b/compiler/hieFile/HieDebug.hs
new file mode 100644
index 0000000000..7896cf7720
--- /dev/null
+++ b/compiler/hieFile/HieDebug.hs
@@ -0,0 +1,143 @@
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE FlexibleContexts #-}
+module HieDebug where
+
+import GhcPrelude
+
+import SrcLoc
+import Module
+import FastString
+import Outputable
+
+import HieTypes
+import HieBin
+import HieUtils
+
+import qualified Data.Map as M
+import qualified Data.Set as S
+import Data.Function ( on )
+import Data.List ( sortOn )
+import Data.Foldable ( toList )
+
+ppHies :: Outputable a => (HieASTs a) -> SDoc
+ppHies (HieASTs asts) = M.foldrWithKey go "" asts
+ where
+ go k a rest = vcat $
+ [ "File: " <> ppr k
+ , ppHie a
+ , rest
+ ]
+
+ppHie :: Outputable a => HieAST a -> SDoc
+ppHie = go 0
+ where
+ go n (Node inf sp children) = hang header n rest
+ where
+ rest = vcat $ map (go (n+2)) children
+ header = hsep
+ [ "Node"
+ , ppr sp
+ , ppInfo inf
+ ]
+
+ppInfo :: Outputable a => NodeInfo a -> SDoc
+ppInfo ni = hsep
+ [ ppr $ toList $ nodeAnnotations ni
+ , ppr $ nodeType ni
+ , ppr $ M.toList $ nodeIdentifiers ni
+ ]
+
+type Diff a = a -> a -> [SDoc]
+
+diffFile :: Diff HieFile
+diffFile = diffAsts eqDiff `on` (getAsts . hie_asts)
+
+diffAsts :: (Outputable a, Eq a) => Diff a -> Diff (M.Map FastString (HieAST a))
+diffAsts f = diffList (diffAst f) `on` M.elems
+
+diffAst :: (Outputable a, Eq a) => Diff a -> Diff (HieAST a)
+diffAst diffType (Node info1 span1 xs1) (Node info2 span2 xs2) =
+ infoDiff ++ spanDiff ++ diffList (diffAst diffType) xs1 xs2
+ where
+ spanDiff
+ | span1 /= span2 = [hsep ["Spans", ppr span1, "and", ppr span2, "differ"]]
+ | otherwise = []
+ infoDiff
+ = (diffList eqDiff `on` (S.toAscList . nodeAnnotations)) info1 info2
+ ++ (diffList diffType `on` nodeType) info1 info2
+ ++ (diffIdents `on` nodeIdentifiers) info1 info2
+ diffIdents a b = (diffList diffIdent `on` normalizeIdents) a b
+ diffIdent (a,b) (c,d) = diffName a c
+ ++ eqDiff b d
+ diffName (Right a) (Right b) = case (a,b) of
+ (ExternalName m o _, ExternalName m' o' _) -> eqDiff (m,o) (m',o')
+ (LocalName o _, ExternalName _ o' _) -> eqDiff o o'
+ _ -> eqDiff a b
+ diffName a b = eqDiff a b
+
+type DiffIdent = Either ModuleName HieName
+
+normalizeIdents :: NodeIdentifiers a -> [(DiffIdent,IdentifierDetails a)]
+normalizeIdents = sortOn fst . map (first toHieName) . M.toList
+ where
+ first f (a,b) = (fmap f a, b)
+
+diffList :: Diff a -> Diff [a]
+diffList f xs ys
+ | length xs == length ys = concat $ zipWith f xs ys
+ | otherwise = ["length of lists doesn't match"]
+
+eqDiff :: (Outputable a, Eq a) => Diff a
+eqDiff a b
+ | a == b = []
+ | otherwise = [hsep [ppr a, "and", ppr b, "do not match"]]
+
+validAst :: HieAST a -> Either SDoc ()
+validAst (Node _ span children) = do
+ checkContainment children
+ checkSorted children
+ mapM_ validAst children
+ where
+ checkSorted [] = return ()
+ checkSorted [_] = return ()
+ checkSorted (x:y:xs)
+ | nodeSpan x `leftOf` nodeSpan y = checkSorted (y:xs)
+ | otherwise = Left $ hsep
+ [ ppr $ nodeSpan x
+ , "is not to the left of"
+ , ppr $ nodeSpan y
+ ]
+ checkContainment [] = return ()
+ checkContainment (x:xs)
+ | span `containsSpan` (nodeSpan x) = checkContainment xs
+ | otherwise = Left $ hsep
+ [ ppr $ span
+ , "does not contain"
+ , ppr $ nodeSpan x
+ ]
+
+-- | Look for any identifiers which occur outside of their supposed scopes.
+-- Returns a list of error messages.
+validateScopes :: M.Map FastString (HieAST a) -> [SDoc]
+validateScopes asts = M.foldrWithKey (\k a b -> valid k a ++ b) [] refMap
+ where
+ refMap = generateReferencesMap asts
+ valid (Left _) _ = []
+ valid (Right n) refs = concatMap inScope refs
+ where
+ mapRef = foldMap getScopeFromContext . identInfo . snd
+ scopes = case foldMap mapRef refs of
+ Just xs -> xs
+ Nothing -> []
+ inScope (sp, dets)
+ | definedInAsts asts n
+ && any isOccurrence (identInfo dets)
+ = case scopes of
+ [] -> []
+ _ -> if any (`scopeContainsSpan` sp) scopes
+ then []
+ else return $ hsep $
+ [ "Name", ppr n, "at position", ppr sp
+ , "doesn't occur in calculated scope", ppr scopes]
+ | otherwise = []
diff --git a/compiler/hieFile/HieTypes.hs b/compiler/hieFile/HieTypes.hs
new file mode 100644
index 0000000000..c20887f045
--- /dev/null
+++ b/compiler/hieFile/HieTypes.hs
@@ -0,0 +1,503 @@
+{-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module HieTypes where
+
+import GhcPrelude
+
+import Binary
+import FastString ( FastString )
+import IfaceType
+import Module ( ModuleName )
+import Name ( Name )
+import Outputable hiding ( (<>) )
+import SrcLoc ( RealSrcSpan )
+
+import qualified Data.Array as A
+import qualified Data.Map as M
+import qualified Data.Set as S
+import Data.ByteString ( ByteString )
+import Data.Data ( Typeable, Data )
+import Data.Semigroup ( Semigroup(..) )
+import Data.Word ( Word8 )
+import Control.Applicative ( (<|>) )
+
+type Span = RealSrcSpan
+
+-- | Current version of @.hie@ files
+curHieVersion :: Word8
+curHieVersion = 0
+
+{- |
+GHC builds up a wealth of information about Haskell source as it compiles it.
+@.hie@ files are a way of persisting some of this information to disk so that
+external tools that need to work with haskell source don't need to parse,
+typecheck, and rename all over again. These files contain:
+
+ * a simplified AST
+
+ * nodes are annotated with source positions and types
+ * identifiers are annotated with scope information
+
+ * the raw bytes of the initial Haskell source
+
+Besides saving compilation cycles, @.hie@ files also offer a more stable
+interface than the GHC API.
+-}
+data HieFile = HieFile
+ { hie_version :: Word8
+ -- ^ version of the HIE format
+
+ , hie_ghc_version :: ByteString
+ -- ^ Version of GHC that produced this file
+
+ , hie_hs_file :: FilePath
+ -- ^ Initial Haskell source file path
+
+ , hie_types :: A.Array TypeIndex HieTypeFlat
+ -- ^ Types referenced in the 'hie_asts'.
+ --
+ -- See Note [Efficient serialization of redundant type info]
+
+ , hie_asts :: HieASTs TypeIndex
+ -- ^ Type-annotated abstract syntax trees
+
+ , hie_hs_src :: ByteString
+ -- ^ Raw bytes of the initial Haskell source
+ }
+
+instance Binary HieFile where
+ put_ bh hf = do
+ put_ bh $ hie_version hf
+ put_ bh $ hie_ghc_version hf
+ put_ bh $ hie_hs_file hf
+ put_ bh $ hie_types hf
+ put_ bh $ hie_asts hf
+ put_ bh $ hie_hs_src hf
+
+ get bh = HieFile
+ <$> get bh
+ <*> get bh
+ <*> get bh
+ <*> get bh
+ <*> get bh
+ <*> get bh
+
+
+{-
+Note [Efficient serialization of redundant type info]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The type information in .hie files is highly repetitive and redundant. For
+example, consider the expression
+
+ const True 'a'
+
+There is a lot of shared structure between the types of subterms:
+
+ * const True 'a' :: Bool
+ * const True :: Char -> Bool
+ * const :: Bool -> Char -> Bool
+
+Since all 3 of these types need to be stored in the .hie file, it is worth
+making an effort to deduplicate this shared structure. The trick is to define
+a new data type that is a flattened version of 'Type':
+
+ data HieType a = HAppTy a a -- data Type = AppTy Type Type
+ | HFunTy a a -- | FunTy Type Type
+ | ...
+
+ type TypeIndex = Int
+
+Types in the final AST are stored in an 'A.Array TypeIndex (HieType TypeIndex)',
+where the 'TypeIndex's in the 'HieType' are references to other elements of the
+array. Types recovered from GHC are deduplicated and stored in this compressed
+form with sharing of subtrees.
+-}
+
+type TypeIndex = Int
+
+-- | A flattened version of 'Type'.
+--
+-- See Note [Efficient serialization of redundant type info]
+data HieType a
+ = HTyVarTy Name
+ | HAppTy a (HieArgs a)
+ | HTyConApp IfaceTyCon (HieArgs a)
+ | HForAllTy ((Name, a),ArgFlag) a
+ | HFunTy a a
+ | HQualTy a a -- ^ type with constraint: @t1 => t2@ (see 'IfaceDFunTy')
+ | HLitTy IfaceTyLit
+ | HCastTy a
+ | HCoercionTy
+ deriving (Functor, Foldable, Traversable, Eq)
+
+type HieTypeFlat = HieType TypeIndex
+
+-- | Roughly isomorphic to the original core 'Type'.
+newtype HieTypeFix = Roll (HieType (HieTypeFix))
+
+instance Binary (HieType TypeIndex) where
+ put_ bh (HTyVarTy n) = do
+ putByte bh 0
+ put_ bh n
+ put_ bh (HAppTy a b) = do
+ putByte bh 1
+ put_ bh a
+ put_ bh b
+ put_ bh (HTyConApp n xs) = do
+ putByte bh 2
+ put_ bh n
+ put_ bh xs
+ put_ bh (HForAllTy bndr a) = do
+ putByte bh 3
+ put_ bh bndr
+ put_ bh a
+ put_ bh (HFunTy a b) = do
+ putByte bh 4
+ put_ bh a
+ put_ bh b
+ put_ bh (HQualTy a b) = do
+ putByte bh 5
+ put_ bh a
+ put_ bh b
+ put_ bh (HLitTy l) = do
+ putByte bh 6
+ put_ bh l
+ put_ bh (HCastTy a) = do
+ putByte bh 7
+ put_ bh a
+ put_ bh (HCoercionTy) = putByte bh 8
+
+ get bh = do
+ (t :: Word8) <- get bh
+ case t of
+ 0 -> HTyVarTy <$> get bh
+ 1 -> HAppTy <$> get bh <*> get bh
+ 2 -> HTyConApp <$> get bh <*> get bh
+ 3 -> HForAllTy <$> get bh <*> get bh
+ 4 -> HFunTy <$> get bh <*> get bh
+ 5 -> HQualTy <$> get bh <*> get bh
+ 6 -> HLitTy <$> get bh
+ 7 -> HCastTy <$> get bh
+ 8 -> return HCoercionTy
+ _ -> panic "Binary (HieArgs Int): invalid tag"
+
+
+-- | A list of type arguments along with their respective visibilities (ie. is
+-- this an argument that would return 'True' for 'isVisibleArgFlag'?).
+newtype HieArgs a = HieArgs [(Bool,a)]
+ deriving (Functor, Foldable, Traversable, Eq)
+
+instance Binary (HieArgs TypeIndex) where
+ put_ bh (HieArgs xs) = put_ bh xs
+ get bh = HieArgs <$> get bh
+
+-- | Mapping from filepaths (represented using 'FastString') to the
+-- corresponding AST
+newtype HieASTs a = HieASTs { getAsts :: (M.Map FastString (HieAST a)) }
+ deriving (Functor, Foldable, Traversable)
+
+instance Binary (HieASTs TypeIndex) where
+ put_ bh asts = put_ bh $ M.toAscList $ getAsts asts
+ get bh = HieASTs <$> fmap M.fromDistinctAscList (get bh)
+
+
+data HieAST a =
+ Node
+ { nodeInfo :: NodeInfo a
+ , nodeSpan :: Span
+ , nodeChildren :: [HieAST a]
+ } deriving (Functor, Foldable, Traversable)
+
+instance Binary (HieAST TypeIndex) where
+ put_ bh ast = do
+ put_ bh $ nodeInfo ast
+ put_ bh $ nodeSpan ast
+ put_ bh $ nodeChildren ast
+
+ get bh = Node
+ <$> get bh
+ <*> get bh
+ <*> get bh
+
+
+-- | The information stored in one AST node.
+--
+-- The type parameter exists to provide flexibility in representation of types
+-- (see Note [Efficient serialization of redundant type info]).
+data NodeInfo a = NodeInfo
+ { nodeAnnotations :: S.Set (FastString,FastString)
+ -- ^ (name of the AST node constructor, name of the AST node Type)
+
+ , nodeType :: [a]
+ -- ^ The Haskell types of this node, if any.
+
+ , nodeIdentifiers :: NodeIdentifiers a
+ -- ^ All the identifiers and their details
+ } deriving (Functor, Foldable, Traversable)
+
+instance Binary (NodeInfo TypeIndex) where
+ put_ bh ni = do
+ put_ bh $ S.toAscList $ nodeAnnotations ni
+ put_ bh $ nodeType ni
+ put_ bh $ M.toList $ nodeIdentifiers ni
+ get bh = NodeInfo
+ <$> fmap (S.fromDistinctAscList) (get bh)
+ <*> get bh
+ <*> fmap (M.fromList) (get bh)
+
+type Identifier = Either ModuleName Name
+
+type NodeIdentifiers a = M.Map Identifier (IdentifierDetails a)
+
+-- | Information associated with every identifier
+--
+-- We need to include types with identifiers because sometimes multiple
+-- identifiers occur in the same span(Overloaded Record Fields and so on)
+data IdentifierDetails a = IdentifierDetails
+ { identType :: Maybe a
+ , identInfo :: S.Set ContextInfo
+ } deriving (Eq, Functor, Foldable, Traversable)
+
+instance Outputable a => Outputable (IdentifierDetails a) where
+ ppr x = text "IdentifierDetails" <+> ppr (identType x) <+> ppr (identInfo x)
+
+instance Semigroup (IdentifierDetails a) where
+ d1 <> d2 = IdentifierDetails (identType d1 <|> identType d2)
+ (S.union (identInfo d1) (identInfo d2))
+
+instance Monoid (IdentifierDetails a) where
+ mempty = IdentifierDetails Nothing S.empty
+
+instance Binary (IdentifierDetails TypeIndex) where
+ put_ bh dets = do
+ put_ bh $ identType dets
+ put_ bh $ S.toAscList $ identInfo dets
+ get bh = IdentifierDetails
+ <$> get bh
+ <*> fmap (S.fromDistinctAscList) (get bh)
+
+
+-- | Different contexts under which identifiers exist
+data ContextInfo
+ = Use -- ^ regular variable
+ | MatchBind
+ | IEThing IEType -- ^ import/export
+ | TyDecl
+
+ -- | Value binding
+ | ValBind
+ BindType -- ^ whether or not the binding is in an instance
+ Scope -- ^ scope over which the value is bound
+ (Maybe Span) -- ^ span of entire binding
+
+ -- | Pattern binding
+ --
+ -- This case is tricky because the bound identifier can be used in two
+ -- distinct scopes. Consider the following example (with @-XViewPatterns@)
+ --
+ -- @
+ -- do (b, a, (a -> True)) <- bar
+ -- foo a
+ -- @
+ --
+ -- The identifier @a@ has two scopes: in the view pattern @(a -> True)@ and
+ -- in the rest of the @do@-block in @foo a@.
+ | PatternBind
+ Scope -- ^ scope /in the pattern/ (the variable bound can be used
+ -- further in the pattern)
+ Scope -- ^ rest of the scope outside the pattern
+ (Maybe Span) -- ^ span of entire binding
+
+ | ClassTyDecl (Maybe Span)
+
+ -- | Declaration
+ | Decl
+ DeclType -- ^ type of declaration
+ (Maybe Span) -- ^ span of entire binding
+
+ -- | Type variable
+ | TyVarBind Scope TyVarScope
+
+ -- | Record field
+ | RecField RecFieldContext (Maybe Span)
+ deriving (Eq, Ord, Show)
+
+instance Outputable ContextInfo where
+ ppr = text . show
+
+instance Binary ContextInfo where
+ put_ bh Use = putByte bh 0
+ put_ bh (IEThing t) = do
+ putByte bh 1
+ put_ bh t
+ put_ bh TyDecl = putByte bh 2
+ put_ bh (ValBind bt sc msp) = do
+ putByte bh 3
+ put_ bh bt
+ put_ bh sc
+ put_ bh msp
+ put_ bh (PatternBind a b c) = do
+ putByte bh 4
+ put_ bh a
+ put_ bh b
+ put_ bh c
+ put_ bh (ClassTyDecl sp) = do
+ putByte bh 5
+ put_ bh sp
+ put_ bh (Decl a b) = do
+ putByte bh 6
+ put_ bh a
+ put_ bh b
+ put_ bh (TyVarBind a b) = do
+ putByte bh 7
+ put_ bh a
+ put_ bh b
+ put_ bh (RecField a b) = do
+ putByte bh 8
+ put_ bh a
+ put_ bh b
+ put_ bh MatchBind = putByte bh 9
+
+ get bh = do
+ (t :: Word8) <- get bh
+ case t of
+ 0 -> return Use
+ 1 -> IEThing <$> get bh
+ 2 -> return TyDecl
+ 3 -> ValBind <$> get bh <*> get bh <*> get bh
+ 4 -> PatternBind <$> get bh <*> get bh <*> get bh
+ 5 -> ClassTyDecl <$> get bh
+ 6 -> Decl <$> get bh <*> get bh
+ 7 -> TyVarBind <$> get bh <*> get bh
+ 8 -> RecField <$> get bh <*> get bh
+ 9 -> return MatchBind
+ _ -> panic "Binary ContextInfo: invalid tag"
+
+
+-- | Types of imports and exports
+data IEType
+ = Import
+ | ImportAs
+ | ImportHiding
+ | Export
+ deriving (Eq, Enum, Ord, Show)
+
+instance Binary IEType where
+ put_ bh b = putByte bh (fromIntegral (fromEnum b))
+ get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
+
+
+data RecFieldContext
+ = RecFieldDecl
+ | RecFieldAssign
+ | RecFieldMatch
+ | RecFieldOcc
+ deriving (Eq, Enum, Ord, Show)
+
+instance Binary RecFieldContext where
+ put_ bh b = putByte bh (fromIntegral (fromEnum b))
+ get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
+
+
+data BindType
+ = RegularBind
+ | InstanceBind
+ deriving (Eq, Ord, Show, Enum)
+
+instance Binary BindType where
+ put_ bh b = putByte bh (fromIntegral (fromEnum b))
+ get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
+
+
+data DeclType
+ = FamDec -- ^ type or data family
+ | SynDec -- ^ type synonym
+ | DataDec -- ^ data declaration
+ | ConDec -- ^ constructor declaration
+ | PatSynDec -- ^ pattern synonym
+ | ClassDec -- ^ class declaration
+ | InstDec -- ^ instance declaration
+ deriving (Eq, Ord, Show, Enum)
+
+instance Binary DeclType where
+ put_ bh b = putByte bh (fromIntegral (fromEnum b))
+ get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
+
+
+data Scope
+ = NoScope
+ | LocalScope Span
+ | ModuleScope
+ deriving (Eq, Ord, Show, Typeable, Data)
+
+instance Outputable Scope where
+ ppr NoScope = text "NoScope"
+ ppr (LocalScope sp) = text "LocalScope" <+> ppr sp
+ ppr ModuleScope = text "ModuleScope"
+
+instance Binary Scope where
+ put_ bh NoScope = putByte bh 0
+ put_ bh (LocalScope span) = do
+ putByte bh 1
+ put_ bh span
+ put_ bh ModuleScope = putByte bh 2
+
+ get bh = do
+ (t :: Word8) <- get bh
+ case t of
+ 0 -> return NoScope
+ 1 -> LocalScope <$> get bh
+ 2 -> return ModuleScope
+ _ -> panic "Binary Scope: invalid tag"
+
+
+-- | Scope of a type variable.
+--
+-- This warrants a data type apart from 'Scope' because of complexities
+-- introduced by features like @-XScopedTypeVariables@ and @-XInstanceSigs@. For
+-- example, consider:
+--
+-- @
+-- foo, bar, baz :: forall a. a -> a
+-- @
+--
+-- Here @a@ is in scope in all the definitions of @foo@, @bar@, and @baz@, so we
+-- need a list of scopes to keep track of this. Furthermore, this list cannot be
+-- computed until we resolve the binding sites of @foo@, @bar@, and @baz@.
+--
+-- Consequently, @a@ starts with an @'UnresolvedScope' [foo, bar, baz] Nothing@
+-- which later gets resolved into a 'ResolvedScopes'.
+data TyVarScope
+ = ResolvedScopes [Scope]
+
+ -- | Unresolved scopes should never show up in the final @.hie@ file
+ | UnresolvedScope
+ [Name] -- ^ names of the definitions over which the scope spans
+ (Maybe Span) -- ^ the location of the instance/class declaration for
+ -- the case where the type variable is declared in a
+ -- method type signature
+ deriving (Eq, Ord)
+
+instance Show TyVarScope where
+ show (ResolvedScopes sc) = show sc
+ show _ = error "UnresolvedScope"
+
+instance Binary TyVarScope where
+ put_ bh (ResolvedScopes xs) = do
+ putByte bh 0
+ put_ bh xs
+ put_ bh (UnresolvedScope ns span) = do
+ putByte bh 1
+ put_ bh ns
+ put_ bh span
+
+ get bh = do
+ (t :: Word8) <- get bh
+ case t of
+ 0 -> ResolvedScopes <$> get bh
+ 1 -> UnresolvedScope <$> get bh <*> get bh
+ _ -> panic "Binary TyVarScope: invalid tag"
diff --git a/compiler/hieFile/HieUtils.hs b/compiler/hieFile/HieUtils.hs
new file mode 100644
index 0000000000..5259ea1280
--- /dev/null
+++ b/compiler/hieFile/HieUtils.hs
@@ -0,0 +1,455 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE FlexibleInstances #-}
+module HieUtils where
+
+import GhcPrelude
+
+import CoreMap
+import DynFlags ( DynFlags )
+import FastString ( FastString, mkFastString )
+import IfaceType
+import Name hiding (varName)
+import Outputable ( renderWithStyle, ppr, defaultUserStyle )
+import SrcLoc
+import ToIface
+import TyCon
+import TyCoRep
+import Type
+import Var
+import VarEnv
+
+import HieTypes
+
+import qualified Data.Map as M
+import qualified Data.Set as S
+import qualified Data.IntMap.Strict as IM
+import qualified Data.Array as A
+import Data.Data ( typeOf, typeRepTyCon, Data(toConstr) )
+import Data.Maybe ( maybeToList )
+import Data.Monoid
+import Data.Traversable ( for )
+import Control.Monad.Trans.State.Strict hiding (get)
+
+
+generateReferencesMap
+ :: Foldable f
+ => f (HieAST a)
+ -> M.Map Identifier [(Span, IdentifierDetails a)]
+generateReferencesMap = foldr (\ast m -> M.unionWith (++) (go ast) m) M.empty
+ where
+ go ast = M.unionsWith (++) (this : map go (nodeChildren ast))
+ where
+ this = fmap (pure . (nodeSpan ast,)) $ nodeIdentifiers $ nodeInfo ast
+
+renderHieType :: DynFlags -> HieTypeFix -> String
+renderHieType df ht = renderWithStyle df (ppr $ hieTypeToIface ht) sty
+ where sty = defaultUserStyle df
+
+resolveVisibility :: Type -> [Type] -> [(Bool,Type)]
+resolveVisibility kind ty_args
+ = go (mkEmptyTCvSubst in_scope) kind ty_args
+ where
+ in_scope = mkInScopeSet (tyCoVarsOfTypes ty_args)
+
+ go _ _ [] = []
+ go env ty ts
+ | Just ty' <- coreView ty
+ = go env ty' ts
+ go env (ForAllTy (Bndr tv vis) res) (t:ts)
+ | isVisibleArgFlag vis = (True , t) : ts'
+ | otherwise = (False, t) : ts'
+ where
+ ts' = go (extendTvSubst env tv t) res ts
+
+ go env (FunTy _ res) (t:ts) -- No type-class args in tycon apps
+ = (True,t) : (go env res ts)
+
+ go env (TyVarTy tv) ts
+ | Just ki <- lookupTyVar env tv = go env ki ts
+ go env kind (t:ts) = (True, t) : (go env kind ts) -- Ill-kinded
+
+foldType :: (HieType a -> a) -> HieTypeFix -> a
+foldType f (Roll t) = f $ fmap (foldType f) t
+
+hieTypeToIface :: HieTypeFix -> IfaceType
+hieTypeToIface = foldType go
+ where
+ go (HTyVarTy n) = IfaceTyVar $ occNameFS $ getOccName n
+ go (HAppTy a b) = IfaceAppTy a (hieToIfaceArgs b)
+ go (HLitTy l) = IfaceLitTy l
+ go (HForAllTy ((n,k),af) t) = let b = (occNameFS $ getOccName n, k)
+ in IfaceForAllTy (Bndr (IfaceTvBndr b) af) t
+ go (HFunTy a b) = IfaceFunTy a b
+ go (HQualTy pred b) = IfaceDFunTy pred b
+ go (HCastTy a) = a
+ go HCoercionTy = IfaceTyVar "<coercion type>"
+ go (HTyConApp a xs) = IfaceTyConApp a (hieToIfaceArgs xs)
+
+ -- This isn't fully faithful - we can't produce the 'Inferred' case
+ hieToIfaceArgs :: HieArgs IfaceType -> IfaceAppArgs
+ hieToIfaceArgs (HieArgs xs) = go' xs
+ where
+ go' [] = IA_Nil
+ go' ((True ,x):xs) = IA_Arg x Required $ go' xs
+ go' ((False,x):xs) = IA_Arg x Specified $ go' xs
+
+data HieTypeState
+ = HTS
+ { tyMap :: !(TypeMap TypeIndex)
+ , htyTable :: !(IM.IntMap HieTypeFlat)
+ , freshIndex :: !TypeIndex
+ }
+
+initialHTS :: HieTypeState
+initialHTS = HTS emptyTypeMap IM.empty 0
+
+freshTypeIndex :: State HieTypeState TypeIndex
+freshTypeIndex = do
+ index <- gets freshIndex
+ modify' $ \hts -> hts { freshIndex = index+1 }
+ return index
+
+compressTypes
+ :: HieASTs Type
+ -> (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
+compressTypes asts = (a, arr)
+ where
+ (a, (HTS _ m i)) = flip runState initialHTS $
+ for asts $ \typ -> do
+ i <- getTypeIndex typ
+ return i
+ arr = A.array (0,i-1) (IM.toList m)
+
+recoverFullType :: TypeIndex -> A.Array TypeIndex HieTypeFlat -> HieTypeFix
+recoverFullType i m = go i
+ where
+ go i = Roll $ fmap go (m A.! i)
+
+getTypeIndex :: Type -> State HieTypeState TypeIndex
+getTypeIndex t
+ | otherwise = do
+ tm <- gets tyMap
+ case lookupTypeMap tm t of
+ Just i -> return i
+ Nothing -> do
+ ht <- go t
+ extendHTS t ht
+ where
+ extendHTS t ht = do
+ i <- freshTypeIndex
+ modify' $ \(HTS tm tt fi) ->
+ HTS (extendTypeMap tm t i) (IM.insert i ht tt) fi
+ return i
+
+ go (TyVarTy v) = return $ HTyVarTy $ varName v
+ go ty@(AppTy _ _) = do
+ let (head,args) = splitAppTys ty
+ visArgs = HieArgs $ resolveVisibility (typeKind head) args
+ ai <- getTypeIndex head
+ argsi <- mapM getTypeIndex visArgs
+ return $ HAppTy ai argsi
+ go (TyConApp f xs) = do
+ let visArgs = HieArgs $ resolveVisibility (tyConKind f) xs
+ is <- mapM getTypeIndex visArgs
+ return $ HTyConApp (toIfaceTyCon f) is
+ go (ForAllTy (Bndr v a) t) = do
+ k <- getTypeIndex (varType v)
+ i <- getTypeIndex t
+ return $ HForAllTy ((varName v,k),a) i
+ go (FunTy a b) = do
+ ai <- getTypeIndex a
+ bi <- getTypeIndex b
+ return $ if isPredTy a
+ then HQualTy ai bi
+ else HFunTy ai bi
+ go (LitTy a) = return $ HLitTy $ toIfaceTyLit a
+ go (CastTy t _) = do
+ i <- getTypeIndex t
+ return $ HCastTy i
+ go (CoercionTy _) = return HCoercionTy
+
+resolveTyVarScopes :: M.Map FastString (HieAST a) -> M.Map FastString (HieAST a)
+resolveTyVarScopes asts = M.map go asts
+ where
+ go ast = resolveTyVarScopeLocal ast asts
+
+resolveTyVarScopeLocal :: HieAST a -> M.Map FastString (HieAST a) -> HieAST a
+resolveTyVarScopeLocal ast asts = go ast
+ where
+ resolveNameScope dets = dets{identInfo =
+ S.map resolveScope (identInfo dets)}
+ resolveScope (TyVarBind sc (UnresolvedScope names Nothing)) =
+ TyVarBind sc $ ResolvedScopes
+ [ LocalScope binding
+ | name <- names
+ , Just binding <- [getNameBinding name asts]
+ ]
+ resolveScope (TyVarBind sc (UnresolvedScope names (Just sp))) =
+ TyVarBind sc $ ResolvedScopes
+ [ LocalScope binding
+ | name <- names
+ , Just binding <- [getNameBindingInClass name sp asts]
+ ]
+ resolveScope scope = scope
+ go (Node info span children) = Node info' span $ map go children
+ where
+ info' = info { nodeIdentifiers = idents }
+ idents = M.map resolveNameScope $ nodeIdentifiers info
+
+getNameBinding :: Name -> M.Map FastString (HieAST a) -> Maybe Span
+getNameBinding n asts = do
+ (_,msp) <- getNameScopeAndBinding n asts
+ msp
+
+getNameScope :: Name -> M.Map FastString (HieAST a) -> Maybe [Scope]
+getNameScope n asts = do
+ (scopes,_) <- getNameScopeAndBinding n asts
+ return scopes
+
+getNameBindingInClass
+ :: Name
+ -> Span
+ -> M.Map FastString (HieAST a)
+ -> Maybe Span
+getNameBindingInClass n sp asts = do
+ ast <- M.lookup (srcSpanFile sp) asts
+ getFirst $ foldMap First $ do
+ child <- flattenAst ast
+ dets <- maybeToList
+ $ M.lookup (Right n) $ nodeIdentifiers $ nodeInfo child
+ let binding = foldMap (First . getBindSiteFromContext) (identInfo dets)
+ return (getFirst binding)
+
+getNameScopeAndBinding
+ :: Name
+ -> M.Map FastString (HieAST a)
+ -> Maybe ([Scope], Maybe Span)
+getNameScopeAndBinding n asts = case nameSrcSpan n of
+ RealSrcSpan sp -> do -- @Maybe
+ ast <- M.lookup (srcSpanFile sp) asts
+ defNode <- selectLargestContainedBy sp ast
+ getFirst $ foldMap First $ do -- @[]
+ node <- flattenAst defNode
+ dets <- maybeToList
+ $ M.lookup (Right n) $ nodeIdentifiers $ nodeInfo node
+ scopes <- maybeToList $ foldMap getScopeFromContext (identInfo dets)
+ let binding = foldMap (First . getBindSiteFromContext) (identInfo dets)
+ return $ Just (scopes, getFirst binding)
+ _ -> Nothing
+
+getScopeFromContext :: ContextInfo -> Maybe [Scope]
+getScopeFromContext (ValBind _ sc _) = Just [sc]
+getScopeFromContext (PatternBind a b _) = Just [a, b]
+getScopeFromContext (ClassTyDecl _) = Just [ModuleScope]
+getScopeFromContext (Decl _ _) = Just [ModuleScope]
+getScopeFromContext (TyVarBind a (ResolvedScopes xs)) = Just $ a:xs
+getScopeFromContext (TyVarBind a _) = Just [a]
+getScopeFromContext _ = Nothing
+
+getBindSiteFromContext :: ContextInfo -> Maybe Span
+getBindSiteFromContext (ValBind _ _ sp) = sp
+getBindSiteFromContext (PatternBind _ _ sp) = sp
+getBindSiteFromContext _ = Nothing
+
+flattenAst :: HieAST a -> [HieAST a]
+flattenAst n =
+ n : concatMap flattenAst (nodeChildren n)
+
+smallestContainingSatisfying
+ :: Span
+ -> (HieAST a -> Bool)
+ -> HieAST a
+ -> Maybe (HieAST a)
+smallestContainingSatisfying sp cond node
+ | nodeSpan node `containsSpan` sp = getFirst $ mconcat
+ [ foldMap (First . smallestContainingSatisfying sp cond) $
+ nodeChildren node
+ , First $ if cond node then Just node else Nothing
+ ]
+ | sp `containsSpan` nodeSpan node = Nothing
+ | otherwise = Nothing
+
+selectLargestContainedBy :: Span -> HieAST a -> Maybe (HieAST a)
+selectLargestContainedBy sp node
+ | sp `containsSpan` nodeSpan node = Just node
+ | nodeSpan node `containsSpan` sp =
+ getFirst $ foldMap (First . selectLargestContainedBy sp) $
+ nodeChildren node
+ | otherwise = Nothing
+
+selectSmallestContaining :: Span -> HieAST a -> Maybe (HieAST a)
+selectSmallestContaining sp node
+ | nodeSpan node `containsSpan` sp = getFirst $ mconcat
+ [ foldMap (First . selectSmallestContaining sp) $ nodeChildren node
+ , First (Just node)
+ ]
+ | sp `containsSpan` nodeSpan node = Nothing
+ | otherwise = Nothing
+
+definedInAsts :: M.Map FastString (HieAST a) -> Name -> Bool
+definedInAsts asts n = case nameSrcSpan n of
+ RealSrcSpan sp -> srcSpanFile sp `elem` M.keys asts
+ _ -> False
+
+isOccurrence :: ContextInfo -> Bool
+isOccurrence Use = True
+isOccurrence _ = False
+
+scopeContainsSpan :: Scope -> Span -> Bool
+scopeContainsSpan NoScope _ = False
+scopeContainsSpan ModuleScope _ = True
+scopeContainsSpan (LocalScope a) b = a `containsSpan` b
+
+-- | One must contain the other. Leaf nodes cannot contain anything
+combineAst :: HieAST Type -> HieAST Type -> HieAST Type
+combineAst a@(Node aInf aSpn xs) b@(Node bInf bSpn ys)
+ | aSpn == bSpn = Node (aInf `combineNodeInfo` bInf) aSpn (mergeAsts xs ys)
+ | aSpn `containsSpan` bSpn = combineAst b a
+combineAst a (Node xs span children) = Node xs span (insertAst a children)
+
+-- | Insert an AST in a sorted list of disjoint Asts
+insertAst :: HieAST Type -> [HieAST Type] -> [HieAST Type]
+insertAst x = mergeAsts [x]
+
+-- | Merge two nodes together.
+--
+-- Precondition and postcondition: elements in 'nodeType' are ordered.
+combineNodeInfo :: NodeInfo Type -> NodeInfo Type -> NodeInfo Type
+(NodeInfo as ai ad) `combineNodeInfo` (NodeInfo bs bi bd) =
+ NodeInfo (S.union as bs) (mergeSorted ai bi) (M.unionWith (<>) ad bd)
+ where
+ mergeSorted :: [Type] -> [Type] -> [Type]
+ mergeSorted la@(a:as) lb@(b:bs) = case nonDetCmpType a b of
+ LT -> a : mergeSorted as lb
+ EQ -> a : mergeSorted as bs
+ GT -> b : mergeSorted la bs
+ mergeSorted as [] = as
+ mergeSorted [] bs = bs
+
+
+{- | Merge two sorted, disjoint lists of ASTs, combining when necessary.
+
+In the absence of position-altering pragmas (ex: @# line "file.hs" 3@),
+different nodes in an AST tree should either have disjoint spans (in
+which case you can say for sure which one comes first) or one span
+should be completely contained in the other (in which case the contained
+span corresponds to some child node).
+
+However, since Haskell does have position-altering pragmas it /is/
+possible for spans to be overlapping. Here is an example of a source file
+in which @foozball@ and @quuuuuux@ have overlapping spans:
+
+@
+module Baz where
+
+# line 3 "Baz.hs"
+foozball :: Int
+foozball = 0
+
+# line 3 "Baz.hs"
+bar, quuuuuux :: Int
+bar = 1
+quuuuuux = 2
+@
+
+In these cases, we just do our best to produce sensible `HieAST`'s. The blame
+should be laid at the feet of whoever wrote the line pragmas in the first place
+(usually the C preprocessor...).
+-}
+mergeAsts :: [HieAST Type] -> [HieAST Type] -> [HieAST Type]
+mergeAsts xs [] = xs
+mergeAsts [] ys = ys
+mergeAsts xs@(a:as) ys@(b:bs)
+ | span_a `containsSpan` span_b = mergeAsts (combineAst a b : as) bs
+ | span_b `containsSpan` span_a = mergeAsts as (combineAst a b : bs)
+ | span_a `rightOf` span_b = b : mergeAsts xs bs
+ | span_a `leftOf` span_b = a : mergeAsts as ys
+
+ -- These cases are to work around ASTs that are not fully disjoint
+ | span_a `startsRightOf` span_b = b : mergeAsts as ys
+ | otherwise = a : mergeAsts as ys
+ where
+ span_a = nodeSpan a
+ span_b = nodeSpan b
+
+rightOf :: Span -> Span -> Bool
+rightOf s1 s2
+ = (srcSpanStartLine s1, srcSpanStartCol s1)
+ >= (srcSpanEndLine s2, srcSpanEndCol s2)
+ && (srcSpanFile s1 == srcSpanFile s2)
+
+leftOf :: Span -> Span -> Bool
+leftOf s1 s2
+ = (srcSpanEndLine s1, srcSpanEndCol s1)
+ <= (srcSpanStartLine s2, srcSpanStartCol s2)
+ && (srcSpanFile s1 == srcSpanFile s2)
+
+startsRightOf :: Span -> Span -> Bool
+startsRightOf s1 s2
+ = (srcSpanStartLine s1, srcSpanStartCol s1)
+ >= (srcSpanStartLine s2, srcSpanStartCol s2)
+
+-- | combines and sorts ASTs using a merge sort
+mergeSortAsts :: [HieAST Type] -> [HieAST Type]
+mergeSortAsts = go . map pure
+ where
+ go [] = []
+ go [xs] = xs
+ go xss = go (mergePairs xss)
+ mergePairs [] = []
+ mergePairs [xs] = [xs]
+ mergePairs (xs:ys:xss) = mergeAsts xs ys : mergePairs xss
+
+simpleNodeInfo :: FastString -> FastString -> NodeInfo a
+simpleNodeInfo cons typ = NodeInfo (S.singleton (cons, typ)) [] M.empty
+
+locOnly :: SrcSpan -> [HieAST a]
+locOnly (RealSrcSpan span) =
+ [Node e span []]
+ where e = NodeInfo S.empty [] M.empty
+locOnly _ = []
+
+mkScope :: SrcSpan -> Scope
+mkScope (RealSrcSpan sp) = LocalScope sp
+mkScope _ = NoScope
+
+mkLScope :: Located a -> Scope
+mkLScope = mkScope . getLoc
+
+combineScopes :: Scope -> Scope -> Scope
+combineScopes ModuleScope _ = ModuleScope
+combineScopes _ ModuleScope = ModuleScope
+combineScopes NoScope x = x
+combineScopes x NoScope = x
+combineScopes (LocalScope a) (LocalScope b) =
+ mkScope $ combineSrcSpans (RealSrcSpan a) (RealSrcSpan b)
+
+{-# INLINEABLE makeNode #-}
+makeNode
+ :: (Applicative m, Data a)
+ => a -- ^ helps fill in 'nodeAnnotations' (with 'Data')
+ -> SrcSpan -- ^ return an empty list if this is unhelpful
+ -> m [HieAST b]
+makeNode x spn = pure $ case spn of
+ RealSrcSpan span -> [Node (simpleNodeInfo cons typ) span []]
+ _ -> []
+ where
+ cons = mkFastString . show . toConstr $ x
+ typ = mkFastString . show . typeRepTyCon . typeOf $ x
+
+{-# INLINEABLE makeTypeNode #-}
+makeTypeNode
+ :: (Applicative m, Data a)
+ => a -- ^ helps fill in 'nodeAnnotations' (with 'Data')
+ -> SrcSpan -- ^ return an empty list if this is unhelpful
+ -> Type -- ^ type to associate with the node
+ -> m [HieAST Type]
+makeTypeNode x spn etyp = pure $ case spn of
+ RealSrcSpan span ->
+ [Node (NodeInfo (S.singleton (cons,typ)) [etyp] M.empty) span []]
+ _ -> []
+ where
+ cons = mkFastString . show . toConstr $ x
+ typ = mkFastString . show . typeRepTyCon . typeOf $ x
diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs
index 7b66472d7a..c23f577bba 100644
--- a/compiler/iface/MkIface.hs
+++ b/compiler/iface/MkIface.hs
@@ -1291,6 +1291,8 @@ checkVersions hsc_env mod_summary iface
; if recompileRequired recomp then return (recomp, Nothing) else do {
; recomp <- checkHsig mod_summary iface
; if recompileRequired recomp then return (recomp, Nothing) else do {
+ ; recomp <- checkHie mod_summary
+ ; if recompileRequired recomp then return (recomp, Nothing) else do {
; recomp <- checkDependencies hsc_env mod_summary iface
; if recompileRequired recomp then return (recomp, Just iface) else do {
; recomp <- checkPlugins hsc_env iface
@@ -1313,7 +1315,7 @@ checkVersions hsc_env mod_summary iface
; updateEps_ $ \eps -> eps { eps_is_boot = mod_deps }
; recomp <- checkList [checkModUsage this_pkg u | u <- mi_usages iface]
; return (recomp, Just iface)
- }}}}}}}}}
+ }}}}}}}}}}
where
this_pkg = thisPackage (hsc_dflags hsc_env)
-- This is a bit of a hack really
@@ -1365,6 +1367,22 @@ checkHsig mod_summary iface = do
True -> up_to_date (text "implementing module unchanged")
False -> return (RecompBecause "implementing module changed")
+-- | Check if @.hie@ file is out of date or missing.
+checkHie :: ModSummary -> IfG RecompileRequired
+checkHie mod_summary = do
+ dflags <- getDynFlags
+ let hie_date_opt = ms_hie_date mod_summary
+ hs_date = ms_hs_date mod_summary
+ pure $ case gopt Opt_WriteHie dflags of
+ False -> UpToDate
+ True -> case hie_date_opt of
+ Nothing -> RecompBecause "HIE file is missing"
+ Just hie_date
+ | hie_date < hs_date
+ -> RecompBecause "HIE file is out of date"
+ | otherwise
+ -> UpToDate
+
-- | Check the flags haven't changed
checkFlagHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkFlagHash hsc_env iface = do
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 295d36284f..f1a5cb46e0 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -75,6 +75,8 @@ import Data.Maybe
import Data.Version
import Data.Either ( partitionEithers )
+import Data.Time ( UTCTime )
+
-- ---------------------------------------------------------------------------
-- Pre-process
@@ -1016,6 +1018,7 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
let o_file = ml_obj_file location -- The real object file
hi_file = ml_hi_file location
+ hie_file = ml_hie_file location
dest_file | writeInterfaceOnlyMode dflags
= hi_file
| otherwise
@@ -1023,7 +1026,7 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
-- Figure out if the source has changed, for recompilation avoidance.
--
- -- Setting source_unchanged to True means that M.o seems
+ -- Setting source_unchanged to True means that M.o (or M.hie) seems
-- to be up to date wrt M.hs; so no need to recompile unless imports have
-- changed (which the compiler itself figures out).
-- Setting source_unchanged to False tells the compiler that M.o is out of
@@ -1037,13 +1040,14 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
-- (b) we aren't going all the way to .o file (e.g. ghc -S)
then return SourceModified
-- Otherwise look at file modification dates
- else do dest_file_exists <- doesFileExist dest_file
- if not dest_file_exists
- then return SourceModified -- Need to recompile
- else do t2 <- getModificationUTCTime dest_file
- if t2 > src_timestamp
- then return SourceUnmodified
- else return SourceModified
+ else do dest_file_mod <- sourceModified dest_file src_timestamp
+ hie_file_mod <- if gopt Opt_WriteHie dflags
+ then sourceModified hie_file
+ src_timestamp
+ else pure False
+ if dest_file_mod || hie_file_mod
+ then return SourceModified
+ else return SourceUnmodified
PipeState{hsc_env=hsc_env'} <- getPipeState
@@ -1062,6 +1066,7 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
ms_obj_date = Nothing,
ms_parsed_mod = Nothing,
ms_iface_date = Nothing,
+ ms_hie_date = Nothing,
ms_textual_imps = imps,
ms_srcimps = src_imps }
@@ -1634,8 +1639,9 @@ getLocation src_flavour mod_name = do
location1 <- liftIO $ mkHomeModLocation2 dflags mod_name basename suff
-- Boot-ify it if necessary
- let location2 | HsBootFile <- src_flavour = addBootSuffixLocn location1
- | otherwise = location1
+ let location2
+ | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
+ | otherwise = location1
-- Take -ohi into account if present
@@ -2251,6 +2257,18 @@ writeInterfaceOnlyMode dflags =
gopt Opt_WriteInterface dflags &&
HscNothing == hscTarget dflags
+-- | Figure out if a source file was modified after an output file (or if we
+-- anyways need to consider the source file modified since the output is gone).
+sourceModified :: FilePath -- ^ destination file we are looking for
+ -> UTCTime -- ^ last time of modification of source file
+ -> IO Bool -- ^ do we need to regenerate the output?
+sourceModified dest_file src_timestamp = do
+ dest_file_exists <- doesFileExist dest_file
+ if not dest_file_exists
+ then return True -- Need to recompile
+ else do t2 <- getModificationUTCTime dest_file
+ return (t2 <= src_timestamp)
+
-- | What phase to run after one of the backend code generators has run
hscPostBackendPhase :: DynFlags -> HscSource -> HscTarget -> Phase
hscPostBackendPhase _ HsBootFile _ = StopLn
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 9e93e47eeb..6c4ee86084 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -511,6 +511,7 @@ data GeneralFlag
| Opt_OmitInterfacePragmas
| Opt_ExposeAllUnfoldings
| Opt_WriteInterface -- forces .hi files to be written even with -fno-code
+ | Opt_WriteHie -- generate .hie files
-- profiling opts
| Opt_AutoSccsOnIndividualCafs
@@ -544,6 +545,7 @@ data GeneralFlag
| Opt_GhciSandbox
| Opt_GhciHistory
| Opt_GhciLeakCheck
+ | Opt_ValidateHie
| Opt_LocalGhciHistory
| Opt_NoIt
| Opt_HelpfulErrors
@@ -942,12 +944,14 @@ data DynFlags = DynFlags {
objectDir :: Maybe String,
dylibInstallName :: Maybe String,
hiDir :: Maybe String,
+ hieDir :: Maybe String,
stubDir :: Maybe String,
dumpDir :: Maybe String,
objectSuf :: String,
hcSuf :: String,
hiSuf :: String,
+ hieSuf :: String,
canGenerateDynamicToo :: IORef Bool,
dynObjectSuf :: String,
@@ -1910,12 +1914,14 @@ defaultDynFlags mySettings (myLlvmTargets, myLlvmPasses) =
objectDir = Nothing,
dylibInstallName = Nothing,
hiDir = Nothing,
+ hieDir = Nothing,
stubDir = Nothing,
dumpDir = Nothing,
objectSuf = phaseInputExt StopLn,
hcSuf = phaseInputExt HCc,
hiSuf = "hi",
+ hieSuf = "hie",
canGenerateDynamicToo = panic "defaultDynFlags: No canGenerateDynamicToo",
dynObjectSuf = "dyn_" ++ phaseInputExt StopLn,
@@ -2493,10 +2499,10 @@ getVerbFlags dflags
| verbosity dflags >= 4 = ["-v"]
| otherwise = []
-setObjectDir, setHiDir, setStubDir, setDumpDir, setOutputDir,
+setObjectDir, setHiDir, setHieDir, setStubDir, setDumpDir, setOutputDir,
setDynObjectSuf, setDynHiSuf,
setDylibInstallName,
- setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
+ setObjectSuf, setHiSuf, setHieSuf, setHcSuf, parseDynLibLoaderMode,
setPgmP, addOptl, addOptc, addOptP,
addCmdlineFramework, addHaddockOpts, addGhciScript,
setInteractivePrint
@@ -2506,18 +2512,24 @@ setOutputFile, setDynOutputFile, setOutputHi, setDumpPrefixForce
setObjectDir f d = d { objectDir = Just f}
setHiDir f d = d { hiDir = Just f}
+setHieDir f d = d { hieDir = Just f}
setStubDir f d = d { stubDir = Just f
, includePaths = addGlobalInclude (includePaths d) [f] }
-- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
-- \#included from the .hc file when compiling via C (i.e. unregisterised
-- builds).
setDumpDir f d = d { dumpDir = Just f}
-setOutputDir f = setObjectDir f . setHiDir f . setStubDir f . setDumpDir f
+setOutputDir f = setObjectDir f
+ . setHieDir f
+ . setHiDir f
+ . setStubDir f
+ . setDumpDir f
setDylibInstallName f d = d { dylibInstallName = Just f}
setObjectSuf f d = d { objectSuf = f}
setDynObjectSuf f d = d { dynObjectSuf = f}
setHiSuf f d = d { hiSuf = f}
+setHieSuf f d = d { hieSuf = f}
setDynHiSuf f d = d { dynHiSuf = f}
setHcSuf f d = d { hcSuf = f}
@@ -3062,8 +3074,10 @@ dynamic_flags_deps = [
, make_ord_flag defGhcFlag "dynosuf" (hasArg setDynObjectSuf)
, make_ord_flag defGhcFlag "hcsuf" (hasArg setHcSuf)
, make_ord_flag defGhcFlag "hisuf" (hasArg setHiSuf)
+ , make_ord_flag defGhcFlag "hiesuf" (hasArg setHieSuf)
, make_ord_flag defGhcFlag "dynhisuf" (hasArg setDynHiSuf)
, make_ord_flag defGhcFlag "hidir" (hasArg setHiDir)
+ , make_ord_flag defGhcFlag "hiedir" (hasArg setHieDir)
, make_ord_flag defGhcFlag "tmpdir" (hasArg setTmpDir)
, make_ord_flag defGhcFlag "stubdir" (hasArg setStubDir)
, make_ord_flag defGhcFlag "dumpdir" (hasArg setDumpDir)
@@ -4088,6 +4102,7 @@ fFlagsDeps = [
flagSpec "gen-manifest" Opt_GenManifest,
flagSpec "ghci-history" Opt_GhciHistory,
flagSpec "ghci-leak-check" Opt_GhciLeakCheck,
+ flagSpec "validate-ide-info" Opt_ValidateHie,
flagGhciSpec "local-ghci-history" Opt_LocalGhciHistory,
flagGhciSpec "no-it" Opt_NoIt,
flagSpec "ghci-sandbox" Opt_GhciSandbox,
@@ -4143,6 +4158,7 @@ fFlagsDeps = [
flagSpec "strictness" Opt_Strictness,
flagSpec "use-rpaths" Opt_RPath,
flagSpec "write-interface" Opt_WriteInterface,
+ flagSpec "write-ide-info" Opt_WriteHie,
flagSpec "unbox-small-strict-fields" Opt_UnboxSmallStrictFields,
flagSpec "unbox-strict-fields" Opt_UnboxStrictFields,
flagSpec "version-macros" Opt_VersionMacros,
diff --git a/compiler/main/Finder.hs b/compiler/main/Finder.hs
index 57d608bbf7..2db0a5e0b4 100644
--- a/compiler/main/Finder.hs
+++ b/compiler/main/Finder.hs
@@ -482,23 +482,27 @@ mkHomeModLocation2 dflags mod src_basename ext = do
obj_fn = mkObjPath dflags src_basename mod_basename
hi_fn = mkHiPath dflags src_basename mod_basename
+ hie_fn = mkHiePath dflags src_basename mod_basename
return (ModLocation{ ml_hs_file = Just (src_basename <.> ext),
ml_hi_file = hi_fn,
- ml_obj_file = obj_fn })
+ ml_obj_file = obj_fn,
+ ml_hie_file = hie_fn })
mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
-> IO ModLocation
mkHiOnlyModLocation dflags hisuf path basename
= do let full_basename = path </> basename
obj_fn = mkObjPath dflags full_basename basename
+ hie_fn = mkHiePath dflags full_basename basename
return ModLocation{ ml_hs_file = Nothing,
ml_hi_file = full_basename <.> hisuf,
-- Remove the .hi-boot suffix from
-- hi_file, if it had one. We always
-- want the name of the real .hi file
-- in the ml_hi_file field.
- ml_obj_file = obj_fn
+ ml_obj_file = obj_fn,
+ ml_hie_file = hie_fn
}
-- | Constructs the filename of a .o file for a given source file.
@@ -532,6 +536,21 @@ mkHiPath dflags basename mod_basename = hi_basename <.> hisuf
hi_basename | Just dir <- hidir = dir </> mod_basename
| otherwise = basename
+-- | Constructs the filename of a .hie file for a given source file.
+-- Does /not/ check whether the .hie file exists
+mkHiePath
+ :: DynFlags
+ -> FilePath -- the filename of the source file, minus the extension
+ -> String -- the module name with dots replaced by slashes
+ -> FilePath
+mkHiePath dflags basename mod_basename = hie_basename <.> hiesuf
+ where
+ hiedir = hieDir dflags
+ hiesuf = hieSuf dflags
+
+ hie_basename | Just dir <- hiedir = dir </> mod_basename
+ | otherwise = basename
+
-- -----------------------------------------------------------------------------
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index 39b6427173..8b2bc01ffe 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -2186,6 +2186,8 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
then liftIO $ getObjTimestamp location NotBoot
else return Nothing
hi_timestamp <- maybeGetIfaceDate dflags location
+ let hie_location = ml_hie_file location
+ hie_timestamp <- modificationTimeIfExists hie_location
-- We have to repopulate the Finder's cache because it
-- was flushed before the downsweep.
@@ -2193,7 +2195,8 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
(moduleName (ms_mod old_summary)) (ms_location old_summary)
return old_summary{ ms_obj_date = obj_timestamp
- , ms_iface_date = hi_timestamp }
+ , ms_iface_date = hi_timestamp
+ , ms_hie_date = hie_timestamp }
else
new_summary src_timestamp
@@ -2232,6 +2235,7 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
else return Nothing
hi_timestamp <- maybeGetIfaceDate dflags location
+ hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
extra_sig_imports <- findExtraSigImports hsc_env hsc_src mod_name
required_by_imports <- implicitRequirements hsc_env the_imps
@@ -2247,6 +2251,7 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
ms_textual_imps = the_imps ++ extra_sig_imports ++ required_by_imports,
ms_hs_date = src_timestamp,
ms_iface_date = hi_timestamp,
+ ms_hie_date = hie_timestamp,
ms_obj_date = obj_timestamp })
findSummaryBySourceFile :: [ModSummary] -> FilePath -> Maybe ModSummary
@@ -2304,8 +2309,10 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
then getObjTimestamp location is_boot
else return Nothing
hi_timestamp <- maybeGetIfaceDate dflags location
+ hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
return (Just (Right old_summary{ ms_obj_date = obj_timestamp
- , ms_iface_date = hi_timestamp}))
+ , ms_iface_date = hi_timestamp
+ , ms_hie_date = hie_timestamp }))
| otherwise =
-- source changed: re-summarise.
new_summary location (ms_mod old_summary) src_fn src_timestamp
@@ -2389,6 +2396,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
else return Nothing
hi_timestamp <- maybeGetIfaceDate dflags location
+ hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
extra_sig_imports <- findExtraSigImports hsc_env hsc_src mod_name
required_by_imports <- implicitRequirements hsc_env the_imps
@@ -2404,6 +2412,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
ms_textual_imps = the_imps ++ extra_sig_imports ++ required_by_imports,
ms_hs_date = src_timestamp,
ms_iface_date = hi_timestamp,
+ ms_hie_date = hie_timestamp,
ms_obj_date = obj_timestamp })))
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 9b9edf7d21..c2c912451b 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -85,6 +85,7 @@ module HscMain
import GhcPrelude
import Data.Data hiding (Fixity, TyCon)
+import Data.Maybe ( fromJust )
import Id
import GHCi ( addSptEntry )
import GHCi.RemoteTypes ( ForeignHValue )
@@ -167,10 +168,15 @@ import Data.IORef
import System.FilePath as FilePath
import System.Directory
import System.IO (fixIO)
-import qualified Data.Map as Map
+import qualified Data.Map as M
import qualified Data.Set as S
import Data.Set (Set)
+import HieAst ( mkHieFile )
+import HieTypes ( getAsts, hie_asts )
+import HieBin ( readHieFile, writeHieFile )
+import HieDebug ( diffFile, validateScopes )
+
#include "HsVersions.h"
@@ -379,8 +385,8 @@ hscParse' mod_summary
hpm_module = rdr_module,
hpm_src_files = srcs2,
hpm_annotations
- = (Map.fromListWith (++) $ annotations pst,
- Map.fromList $ ((noSrcSpan,comment_q pst)
+ = (M.fromListWith (++) $ annotations pst,
+ M.fromList $ ((noSrcSpan,comment_q pst)
:(annotations_comments pst)))
}
@@ -392,15 +398,41 @@ hscParse' mod_summary
-- -----------------------------------------------------------------------------
-- | If the renamed source has been kept, extract it. Dump it if requested.
-extract_renamed_stuff :: TcGblEnv -> Hsc (TcGblEnv, RenamedStuff)
-extract_renamed_stuff tc_result = do
+extract_renamed_stuff :: ModSummary -> TcGblEnv -> Hsc RenamedStuff
+extract_renamed_stuff mod_summary tc_result = do
let rn_info = getRenamedStuff tc_result
dflags <- getDynFlags
liftIO $ dumpIfSet_dyn dflags Opt_D_dump_rn_ast "Renamer" $
showAstData NoBlankSrcSpan rn_info
- return (tc_result, rn_info)
+ -- Create HIE files
+ when (gopt Opt_WriteHie dflags) $ do
+ hieFile <- mkHieFile mod_summary (tcg_binds tc_result)
+ (fromJust rn_info)
+ let out_file = ml_hie_file $ ms_location mod_summary
+ liftIO $ writeHieFile out_file hieFile
+
+ -- Validate HIE files
+ when (gopt Opt_ValidateHie dflags) $ do
+ hs_env <- Hsc $ \e w -> return (e, w)
+ liftIO $ do
+ -- Validate Scopes
+ case validateScopes $ getAsts $ hie_asts hieFile of
+ [] -> putMsg dflags $ text "Got valid scopes"
+ xs -> do
+ putMsg dflags $ text "Got invalid scopes"
+ mapM_ (putMsg dflags) xs
+ -- Roundtrip testing
+ nc <- readIORef $ hsc_NC hs_env
+ (file', _) <- readHieFile nc out_file
+ case diffFile hieFile file' of
+ [] ->
+ putMsg dflags $ text "Got no roundtrip errors"
+ xs -> do
+ putMsg dflags $ text "Got roundtrip errors"
+ mapM_ (putMsg dflags) xs
+ return rn_info
-- -----------------------------------------------------------------------------
@@ -408,22 +440,23 @@ extract_renamed_stuff tc_result = do
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule
-> IO (TcGblEnv, RenamedStuff)
hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $ do
- tc_result <- hscTypecheck True mod_summary (Just rdr_module)
- extract_renamed_stuff tc_result
+ tc_result <- hsc_typecheck True mod_summary (Just rdr_module)
+ rn_info <- extract_renamed_stuff mod_summary tc_result
+ return (tc_result, rn_info)
+-- | Rename and typecheck a module, but don't return the renamed syntax
hscTypecheck :: Bool -- ^ Keep renamed source?
-> ModSummary -> Maybe HsParsedModule
-> Hsc TcGblEnv
hscTypecheck keep_rn mod_summary mb_rdr_module = do
- tc_result <- hscTypecheck' keep_rn mod_summary mb_rdr_module
- _ <- extract_renamed_stuff tc_result
+ tc_result <- hsc_typecheck keep_rn mod_summary mb_rdr_module
+ _ <- extract_renamed_stuff mod_summary tc_result
return tc_result
-
-hscTypecheck' :: Bool -- ^ Keep renamed source?
+hsc_typecheck :: Bool -- ^ Keep renamed source?
-> ModSummary -> Maybe HsParsedModule
-> Hsc TcGblEnv
-hscTypecheck' keep_rn mod_summary mb_rdr_module = do
+hsc_typecheck keep_rn mod_summary mb_rdr_module = do
hsc_env <- getHscEnv
let hsc_src = ms_hsc_src mod_summary
dflags = hsc_dflags hsc_env
@@ -433,6 +466,7 @@ hscTypecheck' keep_rn mod_summary mb_rdr_module = do
inner_mod = canonicalizeHomeModule dflags mod_name
src_filename = ms_hspp_file mod_summary
real_loc = realSrcLocSpan $ mkRealSrcLoc (mkFastString src_filename) 1 1
+ keep_rn' = gopt Opt_WriteHie dflags || keep_rn
MASSERT( moduleUnitId outer_mod == thisPackage dflags )
if hsc_src == HsigFile && not (isHoleModule inner_mod)
then ioMsgMaybe $ tcRnInstantiateSignature hsc_env outer_mod' real_loc
@@ -440,7 +474,7 @@ hscTypecheck' keep_rn mod_summary mb_rdr_module = do
do hpm <- case mb_rdr_module of
Just hpm -> return hpm
Nothing -> hscParse' mod_summary
- tc_result0 <- tcRnModule' mod_summary keep_rn hpm
+ tc_result0 <- tcRnModule' mod_summary keep_rn' hpm
if hsc_src == HsigFile
then do (iface, _, _) <- liftIO $ hscSimpleIface hsc_env tc_result0 Nothing
ioMsgMaybe $
@@ -1411,7 +1445,8 @@ hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do
where
no_loc = ModLocation{ ml_hs_file = Just filename,
ml_hi_file = panic "hscCompileCmmFile: no hi file",
- ml_obj_file = panic "hscCompileCmmFile: no obj file" }
+ ml_obj_file = panic "hscCompileCmmFile: no obj file",
+ ml_hie_file = panic "hscCompileCmmFile: no hie file"}
-------------------- Stuff for new code gen ---------------------
@@ -1591,7 +1626,8 @@ hscDeclsWithLocation hsc_env0 str source linenumber =
-- We use a basically null location for iNTERACTIVE
let iNTERACTIVELoc = ModLocation{ ml_hs_file = Nothing,
ml_hi_file = panic "hsDeclsWithLocation:ml_hi_file",
- ml_obj_file = panic "hsDeclsWithLocation:ml_hi_file"}
+ ml_obj_file = panic "hsDeclsWithLocation:ml_obj_file",
+ ml_hie_file = panic "hsDeclsWithLocation:ml_hie_file" }
ds_result <- hscDesugar' iNTERACTIVELoc tc_gblenv
{- Simplify -}
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index d0cf7e0dd8..456332daeb 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -2752,6 +2752,8 @@ data ModSummary
-- ^ Timestamp of hi file, if we *only* are typechecking (it is
-- 'Nothing' otherwise.
-- See Note [Recompilation checking in -fno-code mode] and #9243
+ ms_hie_date :: Maybe UTCTime,
+ -- ^ Timestamp of hie file, if we have one
ms_srcimps :: [(Maybe FastString, Located ModuleName)],
-- ^ Source imports of the module
ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
@@ -2833,7 +2835,7 @@ showModMsg dflags target recomp mod_summary = showSDoc dflags $
{-
************************************************************************
* *
-\subsection{Recmpilation}
+\subsection{Recompilation}
* *
************************************************************************
-}
diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs
index 16b81015e1..77ea116042 100644
--- a/compiler/typecheck/TcRnMonad.hs
+++ b/compiler/typecheck/TcRnMonad.hs
@@ -238,6 +238,8 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
maybe_rn_syntax empty_val
| dopt Opt_D_dump_rn_ast dflags = Just empty_val
+ | gopt Opt_WriteHie dflags = Just empty_val
+
-- We want to serialize the documentation in the .hi-files,
-- and need to extract it from the renamed syntax first.
-- See 'ExtractDocs.extractDocs'.
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index c8b4989bf3..4bd05da485 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -409,6 +409,15 @@ instance Binary a => Binary [a] where
loop n = do a <- get bh; as <- loop (n-1); return (a:as)
loop len
+instance (Ix a, Binary a, Binary b) => Binary (Array a b) where
+ put_ bh arr = do
+ put_ bh $ bounds arr
+ put_ bh $ elems arr
+ get bh = do
+ bounds <- get bh
+ xs <- get bh
+ return $ listArray bounds xs
+
instance (Binary a, Binary b) => Binary (a,b) where
put_ bh (a,b) = do put_ bh a; put_ bh b
get bh = do a <- get bh
@@ -1147,14 +1156,27 @@ instance Binary a => Binary (Located a) where
x <- get bh
return (L l x)
+instance Binary RealSrcSpan where
+ put_ bh ss = do
+ put_ bh (srcSpanFile ss)
+ put_ bh (srcSpanStartLine ss)
+ put_ bh (srcSpanStartCol ss)
+ put_ bh (srcSpanEndLine ss)
+ put_ bh (srcSpanEndCol ss)
+
+ get bh = do
+ f <- get bh
+ sl <- get bh
+ sc <- get bh
+ el <- get bh
+ ec <- get bh
+ return (mkRealSrcSpan (mkRealSrcLoc f sl sc)
+ (mkRealSrcLoc f el ec))
+
instance Binary SrcSpan where
put_ bh (RealSrcSpan ss) = do
putByte bh 0
- put_ bh (srcSpanFile ss)
- put_ bh (srcSpanStartLine ss)
- put_ bh (srcSpanStartCol ss)
- put_ bh (srcSpanEndLine ss)
- put_ bh (srcSpanEndCol ss)
+ put_ bh ss
put_ bh (UnhelpfulSpan s) = do
putByte bh 1
@@ -1163,13 +1185,8 @@ instance Binary SrcSpan where
get bh = do
h <- getByte bh
case h of
- 0 -> do f <- get bh
- sl <- get bh
- sc <- get bh
- el <- get bh
- ec <- get bh
- return (mkSrcSpan (mkSrcLoc f sl sc)
- (mkSrcLoc f el ec))
+ 0 -> do ss <- get bh
+ return (RealSrcSpan ss)
_ -> do s <- get bh
return (UnhelpfulSpan s)
diff --git a/docs/users_guide/8.8.1-notes.rst b/docs/users_guide/8.8.1-notes.rst
index ea38029a0a..6e52a63038 100644
--- a/docs/users_guide/8.8.1-notes.rst
+++ b/docs/users_guide/8.8.1-notes.rst
@@ -103,6 +103,10 @@ Runtime system
- The output filename used for :ref:`eventlog output <rts-eventlog>` can now be
specified with the :rts-flag:`-ol` flag.
+- Add support for generating a new type of output: extended interfaces files.
+ Generation of these files, which sport a ``.hie`` suffix, is enabled via the
+ ``-fwrite-ide-info`` flag. See :ref:`hie-options` for more information.
+
Template Haskell
~~~~~~~~~~~~~~~~
diff --git a/docs/users_guide/separate_compilation.rst b/docs/users_guide/separate_compilation.rst
index d17ed2111c..338c438eea 100644
--- a/docs/users_guide/separate_compilation.rst
+++ b/docs/users_guide/separate_compilation.rst
@@ -288,6 +288,14 @@ Redirecting the compilation output(s)
Redirects all generated interface files into ⟨dir⟩, instead of the
default.
+.. ghc-flag:: -hiedir ⟨dir⟩
+ :shortdesc: set directory for extended interface files
+ :type: dynamic
+ :category:
+
+ Redirects all generated extended interface files into ⟨dir⟩, instead of
+ the default.
+
.. ghc-flag:: -stubdir ⟨dir⟩
:shortdesc: redirect FFI stub files
:type: dynamic
@@ -351,6 +359,12 @@ Redirecting the compilation output(s)
to get the profiled version.
+.. ghc-flag:: -hiesuf ⟨suffix⟩
+ :shortdesc: set the suffix to use for extended interface files
+ :type: dynamic
+
+ The ``-hiesuf`` ⟨suffix⟩ will change the ``.hie`` file suffix for
+ extended interface files to whatever you specify.
.. ghc-flag:: -hcsuf ⟨suffix⟩
:shortdesc: set the suffix to use for intermediate C files
@@ -534,6 +548,46 @@ Other options related to interface files
where ⟨file⟩ is the name of an interface file, dumps the contents of
that interface in a human-readable format. See :ref:`modes`.
+.. _hie-options:
+
+Options related to extended interface files
+-------------------------------------------
+
+.. index::
+ single: extended interface files, options
+
+GHC builds up a wealth of information about a Haskell source file as it compiles
+it. Extended interface files are a way of persisting some of this information to
+disk so that external tools, such as IDE's, can avoid parsing, typechecking, and
+renaming all over again. These files contain
+
+ * a simplified AST
+
+ * nodes are annotated with source positions and types
+ * identifiers are annotated with scope information
+
+ * the raw bytes of the initial Haskell source
+
+The GHC API exposes functions for reading and writing these files.
+
+.. ghc-flag:: -fwrite-ide-info
+ :shortdesc: Write out extended interface files
+ :type: dynamic
+ :category: extended-interface-files
+
+ Writes out extended interface files alongisde regular enterface files.
+ Just like regular interface files, GHC has a recompilation check to detect
+ out of date or missing extended interface files.
+
+.. ghc-flag:: -fvalidate-ide-info
+ :shortdesc: Perform some sanity checks on the extended interface files
+ :type: dynamic
+ :category: extended-interface-files
+
+ Runs a series of sanity checks and lints on the extended interface files
+ that are being written out. These include testing things properties such as
+ variables not occuring outside of their expected scopes.
+
.. _recomp:
The recompilation checker
diff --git a/docs/users_guide/using.rst b/docs/users_guide/using.rst
index 553269cc75..420e2d3bfc 100644
--- a/docs/users_guide/using.rst
+++ b/docs/users_guide/using.rst
@@ -203,6 +203,9 @@ the "right thing" to happen to those files.
``.hi``
A Haskell interface file, probably compiler-generated.
+``.hie``
+ An extended Haskell interface file, produced by the Haskell compiler.
+
``.hc``
Intermediate C file produced by the Haskell compiler.
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index b656d1f8b8..e2cad2cffd 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -106,9 +106,7 @@ commonGhcArgs = do
, map ("-optc" ++) <$> getStagedSettingList ConfCcArgs
, map ("-optP" ++) <$> getStagedSettingList ConfCppArgs
, map ("-optP" ++) <$> getContextData cppOpts
- , arg "-odir" , arg path
- , arg "-hidir" , arg path
- , arg "-stubdir" , arg path ]
+ , arg "-outputdir", arg path ]
-- TODO: Do '-ticky' in all debug ways?
wayGhcArgs :: Args
diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk
index 45dc0ce988..9166abc378 100644
--- a/rules/distdir-way-opts.mk
+++ b/rules/distdir-way-opts.mk
@@ -153,7 +153,7 @@ $1_$2_$3_MOST_HC_OPTS = \
$1_$2_$3_MOST_DIR_HC_OPTS = \
$$($1_$2_$3_MOST_HC_OPTS) \
- -odir $1/$2/build -hidir $1/$2/build -stubdir $1/$2/build
+ -outputdir $1/$2/build
# NB. CONF_HC_OPTS_STAGE$4 has to be late enough to override $1_$2_HC_OPTS, so
# that -O0 is effective (see #5484)
diff --git a/testsuite/tests/driver/recomp018/A.hs b/testsuite/tests/driver/recomp018/A.hs
new file mode 100644
index 0000000000..e9c922f03a
--- /dev/null
+++ b/testsuite/tests/driver/recomp018/A.hs
@@ -0,0 +1,7 @@
+module A where
+
+import B
+import C
+
+foo :: Int
+foo = 4
diff --git a/testsuite/tests/driver/recomp018/B.hs b/testsuite/tests/driver/recomp018/B.hs
new file mode 100644
index 0000000000..aa2dfcc38f
--- /dev/null
+++ b/testsuite/tests/driver/recomp018/B.hs
@@ -0,0 +1,6 @@
+module B where
+
+data B a = B a
+
+b :: a -> B a
+b = B
diff --git a/testsuite/tests/driver/recomp018/C.hs b/testsuite/tests/driver/recomp018/C.hs
new file mode 100644
index 0000000000..43bb9dd632
--- /dev/null
+++ b/testsuite/tests/driver/recomp018/C.hs
@@ -0,0 +1,6 @@
+module C where
+
+data C a = C a
+
+c :: a -> C a
+c = C
diff --git a/testsuite/tests/driver/recomp018/Makefile b/testsuite/tests/driver/recomp018/Makefile
new file mode 100644
index 0000000000..fa18a54fe1
--- /dev/null
+++ b/testsuite/tests/driver/recomp018/Makefile
@@ -0,0 +1,30 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+# Recompilation tests for .hie files
+
+clean:
+ rm -f *.o *.hi *.hie
+
+recomp018: clean
+ echo 'first run'
+ '$(TEST_HC)' $(TEST_HC_OPTS) --make -fwrite-ide-info A.hs
+ sleep 1
+
+ # Check the .hie files have been created
+ test -f A.hie
+ test -f B.hie
+ test -f C.hie
+
+ # Remove some of those files
+ rm A.hie B.hie
+
+ # Recompile
+ echo 'second run'
+ '$(TEST_HC)' $(TEST_HC_OPTS) --make -fwrite-ide-info A.hs
+
+ # Check the .hie files have been created
+ test -f A.hie
+ test -f B.hie
+ test -f C.hie
diff --git a/testsuite/tests/driver/recomp018/all.T b/testsuite/tests/driver/recomp018/all.T
new file mode 100644
index 0000000000..0d8faf70ca
--- /dev/null
+++ b/testsuite/tests/driver/recomp018/all.T
@@ -0,0 +1,5 @@
+# Test for regenerating .hie files that are out of date or missing
+
+test('recomp018',
+ [extra_files(['A.hs', 'B.hs', 'C.hs'])],
+ run_command, ['$MAKE -s --no-print-directory recomp018'])
diff --git a/testsuite/tests/driver/recomp018/recomp018.stdout b/testsuite/tests/driver/recomp018/recomp018.stdout
new file mode 100644
index 0000000000..ff1b3c016d
--- /dev/null
+++ b/testsuite/tests/driver/recomp018/recomp018.stdout
@@ -0,0 +1,7 @@
+first run
+[1 of 3] Compiling B ( B.hs, B.o )
+[2 of 3] Compiling C ( C.hs, C.o )
+[3 of 3] Compiling A ( A.hs, A.o )
+second run
+[1 of 3] Compiling B ( B.hs, B.o ) [HIE file is missing]
+[3 of 3] Compiling A ( A.hs, A.o ) [HIE file is missing]
diff --git a/testsuite/tests/hiefile/Makefile b/testsuite/tests/hiefile/Makefile
new file mode 100644
index 0000000000..9a36a1c5fe
--- /dev/null
+++ b/testsuite/tests/hiefile/Makefile
@@ -0,0 +1,3 @@
+TOP=../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/testsuite/tests/hiefile/should_compile/CPP.hs b/testsuite/tests/hiefile/should_compile/CPP.hs
new file mode 100644
index 0000000000..f00ce031ea
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/CPP.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE CPP #-}
+module CPP where
+
+#define SOMETHING1
+
+foo :: String
+foo = {- " single quotes are fine in block comments
+ {- nested block comments are fine -}
+ -} "foo"
+
+#define SOMETHING2
+
+bar :: String
+bar = "block comment in a string is not a comment {- "
+
+#define SOMETHING3
+
+-- " single quotes are fine in line comments
+-- {- unclosed block comments are fine in line comments
+
+-- Multiline CPP is also fine
+#define FOO\
+ 1
+
+baz :: String
+baz = "line comment in a string is not a comment --"
diff --git a/testsuite/tests/hiefile/should_compile/CPP.stderr b/testsuite/tests/hiefile/should_compile/CPP.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/CPP.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/Constructors.hs b/testsuite/tests/hiefile/should_compile/Constructors.hs
new file mode 100644
index 0000000000..8cb465359b
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/Constructors.hs
@@ -0,0 +1,35 @@
+module Constructors where
+
+
+data Foo
+ = Bar
+ | Baz
+ | Quux Foo Int
+
+newtype Norf = Norf (Foo, [Foo], Foo)
+
+
+bar, baz, quux :: Foo
+bar = Bar
+baz = Baz
+quux = Quux quux 0
+
+
+unfoo :: Foo -> Int
+unfoo Bar = 0
+unfoo Baz = 0
+unfoo (Quux foo n) = 42 * n + unfoo foo
+
+
+unnorf :: Norf -> [Foo]
+unnorf (Norf (Bar, xs, Bar)) = xs
+unnorf (Norf (Baz, xs, Baz)) = reverse xs
+unnorf _ = undefined
+
+
+unnorf' :: Norf -> Int
+unnorf' x@(Norf (f1@(Quux _ n), _, f2@(Quux f3 _))) =
+ x' + n * unfoo f1 + aux f3
+ where
+ aux fx = unfoo f2 * unfoo fx * unfoo f3
+ x' = sum . map unfoo . unnorf $ x
diff --git a/testsuite/tests/hiefile/should_compile/Constructors.stderr b/testsuite/tests/hiefile/should_compile/Constructors.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/Constructors.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/all.T b/testsuite/tests/hiefile/should_compile/all.T
new file mode 100644
index 0000000000..9770bae587
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/all.T
@@ -0,0 +1,12 @@
+test('hie001', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie002', collect_compiler_stats(), compile, ['-fno-code -fwrite-ide-info'])
+test('hie003', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie004', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie005', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie006', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie007', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie008', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie009', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('hie010', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('CPP', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
+test('Constructors', normal, compile, ['-fno-code -fwrite-ide-info -fvalidate-ide-info'])
diff --git a/testsuite/tests/hiefile/should_compile/hie001.hs b/testsuite/tests/hiefile/should_compile/hie001.hs
new file mode 100644
index 0000000000..53fe63ecde
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie001.hs
@@ -0,0 +1,9 @@
+module Foo where
+
+data Foo = Bar { x :: Int, y :: Bool }
+
+foo a = a{x=2}
+
+bar = Bar{ x = 1, y = False}
+
+foobar = foo (id id bar)
diff --git a/testsuite/tests/hiefile/should_compile/hie001.stderr b/testsuite/tests/hiefile/should_compile/hie001.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie001.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie002.hs b/testsuite/tests/hiefile/should_compile/hie002.hs
new file mode 100644
index 0000000000..41146c7f70
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie002.hs
@@ -0,0 +1,3869 @@
+{-# OPTIONS_GHC -w #-}
+{-# OPTIONS -XMagicHash -XBangPatterns #-}
+module Grammar where
+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)
+
+-- The token type:
+data Token = TokenLet
+ | TokenIn
+ | TokenInt Int
+ | TokenSym String
+ | TokenEq
+ | TokenPlus
+ | TokenMinus
+ | TokenTimes
+ | TokenDiv
+ | TokenLParen
+ | TokenRParen
+ | TokenLCurl
+ | TokenRCurl
+ | TokenLRect
+ | TokenRRect
+ deriving (Eq,Show)
+
+-- parser produced by Happy Version 1.19.8
+
+newtype HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104 = HappyAbsSyn HappyAny
+type HappyAny = Happy_GHC_Exts.Any
+happyIn4 :: t4 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn4 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn4 #-}
+happyOut4 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t4
+happyOut4 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut4 #-}
+happyIn5 :: t5 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn5 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn5 #-}
+happyOut5 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t5
+happyOut5 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut5 #-}
+happyIn6 :: t6 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn6 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn6 #-}
+happyOut6 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t6
+happyOut6 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut6 #-}
+happyIn7 :: t7 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn7 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn7 #-}
+happyOut7 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t7
+happyOut7 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut7 #-}
+happyIn8 :: t8 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn8 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn8 #-}
+happyOut8 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t8
+happyOut8 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut8 #-}
+happyIn9 :: t9 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn9 #-}
+happyOut9 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t9
+happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut9 #-}
+happyIn10 :: t10 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn10 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn10 #-}
+happyOut10 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t10
+happyOut10 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut10 #-}
+happyIn11 :: t11 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn11 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn11 #-}
+happyOut11 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t11
+happyOut11 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut11 #-}
+happyIn12 :: t12 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn12 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn12 #-}
+happyOut12 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t12
+happyOut12 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut12 #-}
+happyIn13 :: t13 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn13 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn13 #-}
+happyOut13 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t13
+happyOut13 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut13 #-}
+happyIn14 :: t14 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn14 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn14 #-}
+happyOut14 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t14
+happyOut14 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut14 #-}
+happyIn15 :: t15 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn15 #-}
+happyOut15 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t15
+happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut15 #-}
+happyIn16 :: t16 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn16 #-}
+happyOut16 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t16
+happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut16 #-}
+happyIn17 :: t17 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn17 #-}
+happyOut17 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t17
+happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut17 #-}
+happyIn18 :: t18 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn18 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn18 #-}
+happyOut18 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t18
+happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut18 #-}
+happyIn19 :: t19 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn19 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn19 #-}
+happyOut19 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t19
+happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut19 #-}
+happyIn20 :: t20 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn20 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn20 #-}
+happyOut20 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t20
+happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut20 #-}
+happyIn21 :: t21 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn21 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn21 #-}
+happyOut21 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t21
+happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut21 #-}
+happyIn22 :: t22 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn22 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn22 #-}
+happyOut22 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t22
+happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut22 #-}
+happyIn23 :: t23 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn23 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn23 #-}
+happyOut23 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t23
+happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut23 #-}
+happyIn24 :: t24 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn24 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn24 #-}
+happyOut24 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t24
+happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut24 #-}
+happyIn25 :: t25 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn25 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn25 #-}
+happyOut25 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t25
+happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut25 #-}
+happyIn26 :: t26 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn26 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn26 #-}
+happyOut26 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t26
+happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut26 #-}
+happyIn27 :: t27 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn27 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn27 #-}
+happyOut27 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t27
+happyOut27 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut27 #-}
+happyIn28 :: t28 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn28 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn28 #-}
+happyOut28 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t28
+happyOut28 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut28 #-}
+happyIn29 :: t29 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn29 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn29 #-}
+happyOut29 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t29
+happyOut29 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut29 #-}
+happyIn30 :: t30 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn30 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn30 #-}
+happyOut30 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t30
+happyOut30 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut30 #-}
+happyIn31 :: t31 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn31 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn31 #-}
+happyOut31 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t31
+happyOut31 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut31 #-}
+happyIn32 :: t32 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn32 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn32 #-}
+happyOut32 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t32
+happyOut32 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut32 #-}
+happyIn33 :: t33 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn33 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn33 #-}
+happyOut33 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t33
+happyOut33 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut33 #-}
+happyIn34 :: t34 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn34 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn34 #-}
+happyOut34 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t34
+happyOut34 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut34 #-}
+happyIn35 :: t35 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn35 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn35 #-}
+happyOut35 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t35
+happyOut35 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut35 #-}
+happyIn36 :: t36 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn36 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn36 #-}
+happyOut36 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t36
+happyOut36 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut36 #-}
+happyIn37 :: t37 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn37 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn37 #-}
+happyOut37 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t37
+happyOut37 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut37 #-}
+happyIn38 :: t38 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn38 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn38 #-}
+happyOut38 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t38
+happyOut38 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut38 #-}
+happyIn39 :: t39 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn39 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn39 #-}
+happyOut39 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t39
+happyOut39 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut39 #-}
+happyIn40 :: t40 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn40 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn40 #-}
+happyOut40 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t40
+happyOut40 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut40 #-}
+happyIn41 :: t41 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn41 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn41 #-}
+happyOut41 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t41
+happyOut41 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut41 #-}
+happyIn42 :: t42 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn42 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn42 #-}
+happyOut42 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t42
+happyOut42 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut42 #-}
+happyIn43 :: t43 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn43 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn43 #-}
+happyOut43 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t43
+happyOut43 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut43 #-}
+happyIn44 :: t44 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn44 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn44 #-}
+happyOut44 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t44
+happyOut44 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut44 #-}
+happyIn45 :: t45 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn45 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn45 #-}
+happyOut45 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t45
+happyOut45 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut45 #-}
+happyIn46 :: t46 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn46 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn46 #-}
+happyOut46 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t46
+happyOut46 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut46 #-}
+happyIn47 :: t47 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn47 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn47 #-}
+happyOut47 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t47
+happyOut47 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut47 #-}
+happyIn48 :: t48 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn48 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn48 #-}
+happyOut48 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t48
+happyOut48 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut48 #-}
+happyIn49 :: t49 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn49 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn49 #-}
+happyOut49 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t49
+happyOut49 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut49 #-}
+happyIn50 :: t50 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn50 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn50 #-}
+happyOut50 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t50
+happyOut50 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut50 #-}
+happyIn51 :: t51 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn51 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn51 #-}
+happyOut51 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t51
+happyOut51 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut51 #-}
+happyIn52 :: t52 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn52 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn52 #-}
+happyOut52 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t52
+happyOut52 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut52 #-}
+happyIn53 :: t53 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn53 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn53 #-}
+happyOut53 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t53
+happyOut53 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut53 #-}
+happyIn54 :: t54 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn54 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn54 #-}
+happyOut54 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t54
+happyOut54 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut54 #-}
+happyIn55 :: t55 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn55 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn55 #-}
+happyOut55 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t55
+happyOut55 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut55 #-}
+happyIn56 :: t56 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn56 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn56 #-}
+happyOut56 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t56
+happyOut56 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut56 #-}
+happyIn57 :: t57 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn57 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn57 #-}
+happyOut57 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t57
+happyOut57 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut57 #-}
+happyIn58 :: t58 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn58 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn58 #-}
+happyOut58 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t58
+happyOut58 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut58 #-}
+happyIn59 :: t59 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn59 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn59 #-}
+happyOut59 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t59
+happyOut59 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut59 #-}
+happyIn60 :: t60 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn60 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn60 #-}
+happyOut60 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t60
+happyOut60 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut60 #-}
+happyIn61 :: t61 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn61 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn61 #-}
+happyOut61 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t61
+happyOut61 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut61 #-}
+happyIn62 :: t62 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn62 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn62 #-}
+happyOut62 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t62
+happyOut62 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut62 #-}
+happyIn63 :: t63 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn63 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn63 #-}
+happyOut63 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t63
+happyOut63 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut63 #-}
+happyIn64 :: t64 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn64 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn64 #-}
+happyOut64 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t64
+happyOut64 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut64 #-}
+happyIn65 :: t65 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn65 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn65 #-}
+happyOut65 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t65
+happyOut65 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut65 #-}
+happyIn66 :: t66 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn66 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn66 #-}
+happyOut66 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t66
+happyOut66 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut66 #-}
+happyIn67 :: t67 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn67 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn67 #-}
+happyOut67 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t67
+happyOut67 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut67 #-}
+happyIn68 :: t68 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn68 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn68 #-}
+happyOut68 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t68
+happyOut68 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut68 #-}
+happyIn69 :: t69 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn69 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn69 #-}
+happyOut69 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t69
+happyOut69 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut69 #-}
+happyIn70 :: t70 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn70 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn70 #-}
+happyOut70 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t70
+happyOut70 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut70 #-}
+happyIn71 :: t71 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn71 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn71 #-}
+happyOut71 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t71
+happyOut71 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut71 #-}
+happyIn72 :: t72 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn72 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn72 #-}
+happyOut72 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t72
+happyOut72 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut72 #-}
+happyIn73 :: t73 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn73 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn73 #-}
+happyOut73 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t73
+happyOut73 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut73 #-}
+happyIn74 :: t74 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn74 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn74 #-}
+happyOut74 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t74
+happyOut74 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut74 #-}
+happyIn75 :: t75 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn75 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn75 #-}
+happyOut75 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t75
+happyOut75 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut75 #-}
+happyIn76 :: t76 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn76 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn76 #-}
+happyOut76 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t76
+happyOut76 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut76 #-}
+happyIn77 :: t77 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn77 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn77 #-}
+happyOut77 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t77
+happyOut77 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut77 #-}
+happyIn78 :: t78 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn78 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn78 #-}
+happyOut78 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t78
+happyOut78 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut78 #-}
+happyIn79 :: t79 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn79 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn79 #-}
+happyOut79 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t79
+happyOut79 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut79 #-}
+happyIn80 :: t80 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn80 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn80 #-}
+happyOut80 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t80
+happyOut80 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut80 #-}
+happyIn81 :: t81 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn81 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn81 #-}
+happyOut81 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t81
+happyOut81 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut81 #-}
+happyIn82 :: t82 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn82 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn82 #-}
+happyOut82 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t82
+happyOut82 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut82 #-}
+happyIn83 :: t83 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn83 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn83 #-}
+happyOut83 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t83
+happyOut83 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut83 #-}
+happyIn84 :: t84 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn84 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn84 #-}
+happyOut84 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t84
+happyOut84 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut84 #-}
+happyIn85 :: t85 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn85 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn85 #-}
+happyOut85 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t85
+happyOut85 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut85 #-}
+happyIn86 :: t86 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn86 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn86 #-}
+happyOut86 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t86
+happyOut86 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut86 #-}
+happyIn87 :: t87 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn87 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn87 #-}
+happyOut87 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t87
+happyOut87 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut87 #-}
+happyIn88 :: t88 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn88 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn88 #-}
+happyOut88 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t88
+happyOut88 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut88 #-}
+happyIn89 :: t89 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn89 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn89 #-}
+happyOut89 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t89
+happyOut89 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut89 #-}
+happyIn90 :: t90 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn90 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn90 #-}
+happyOut90 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t90
+happyOut90 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut90 #-}
+happyIn91 :: t91 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn91 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn91 #-}
+happyOut91 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t91
+happyOut91 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut91 #-}
+happyIn92 :: t92 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn92 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn92 #-}
+happyOut92 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t92
+happyOut92 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut92 #-}
+happyIn93 :: t93 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn93 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn93 #-}
+happyOut93 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t93
+happyOut93 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut93 #-}
+happyIn94 :: t94 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn94 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn94 #-}
+happyOut94 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t94
+happyOut94 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut94 #-}
+happyIn95 :: t95 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn95 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn95 #-}
+happyOut95 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t95
+happyOut95 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut95 #-}
+happyIn96 :: t96 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn96 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn96 #-}
+happyOut96 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t96
+happyOut96 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut96 #-}
+happyIn97 :: t97 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn97 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn97 #-}
+happyOut97 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t97
+happyOut97 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut97 #-}
+happyIn98 :: t98 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn98 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn98 #-}
+happyOut98 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t98
+happyOut98 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut98 #-}
+happyIn99 :: t99 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn99 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn99 #-}
+happyOut99 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t99
+happyOut99 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut99 #-}
+happyIn100 :: t100 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn100 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn100 #-}
+happyOut100 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t100
+happyOut100 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut100 #-}
+happyIn101 :: t101 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn101 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn101 #-}
+happyOut101 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t101
+happyOut101 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut101 #-}
+happyIn102 :: t102 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn102 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn102 #-}
+happyOut102 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t102
+happyOut102 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut102 #-}
+happyIn103 :: t103 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn103 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn103 #-}
+happyOut103 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t103
+happyOut103 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut103 #-}
+happyIn104 :: t104 -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyIn104 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyIn104 #-}
+happyOut104 :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> t104
+happyOut104 x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyOut104 #-}
+happyInTok :: (Token) -> (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104)
+happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
+{-# INLINE happyInTok #-}
+happyOutTok :: (HappyAbsSyn t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104) -> (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\x4d\x2a\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\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x41\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x04\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\xe0\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\xe0\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\xe2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x4d\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x4d\x6a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\xe0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\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\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\x04\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\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\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\x04\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\x04\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\x04\x10\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\x04\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\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\x40\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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"#
+
+{-# NOINLINE happyExpListPerState #-}
+happyExpListPerState st =
+ token_strs_expected
+ where token_strs = ["error","%dummy","%start_parseCalc","Exp","Rule0","Rule1","Rule2","Rule3","Rule4","Rule5","Rule6","Rule7","Rule8","Rule9","Rule10","Rule11","Rule12","Rule13","Rule14","Rule15","Rule16","Rule17","Rule18","Rule19","Rule20","Rule21","Rule22","Rule23","Rule24","Rule25","Rule26","Rule27","Rule28","Rule29","Rule30","Rule31","Rule32","Rule33","Rule34","Rule35","Rule36","Rule37","Rule38","Rule39","Rule40","Rule41","Rule42","Rule43","Rule44","Rule45","Rule46","Rule47","Rule48","Rule49","Rule50","Rule51","Rule52","Rule53","Rule54","Rule55","Rule56","Rule57","Rule58","Rule59","Rule60","Rule61","Rule62","Rule63","Rule64","Rule65","Rule66","Rule67","Rule68","Rule69","Rule70","Rule71","Rule72","Rule73","Rule74","Rule75","Rule76","Rule77","Rule78","Rule79","Rule80","Rule81","Rule82","Rule83","Rule84","Rule85","Rule86","Rule87","Rule88","Rule89","Rule90","Rule91","Rule92","Rule93","Rule94","Rule95","Rule96","Rule97","Rule98","Rule99","let","in","int","var","'='","'+'","'-'","'*'","'/'","'('","')'","'{'","'}'","'['","']'","%eof"]
+ bit_start = st * 120
+ bit_end = (st + 1) * 120
+ read_bit = readArrayBit happyExpList
+ bits = map read_bit [bit_start..bit_end - 1]
+ bits_indexed = zip bits [0..119]
+ token_strs_expected = concatMap f bits_indexed
+ f (False, _) = []
+ f (True, nr) = [token_strs !! nr]
+
+happyActOffsets :: HappyAddr
+happyActOffsets = HappyA# "\x6d\x06\x51\x06\x59\x06\xd5\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x06\x6d\x06\x79\x06\x85\x06\x9b\x06\x5a\x07\xcd\x06\x5c\x07\x21\x07\x00\x00\x91\x06\x91\x06\x91\x06\x91\x06\x63\x06\x91\x06\x00\x00\x00\x00\xbf\x06\xbf\x06\x20\x07\x00\x00\x91\x06\x91\x06\xcb\x06\x00\x00\x91\x06\x91\x06\x52\x06\x00\x00\x55\x06\x00\x00\x49\x07\x61\x07\xd4\x06\x00\x00\x55\x07\x65\x07\x2a\x07\x00\x00\x51\x07\x91\x06\x2b\x07\x00\x00\x5f\x06\xd6\x06\xdc\x06\x00\x00\x50\x06\x56\x06\x58\x06\x00\x00\x67\x06\x00\x00\x6f\x06\x00\x00\x70\x06\x00\x00\xdd\x06\x00\x00\xdf\x06\x00\x00\xe1\x06\x00\x00\x2c\x07\x00\x00\x69\x07\x2d\x07\x00\x00\xe3\x06\x00\x00\xe4\x06\x00\x00\xe5\x06\x00\x00\x72\x06\x00\x00\x75\x06\x00\x00\x7f\x06\x00\x00\x87\x06\x00\x00\x88\x06\x00\x00\x8a\x06\x00\x00\xe8\x06\x00\x00\xea\x06\x00\x00\xec\x06\x00\x00\x2e\x07\x00\x00\x2f\x07\x00\x00\xf0\x06\x00\x00\xf1\x06\x00\x00\xf3\x06\x00\x00\x8d\x06\x00\x00\x97\x06\x00\x00\x9d\x06\x00\x00\xa2\x06\x00\x00\xa4\x06\x00\x00\xa5\x06\x00\x00\xf5\x06\x00\x00\xf7\x06\x00\x00\xf8\x06\x00\x00\x30\x07\x00\x00\x31\x07\x00\x00\xf9\x06\x00\x00\xfc\x06\x00\x00\xfe\x06\x00\x00\xa6\x06\x00\x00\xa8\x06\x00\x00\xaa\x06\x00\x00\xab\x06\x00\x00\xac\x06\x00\x00\xad\x06\x00\x00\x00\x07\x00\x00\x04\x07\x00\x00\x05\x07\x00\x00\x3a\x07\x00\x00\x3b\x07\x00\x00\x07\x07\x00\x00\x09\x07\x00\x00\x0b\x07\x00\x00\xaf\x06\x00\x00\xb3\x06\x00\x00\xb5\x06\x00\x00\xba\x06\x00\x00\x47\x06\x00\x00\x60\x06\x00\x00\x0c\x07\x00\x00\x11\x07\x00\x00\x13\x07\x00\x00\x3c\x07\x00\x00\x3d\x07\x00\x00\x00\x00\x00\x00\x0d\x07\x00\x00\x00\x00\x00\x00\xbc\x06\x00\x00\xbd\x06\x00\x00\x10\x07\x00\x00\x3e\x07\x00\x00\x3f\x07\x00\x00\x12\x07\x00\x00\xbe\x06\x00\x00\xc0\x06\x00\x00\x14\x07\x00\x00\x40\x07\x00\x00\x41\x07\x00\x00\x18\x07\x00\x00\xc2\x06\x00\x00\xc3\x06\x00\x00\x19\x07\x00\x00\x4a\x07\x00\x00\x4b\x07\x00\x00\x15\x07\x00\x00\xbb\x06\x00\x00\x00\x00\x00\x00\x57\x07\x00\x00\x00\x00\x00\x00"#
+
+happyGotoOffsets :: HappyAddr
+happyGotoOffsets = HappyA# "\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x66\x00\xcb\x00\x30\x01\x95\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfa\x01\x5f\x02\xc4\x02\x29\x03\x00\x00\x8e\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf3\x03\x58\x04\x00\x00\x00\x00\xbd\x04\x22\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x05\x00\x00\x00\x00\xec\x05\x00\x00\x00\x00\x00\x00\xec\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
+
+happyAdjustOffset :: Happy_GHC_Exts.Int# -> Happy_GHC_Exts.Int#
+happyAdjustOffset off = off
+
+happyDefActions :: HappyAddr
+happyDefActions = HappyA# "\x00\x00\x00\x00\x00\x00\x00\x00\xf5\xff\xf4\xff\xf3\xff\xf2\xff\xf1\xff\xf0\xff\xef\xff\xee\xff\xed\xff\xec\xff\xeb\xff\xea\xff\xe9\xff\xe8\xff\xe7\xff\xe6\xff\xe5\xff\xe4\xff\xe3\xff\xe2\xff\xe1\xff\xe0\xff\xdf\xff\xde\xff\xdd\xff\xdc\xff\xdb\xff\xda\xff\xd9\xff\xd8\xff\xd7\xff\xd6\xff\xd5\xff\xd4\xff\xd3\xff\xd2\xff\xd1\xff\xd0\xff\xcf\xff\xce\xff\xcd\xff\xcc\xff\xcb\xff\xca\xff\xc9\xff\xc8\xff\xc7\xff\xc6\xff\xc5\xff\xc4\xff\xc3\xff\xc2\xff\xc1\xff\xc0\xff\xbf\xff\xbe\xff\xbd\xff\xbc\xff\xbb\xff\xba\xff\xb9\xff\xb8\xff\xb7\xff\xb6\xff\xb5\xff\xb4\xff\xb3\xff\xb2\xff\xb1\xff\xb0\xff\xaf\xff\xae\xff\xad\xff\xac\xff\xab\xff\xaa\xff\xa9\xff\xa8\xff\xa7\xff\xa6\xff\xa5\xff\xa4\xff\xa3\xff\xa2\xff\xa1\xff\xa0\xff\x9f\xff\x9e\xff\x9d\xff\x9c\xff\x9b\xff\x9a\xff\x99\xff\x98\xff\x97\xff\x96\xff\x95\xff\x94\xff\x93\xff\x92\xff\xf7\xff\xf6\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf6\xff\x00\x00\xf6\xff\x00\x00\xf8\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfa\xff\xfb\xff\xfc\xff\xfd\xff\x00\x00\xf9\xff\x00\x00\x00\x00\x00\x00\x91\xff\x00\x00\x00\x00\x00\x00\x69\xff\x00\x00\x68\xff\x00\x00\x00\x00\x00\x00\x90\xff\x00\x00\x00\x00\x00\x00\x7d\xff\x00\x00\x00\x00\x00\x00\x7c\xff\x00\x00\x00\x00\x00\x00\x8f\xff\x00\x00\x00\x00\x00\x00\x67\xff\x00\x00\x66\xff\x00\x00\x55\xff\xf7\xff\x41\xff\x00\x00\x8e\xff\x00\x00\x4b\xff\xf7\xff\x37\xff\x00\x00\x7b\xff\xfe\xff\x00\x00\x7a\xff\x00\x00\x36\xff\x00\x00\x4a\xff\x00\x00\x8d\xff\x00\x00\x40\xff\x00\x00\x54\xff\x00\x00\x65\xff\x00\x00\x64\xff\x00\x00\x53\xff\x00\x00\x3f\xff\x00\x00\x8c\xff\x00\x00\x49\xff\x00\x00\x35\xff\x00\x00\x79\xff\x00\x00\x78\xff\x00\x00\x34\xff\x00\x00\x48\xff\x00\x00\x8b\xff\x00\x00\x3e\xff\x00\x00\x52\xff\x00\x00\x63\xff\x00\x00\x62\xff\x00\x00\x51\xff\x00\x00\x3d\xff\x00\x00\x8a\xff\x00\x00\x47\xff\x00\x00\x33\xff\x00\x00\x77\xff\x00\x00\x76\xff\x00\x00\x32\xff\x00\x00\x46\xff\x00\x00\x89\xff\x00\x00\x3c\xff\x00\x00\x50\xff\x00\x00\x61\xff\x00\x00\x60\xff\x00\x00\x4f\xff\x00\x00\x3b\xff\x00\x00\x88\xff\x00\x00\x45\xff\x00\x00\x31\xff\x00\x00\x75\xff\x00\x00\x74\xff\x00\x00\x30\xff\x00\x00\x44\xff\x00\x00\x87\xff\x00\x00\x3a\xff\x00\x00\x4e\xff\x00\x00\x5f\xff\x00\x00\x5e\xff\x00\x00\x4d\xff\x00\x00\x39\xff\x00\x00\x86\xff\x00\x00\x43\xff\x00\x00\x2f\xff\x00\x00\x73\xff\x00\x00\x72\xff\x2e\xff\x42\xff\x00\x00\x85\xff\x38\xff\x4c\xff\x00\x00\x5d\xff\x00\x00\x5c\xff\x00\x00\x84\xff\x00\x00\x71\xff\x00\x00\x70\xff\x00\x00\x83\xff\x00\x00\x5b\xff\x00\x00\x5a\xff\x00\x00\x82\xff\x00\x00\x6f\xff\x00\x00\x6e\xff\x00\x00\x81\xff\x00\x00\x59\xff\x00\x00\x58\xff\x00\x00\x80\xff\x00\x00\x6d\xff\x00\x00\x6c\xff\x00\x00\x7f\xff\x00\x00\x57\xff\x56\xff\x7e\xff\x00\x00\x6b\xff\x6a\xff"#
+
+happyCheck :: HappyAddr
+happyCheck = HappyA# "\xff\xff\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x01\x00\x01\x00\x03\x00\x04\x00\x03\x00\x0f\x00\x07\x00\x03\x00\x03\x00\x0a\x00\x03\x00\x0c\x00\x04\x00\x0e\x00\x0f\x00\x01\x00\x0f\x00\x03\x00\x04\x00\x0f\x00\x0f\x00\x07\x00\x0f\x00\x05\x00\x0a\x00\x03\x00\x0c\x00\x0d\x00\x0e\x00\x01\x00\x0f\x00\x03\x00\x04\x00\x03\x00\x03\x00\x07\x00\x03\x00\x0f\x00\x0a\x00\x03\x00\x0c\x00\x01\x00\x0e\x00\x03\x00\x04\x00\x0f\x00\x0f\x00\x07\x00\x0f\x00\x03\x00\x0a\x00\x0f\x00\x0c\x00\x01\x00\x0e\x00\x03\x00\x04\x00\x03\x00\x03\x00\x07\x00\x03\x00\x0f\x00\x0a\x00\x03\x00\x0c\x00\x01\x00\x0e\x00\x03\x00\x04\x00\x0f\x00\x0f\x00\x07\x00\x0f\x00\x03\x00\x0a\x00\x0f\x00\x0c\x00\x03\x00\x0e\x00\x03\x00\x06\x00\x07\x00\x08\x00\x09\x00\x03\x00\x0f\x00\x03\x00\x03\x00\x03\x00\x0f\x00\x03\x00\x0f\x00\x03\x00\x03\x00\x03\x00\x03\x00\x0f\x00\x03\x00\x0f\x00\x0f\x00\x0f\x00\x03\x00\x0f\x00\x03\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x03\x00\x0f\x00\x03\x00\x03\x00\x03\x00\x0f\x00\x03\x00\x0f\x00\x03\x00\x03\x00\x08\x00\x09\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x03\x00\x0f\x00\x03\x00\x0f\x00\x0f\x00\x06\x00\x07\x00\x08\x00\x09\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x06\x00\x07\x00\x08\x00\x09\x00\x03\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x10\x00\x03\x00\x03\x00\x03\x00\x0d\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x0d\x00\x0d\x00\x03\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x03\x00\x03\x00\x0d\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x0d\x00\x0d\x00\x03\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x03\x00\x03\x00\x0d\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x03\x00\x0d\x00\x0d\x00\x0d\x00\x03\x00\x03\x00\x0d\x00\x0d\x00\x0d\x00\x0d\x00\x0d\x00\x0d\x00\x03\x00\x03\x00\x0d\x00\x0d\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0b\x00\x0b\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x03\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x0b\x00\x03\x00\x03\x00\x06\x00\x07\x00\x08\x00\x09\x00\x02\x00\x0b\x00\x0b\x00\x0b\x00\x06\x00\x07\x00\x08\x00\x09\x00\x06\x00\x07\x00\x08\x00\x09\x00\x05\x00\x0b\x00\x05\x00\x0b\x00\xff\xff\x0a\x00\xff\xff\x0a\x00\x06\x00\x07\x00\x08\x00\x09\x00\x06\x00\x07\x00\x08\x00\x09\x00\x06\x00\x07\x00\x08\x00\x09\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
+
+happyTable :: HappyAddr
+happyTable = HappyA# "\x00\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x73\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x72\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x70\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x6e\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x7d\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x7c\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x7b\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x7a\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x92\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x8f\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x8e\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x8b\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x8a\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\xac\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x7b\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x03\x00\x03\x00\xa3\x00\x6a\x00\x89\x00\x25\x01\x6b\x00\x9d\x00\xa1\x00\x6c\x00\x9f\x00\x6d\x00\x79\x00\x6e\x00\xa4\x00\x03\x00\x8a\x00\xa9\x00\x6a\x00\x9e\x00\xa2\x00\x6b\x00\xa0\x00\x7a\x00\x6c\x00\xba\x00\x6d\x00\xaa\x00\x6e\x00\x03\x00\x24\x01\x69\x00\x6a\x00\xb8\x00\xb6\x00\x6b\x00\xc0\x00\xbb\x00\x6c\x00\xbe\x00\x6d\x00\x03\x00\x6e\x00\x69\x00\x72\x00\xb9\x00\xb7\x00\x6b\x00\xc1\x00\xbc\x00\x6c\x00\xbf\x00\x6d\x00\x03\x00\x6e\x00\x69\x00\x70\x00\xd6\x00\xd4\x00\x6b\x00\xd2\x00\xbd\x00\x6c\x00\xdc\x00\x6d\x00\x03\x00\x6e\x00\x69\x00\x6a\x00\xd7\x00\xd5\x00\x6b\x00\xd3\x00\xda\x00\x6c\x00\xdd\x00\x6d\x00\x87\x00\x6e\x00\xd8\x00\x75\x00\x76\x00\x77\x00\x78\x00\xf2\x00\xdb\x00\xf0\x00\xee\x00\xf8\x00\x88\x00\xf6\x00\xd9\x00\xf4\x00\x0e\x01\x0c\x01\x0a\x01\xf3\x00\x14\x01\xf1\x00\xef\x00\xf9\x00\x12\x01\xf7\x00\x10\x01\xf5\x00\x0f\x01\x0d\x01\x0b\x01\x26\x01\x15\x01\x28\x01\x32\x01\x34\x01\x13\x01\x3e\x01\x11\x01\x40\x01\x4a\x01\x77\x00\x78\x00\x27\x01\x4c\x01\x29\x01\x33\x01\x35\x01\x8d\x00\x3f\x01\x83\x00\x41\x01\x4b\x01\x75\x00\x76\x00\x77\x00\x78\x00\x99\x00\x8e\x00\xa7\x00\x84\x00\x75\x00\x76\x00\x77\x00\x78\x00\xa5\x00\xb4\x00\x9a\x00\xb2\x00\xa8\x00\xb0\x00\xff\xff\xc6\x00\xc4\x00\xc2\x00\xa6\x00\xb5\x00\xd0\x00\xb3\x00\xce\x00\xb1\x00\xcc\x00\xc7\x00\xc5\x00\xc3\x00\xe2\x00\xe0\x00\xd1\x00\xde\x00\xcf\x00\xec\x00\xcd\x00\xea\x00\xe8\x00\xfe\x00\xe3\x00\xe1\x00\xfc\x00\xdf\x00\xfa\x00\xed\x00\x08\x01\xeb\x00\xe9\x00\xff\x00\x06\x01\x04\x01\xfd\x00\x1a\x01\xfb\x00\x18\x01\x09\x01\x16\x01\x22\x01\x2a\x01\x07\x01\x05\x01\x30\x01\x1b\x01\x36\x01\x19\x01\x3c\x01\x17\x01\x23\x01\x2b\x01\x42\x01\x48\x01\x31\x01\x21\x01\x37\x01\x20\x01\x3d\x01\x4d\x01\x91\x00\x7f\x00\x43\x01\x49\x01\x75\x00\x76\x00\x77\x00\x78\x00\x92\x00\x80\x00\x95\x00\xab\x00\xae\x00\xc8\x00\xca\x00\xe4\x00\xe6\x00\x00\x01\x96\x00\xac\x00\xaf\x00\xc9\x00\xcb\x00\xe5\x00\xe7\x00\x01\x01\x02\x01\x1c\x01\x1e\x01\x2c\x01\x2e\x01\x38\x01\x3a\x01\x44\x01\x03\x01\x1d\x01\x1f\x01\x2d\x01\x2f\x01\x39\x01\x3b\x01\x45\x01\x46\x01\x4e\x01\x75\x00\x76\x00\x77\x00\x78\x00\x94\x00\x9c\x00\x47\x01\x4f\x01\x75\x00\x76\x00\x77\x00\x78\x00\x75\x00\x76\x00\x77\x00\x78\x00\x85\x00\x98\x00\x81\x00\x50\x01\x00\x00\x86\x00\x00\x00\x82\x00\x75\x00\x76\x00\x9b\x00\x78\x00\x75\x00\x76\x00\x97\x00\x78\x00\x75\x00\x76\x00\x77\x00\x78\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
+
+happyReduceArr = Happy_Data_Array.array (1, 209) [
+ (1 , happyReduce_1),
+ (2 , happyReduce_2),
+ (3 , happyReduce_3),
+ (4 , happyReduce_4),
+ (5 , happyReduce_5),
+ (6 , happyReduce_6),
+ (7 , happyReduce_7),
+ (8 , happyReduce_8),
+ (9 , happyReduce_9),
+ (10 , happyReduce_10),
+ (11 , happyReduce_11),
+ (12 , happyReduce_12),
+ (13 , happyReduce_13),
+ (14 , happyReduce_14),
+ (15 , happyReduce_15),
+ (16 , happyReduce_16),
+ (17 , happyReduce_17),
+ (18 , happyReduce_18),
+ (19 , happyReduce_19),
+ (20 , happyReduce_20),
+ (21 , happyReduce_21),
+ (22 , happyReduce_22),
+ (23 , happyReduce_23),
+ (24 , happyReduce_24),
+ (25 , happyReduce_25),
+ (26 , happyReduce_26),
+ (27 , happyReduce_27),
+ (28 , happyReduce_28),
+ (29 , happyReduce_29),
+ (30 , happyReduce_30),
+ (31 , happyReduce_31),
+ (32 , happyReduce_32),
+ (33 , happyReduce_33),
+ (34 , happyReduce_34),
+ (35 , happyReduce_35),
+ (36 , happyReduce_36),
+ (37 , happyReduce_37),
+ (38 , happyReduce_38),
+ (39 , happyReduce_39),
+ (40 , happyReduce_40),
+ (41 , happyReduce_41),
+ (42 , happyReduce_42),
+ (43 , happyReduce_43),
+ (44 , happyReduce_44),
+ (45 , happyReduce_45),
+ (46 , happyReduce_46),
+ (47 , happyReduce_47),
+ (48 , happyReduce_48),
+ (49 , happyReduce_49),
+ (50 , happyReduce_50),
+ (51 , happyReduce_51),
+ (52 , happyReduce_52),
+ (53 , happyReduce_53),
+ (54 , happyReduce_54),
+ (55 , happyReduce_55),
+ (56 , happyReduce_56),
+ (57 , happyReduce_57),
+ (58 , happyReduce_58),
+ (59 , happyReduce_59),
+ (60 , happyReduce_60),
+ (61 , happyReduce_61),
+ (62 , happyReduce_62),
+ (63 , happyReduce_63),
+ (64 , happyReduce_64),
+ (65 , happyReduce_65),
+ (66 , happyReduce_66),
+ (67 , happyReduce_67),
+ (68 , happyReduce_68),
+ (69 , happyReduce_69),
+ (70 , happyReduce_70),
+ (71 , happyReduce_71),
+ (72 , happyReduce_72),
+ (73 , happyReduce_73),
+ (74 , happyReduce_74),
+ (75 , happyReduce_75),
+ (76 , happyReduce_76),
+ (77 , happyReduce_77),
+ (78 , happyReduce_78),
+ (79 , happyReduce_79),
+ (80 , happyReduce_80),
+ (81 , happyReduce_81),
+ (82 , happyReduce_82),
+ (83 , happyReduce_83),
+ (84 , happyReduce_84),
+ (85 , happyReduce_85),
+ (86 , happyReduce_86),
+ (87 , happyReduce_87),
+ (88 , happyReduce_88),
+ (89 , happyReduce_89),
+ (90 , happyReduce_90),
+ (91 , happyReduce_91),
+ (92 , happyReduce_92),
+ (93 , happyReduce_93),
+ (94 , happyReduce_94),
+ (95 , happyReduce_95),
+ (96 , happyReduce_96),
+ (97 , happyReduce_97),
+ (98 , happyReduce_98),
+ (99 , happyReduce_99),
+ (100 , happyReduce_100),
+ (101 , happyReduce_101),
+ (102 , happyReduce_102),
+ (103 , happyReduce_103),
+ (104 , happyReduce_104),
+ (105 , happyReduce_105),
+ (106 , happyReduce_106),
+ (107 , happyReduce_107),
+ (108 , happyReduce_108),
+ (109 , happyReduce_109),
+ (110 , happyReduce_110),
+ (111 , happyReduce_111),
+ (112 , happyReduce_112),
+ (113 , happyReduce_113),
+ (114 , happyReduce_114),
+ (115 , happyReduce_115),
+ (116 , happyReduce_116),
+ (117 , happyReduce_117),
+ (118 , happyReduce_118),
+ (119 , happyReduce_119),
+ (120 , happyReduce_120),
+ (121 , happyReduce_121),
+ (122 , happyReduce_122),
+ (123 , happyReduce_123),
+ (124 , happyReduce_124),
+ (125 , happyReduce_125),
+ (126 , happyReduce_126),
+ (127 , happyReduce_127),
+ (128 , happyReduce_128),
+ (129 , happyReduce_129),
+ (130 , happyReduce_130),
+ (131 , happyReduce_131),
+ (132 , happyReduce_132),
+ (133 , happyReduce_133),
+ (134 , happyReduce_134),
+ (135 , happyReduce_135),
+ (136 , happyReduce_136),
+ (137 , happyReduce_137),
+ (138 , happyReduce_138),
+ (139 , happyReduce_139),
+ (140 , happyReduce_140),
+ (141 , happyReduce_141),
+ (142 , happyReduce_142),
+ (143 , happyReduce_143),
+ (144 , happyReduce_144),
+ (145 , happyReduce_145),
+ (146 , happyReduce_146),
+ (147 , happyReduce_147),
+ (148 , happyReduce_148),
+ (149 , happyReduce_149),
+ (150 , happyReduce_150),
+ (151 , happyReduce_151),
+ (152 , happyReduce_152),
+ (153 , happyReduce_153),
+ (154 , happyReduce_154),
+ (155 , happyReduce_155),
+ (156 , happyReduce_156),
+ (157 , happyReduce_157),
+ (158 , happyReduce_158),
+ (159 , happyReduce_159),
+ (160 , happyReduce_160),
+ (161 , happyReduce_161),
+ (162 , happyReduce_162),
+ (163 , happyReduce_163),
+ (164 , happyReduce_164),
+ (165 , happyReduce_165),
+ (166 , happyReduce_166),
+ (167 , happyReduce_167),
+ (168 , happyReduce_168),
+ (169 , happyReduce_169),
+ (170 , happyReduce_170),
+ (171 , happyReduce_171),
+ (172 , happyReduce_172),
+ (173 , happyReduce_173),
+ (174 , happyReduce_174),
+ (175 , happyReduce_175),
+ (176 , happyReduce_176),
+ (177 , happyReduce_177),
+ (178 , happyReduce_178),
+ (179 , happyReduce_179),
+ (180 , happyReduce_180),
+ (181 , happyReduce_181),
+ (182 , happyReduce_182),
+ (183 , happyReduce_183),
+ (184 , happyReduce_184),
+ (185 , happyReduce_185),
+ (186 , happyReduce_186),
+ (187 , happyReduce_187),
+ (188 , happyReduce_188),
+ (189 , happyReduce_189),
+ (190 , happyReduce_190),
+ (191 , happyReduce_191),
+ (192 , happyReduce_192),
+ (193 , happyReduce_193),
+ (194 , happyReduce_194),
+ (195 , happyReduce_195),
+ (196 , happyReduce_196),
+ (197 , happyReduce_197),
+ (198 , happyReduce_198),
+ (199 , happyReduce_199),
+ (200 , happyReduce_200),
+ (201 , happyReduce_201),
+ (202 , happyReduce_202),
+ (203 , happyReduce_203),
+ (204 , happyReduce_204),
+ (205 , happyReduce_205),
+ (206 , happyReduce_206),
+ (207 , happyReduce_207),
+ (208 , happyReduce_208),
+ (209 , happyReduce_209)
+ ]
+
+happy_n_terms = 17 :: Int
+happy_n_nonterms = 101 :: Int
+
+happyReduce_1 = happyReduce 6# 0# happyReduction_1
+happyReduction_1 (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_2 of { (TokenSym happy_var_2) ->
+ case happyOut4 happy_x_4 of { happy_var_4 ->
+ case happyOut4 happy_x_6 of { happy_var_6 ->
+ happyIn4
+ (Let happy_var_2 happy_var_4 happy_var_6
+ ) `HappyStk` happyRest}}}
+
+happyReduce_2 = happySpecReduce_3 0# happyReduction_2
+happyReduction_2 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_1 of { happy_var_1 ->
+ case happyOut4 happy_x_3 of { happy_var_3 ->
+ happyIn4
+ (Plus happy_var_1 happy_var_3
+ )}}
+
+happyReduce_3 = happySpecReduce_3 0# happyReduction_3
+happyReduction_3 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_1 of { happy_var_1 ->
+ case happyOut4 happy_x_3 of { happy_var_3 ->
+ happyIn4
+ (Minus happy_var_1 happy_var_3
+ )}}
+
+happyReduce_4 = happySpecReduce_3 0# happyReduction_4
+happyReduction_4 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_1 of { happy_var_1 ->
+ case happyOut4 happy_x_3 of { happy_var_3 ->
+ happyIn4
+ (Times happy_var_1 happy_var_3
+ )}}
+
+happyReduce_5 = happySpecReduce_3 0# happyReduction_5
+happyReduction_5 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_1 of { happy_var_1 ->
+ case happyOut4 happy_x_3 of { happy_var_3 ->
+ happyIn4
+ (Div happy_var_1 happy_var_3
+ )}}
+
+happyReduce_6 = happySpecReduce_3 0# happyReduction_6
+happyReduction_6 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn4
+ (happy_var_2
+ )}
+
+happyReduce_7 = happySpecReduce_2 0# happyReduction_7
+happyReduction_7 happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn4
+ (Negate happy_var_2
+ )}
+
+happyReduce_8 = happySpecReduce_1 0# happyReduction_8
+happyReduction_8 happy_x_1
+ = case happyOutTok happy_x_1 of { (TokenInt happy_var_1) ->
+ happyIn4
+ (Int happy_var_1
+ )}
+
+happyReduce_9 = happySpecReduce_1 0# happyReduction_9
+happyReduction_9 happy_x_1
+ = case happyOutTok happy_x_1 of { (TokenSym happy_var_1) ->
+ happyIn4
+ (Var happy_var_1
+ )}
+
+happyReduce_10 = happySpecReduce_1 0# happyReduction_10
+happyReduction_10 happy_x_1
+ = case happyOut5 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_11 = happySpecReduce_1 0# happyReduction_11
+happyReduction_11 happy_x_1
+ = case happyOut6 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_12 = happySpecReduce_1 0# happyReduction_12
+happyReduction_12 happy_x_1
+ = case happyOut7 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_13 = happySpecReduce_1 0# happyReduction_13
+happyReduction_13 happy_x_1
+ = case happyOut8 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_14 = happySpecReduce_1 0# happyReduction_14
+happyReduction_14 happy_x_1
+ = case happyOut9 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_15 = happySpecReduce_1 0# happyReduction_15
+happyReduction_15 happy_x_1
+ = case happyOut10 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_16 = happySpecReduce_1 0# happyReduction_16
+happyReduction_16 happy_x_1
+ = case happyOut11 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_17 = happySpecReduce_1 0# happyReduction_17
+happyReduction_17 happy_x_1
+ = case happyOut12 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_18 = happySpecReduce_1 0# happyReduction_18
+happyReduction_18 happy_x_1
+ = case happyOut13 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_19 = happySpecReduce_1 0# happyReduction_19
+happyReduction_19 happy_x_1
+ = case happyOut14 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_20 = happySpecReduce_1 0# happyReduction_20
+happyReduction_20 happy_x_1
+ = case happyOut15 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_21 = happySpecReduce_1 0# happyReduction_21
+happyReduction_21 happy_x_1
+ = case happyOut16 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_22 = happySpecReduce_1 0# happyReduction_22
+happyReduction_22 happy_x_1
+ = case happyOut17 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_23 = happySpecReduce_1 0# happyReduction_23
+happyReduction_23 happy_x_1
+ = case happyOut18 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_24 = happySpecReduce_1 0# happyReduction_24
+happyReduction_24 happy_x_1
+ = case happyOut19 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_25 = happySpecReduce_1 0# happyReduction_25
+happyReduction_25 happy_x_1
+ = case happyOut20 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_26 = happySpecReduce_1 0# happyReduction_26
+happyReduction_26 happy_x_1
+ = case happyOut21 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_27 = happySpecReduce_1 0# happyReduction_27
+happyReduction_27 happy_x_1
+ = case happyOut22 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_28 = happySpecReduce_1 0# happyReduction_28
+happyReduction_28 happy_x_1
+ = case happyOut23 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_29 = happySpecReduce_1 0# happyReduction_29
+happyReduction_29 happy_x_1
+ = case happyOut24 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_30 = happySpecReduce_1 0# happyReduction_30
+happyReduction_30 happy_x_1
+ = case happyOut25 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_31 = happySpecReduce_1 0# happyReduction_31
+happyReduction_31 happy_x_1
+ = case happyOut26 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_32 = happySpecReduce_1 0# happyReduction_32
+happyReduction_32 happy_x_1
+ = case happyOut27 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_33 = happySpecReduce_1 0# happyReduction_33
+happyReduction_33 happy_x_1
+ = case happyOut28 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_34 = happySpecReduce_1 0# happyReduction_34
+happyReduction_34 happy_x_1
+ = case happyOut29 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_35 = happySpecReduce_1 0# happyReduction_35
+happyReduction_35 happy_x_1
+ = case happyOut30 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_36 = happySpecReduce_1 0# happyReduction_36
+happyReduction_36 happy_x_1
+ = case happyOut31 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_37 = happySpecReduce_1 0# happyReduction_37
+happyReduction_37 happy_x_1
+ = case happyOut32 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_38 = happySpecReduce_1 0# happyReduction_38
+happyReduction_38 happy_x_1
+ = case happyOut33 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_39 = happySpecReduce_1 0# happyReduction_39
+happyReduction_39 happy_x_1
+ = case happyOut34 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_40 = happySpecReduce_1 0# happyReduction_40
+happyReduction_40 happy_x_1
+ = case happyOut35 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_41 = happySpecReduce_1 0# happyReduction_41
+happyReduction_41 happy_x_1
+ = case happyOut36 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_42 = happySpecReduce_1 0# happyReduction_42
+happyReduction_42 happy_x_1
+ = case happyOut37 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_43 = happySpecReduce_1 0# happyReduction_43
+happyReduction_43 happy_x_1
+ = case happyOut38 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_44 = happySpecReduce_1 0# happyReduction_44
+happyReduction_44 happy_x_1
+ = case happyOut39 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_45 = happySpecReduce_1 0# happyReduction_45
+happyReduction_45 happy_x_1
+ = case happyOut40 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_46 = happySpecReduce_1 0# happyReduction_46
+happyReduction_46 happy_x_1
+ = case happyOut41 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_47 = happySpecReduce_1 0# happyReduction_47
+happyReduction_47 happy_x_1
+ = case happyOut42 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_48 = happySpecReduce_1 0# happyReduction_48
+happyReduction_48 happy_x_1
+ = case happyOut43 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_49 = happySpecReduce_1 0# happyReduction_49
+happyReduction_49 happy_x_1
+ = case happyOut44 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_50 = happySpecReduce_1 0# happyReduction_50
+happyReduction_50 happy_x_1
+ = case happyOut45 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_51 = happySpecReduce_1 0# happyReduction_51
+happyReduction_51 happy_x_1
+ = case happyOut46 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_52 = happySpecReduce_1 0# happyReduction_52
+happyReduction_52 happy_x_1
+ = case happyOut47 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_53 = happySpecReduce_1 0# happyReduction_53
+happyReduction_53 happy_x_1
+ = case happyOut48 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_54 = happySpecReduce_1 0# happyReduction_54
+happyReduction_54 happy_x_1
+ = case happyOut49 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_55 = happySpecReduce_1 0# happyReduction_55
+happyReduction_55 happy_x_1
+ = case happyOut50 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_56 = happySpecReduce_1 0# happyReduction_56
+happyReduction_56 happy_x_1
+ = case happyOut51 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_57 = happySpecReduce_1 0# happyReduction_57
+happyReduction_57 happy_x_1
+ = case happyOut52 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_58 = happySpecReduce_1 0# happyReduction_58
+happyReduction_58 happy_x_1
+ = case happyOut53 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_59 = happySpecReduce_1 0# happyReduction_59
+happyReduction_59 happy_x_1
+ = case happyOut54 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_60 = happySpecReduce_1 0# happyReduction_60
+happyReduction_60 happy_x_1
+ = case happyOut55 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_61 = happySpecReduce_1 0# happyReduction_61
+happyReduction_61 happy_x_1
+ = case happyOut56 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_62 = happySpecReduce_1 0# happyReduction_62
+happyReduction_62 happy_x_1
+ = case happyOut57 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_63 = happySpecReduce_1 0# happyReduction_63
+happyReduction_63 happy_x_1
+ = case happyOut58 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_64 = happySpecReduce_1 0# happyReduction_64
+happyReduction_64 happy_x_1
+ = case happyOut59 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_65 = happySpecReduce_1 0# happyReduction_65
+happyReduction_65 happy_x_1
+ = case happyOut60 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_66 = happySpecReduce_1 0# happyReduction_66
+happyReduction_66 happy_x_1
+ = case happyOut61 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_67 = happySpecReduce_1 0# happyReduction_67
+happyReduction_67 happy_x_1
+ = case happyOut62 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_68 = happySpecReduce_1 0# happyReduction_68
+happyReduction_68 happy_x_1
+ = case happyOut63 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_69 = happySpecReduce_1 0# happyReduction_69
+happyReduction_69 happy_x_1
+ = case happyOut64 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_70 = happySpecReduce_1 0# happyReduction_70
+happyReduction_70 happy_x_1
+ = case happyOut65 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_71 = happySpecReduce_1 0# happyReduction_71
+happyReduction_71 happy_x_1
+ = case happyOut66 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_72 = happySpecReduce_1 0# happyReduction_72
+happyReduction_72 happy_x_1
+ = case happyOut67 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_73 = happySpecReduce_1 0# happyReduction_73
+happyReduction_73 happy_x_1
+ = case happyOut68 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_74 = happySpecReduce_1 0# happyReduction_74
+happyReduction_74 happy_x_1
+ = case happyOut69 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_75 = happySpecReduce_1 0# happyReduction_75
+happyReduction_75 happy_x_1
+ = case happyOut70 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_76 = happySpecReduce_1 0# happyReduction_76
+happyReduction_76 happy_x_1
+ = case happyOut71 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_77 = happySpecReduce_1 0# happyReduction_77
+happyReduction_77 happy_x_1
+ = case happyOut72 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_78 = happySpecReduce_1 0# happyReduction_78
+happyReduction_78 happy_x_1
+ = case happyOut73 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_79 = happySpecReduce_1 0# happyReduction_79
+happyReduction_79 happy_x_1
+ = case happyOut74 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_80 = happySpecReduce_1 0# happyReduction_80
+happyReduction_80 happy_x_1
+ = case happyOut75 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_81 = happySpecReduce_1 0# happyReduction_81
+happyReduction_81 happy_x_1
+ = case happyOut76 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_82 = happySpecReduce_1 0# happyReduction_82
+happyReduction_82 happy_x_1
+ = case happyOut77 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_83 = happySpecReduce_1 0# happyReduction_83
+happyReduction_83 happy_x_1
+ = case happyOut78 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_84 = happySpecReduce_1 0# happyReduction_84
+happyReduction_84 happy_x_1
+ = case happyOut79 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_85 = happySpecReduce_1 0# happyReduction_85
+happyReduction_85 happy_x_1
+ = case happyOut80 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_86 = happySpecReduce_1 0# happyReduction_86
+happyReduction_86 happy_x_1
+ = case happyOut81 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_87 = happySpecReduce_1 0# happyReduction_87
+happyReduction_87 happy_x_1
+ = case happyOut82 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_88 = happySpecReduce_1 0# happyReduction_88
+happyReduction_88 happy_x_1
+ = case happyOut83 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_89 = happySpecReduce_1 0# happyReduction_89
+happyReduction_89 happy_x_1
+ = case happyOut84 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_90 = happySpecReduce_1 0# happyReduction_90
+happyReduction_90 happy_x_1
+ = case happyOut85 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_91 = happySpecReduce_1 0# happyReduction_91
+happyReduction_91 happy_x_1
+ = case happyOut86 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_92 = happySpecReduce_1 0# happyReduction_92
+happyReduction_92 happy_x_1
+ = case happyOut87 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_93 = happySpecReduce_1 0# happyReduction_93
+happyReduction_93 happy_x_1
+ = case happyOut88 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_94 = happySpecReduce_1 0# happyReduction_94
+happyReduction_94 happy_x_1
+ = case happyOut89 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_95 = happySpecReduce_1 0# happyReduction_95
+happyReduction_95 happy_x_1
+ = case happyOut90 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_96 = happySpecReduce_1 0# happyReduction_96
+happyReduction_96 happy_x_1
+ = case happyOut91 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_97 = happySpecReduce_1 0# happyReduction_97
+happyReduction_97 happy_x_1
+ = case happyOut92 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_98 = happySpecReduce_1 0# happyReduction_98
+happyReduction_98 happy_x_1
+ = case happyOut93 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_99 = happySpecReduce_1 0# happyReduction_99
+happyReduction_99 happy_x_1
+ = case happyOut94 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_100 = happySpecReduce_1 0# happyReduction_100
+happyReduction_100 happy_x_1
+ = case happyOut95 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_101 = happySpecReduce_1 0# happyReduction_101
+happyReduction_101 happy_x_1
+ = case happyOut96 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_102 = happySpecReduce_1 0# happyReduction_102
+happyReduction_102 happy_x_1
+ = case happyOut97 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_103 = happySpecReduce_1 0# happyReduction_103
+happyReduction_103 happy_x_1
+ = case happyOut98 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_104 = happySpecReduce_1 0# happyReduction_104
+happyReduction_104 happy_x_1
+ = case happyOut99 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_105 = happySpecReduce_1 0# happyReduction_105
+happyReduction_105 happy_x_1
+ = case happyOut100 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_106 = happySpecReduce_1 0# happyReduction_106
+happyReduction_106 happy_x_1
+ = case happyOut101 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_107 = happySpecReduce_1 0# happyReduction_107
+happyReduction_107 happy_x_1
+ = case happyOut102 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_108 = happySpecReduce_1 0# happyReduction_108
+happyReduction_108 happy_x_1
+ = case happyOut103 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_109 = happySpecReduce_1 0# happyReduction_109
+happyReduction_109 happy_x_1
+ = case happyOut104 happy_x_1 of { happy_var_1 ->
+ happyIn4
+ (happy_var_1
+ )}
+
+happyReduce_110 = happySpecReduce_3 1# happyReduction_110
+happyReduction_110 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn5
+ (Dummy happy_var_2
+ )}
+
+happyReduce_111 = happyReduce 4# 2# happyReduction_111
+happyReduction_111 (happy_x_4 `HappyStk`
+ happy_x_3 `HappyStk`
+ happy_x_2 `HappyStk`
+ happy_x_1 `HappyStk`
+ happyRest)
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn6
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_112 = happyReduce 5# 3# happyReduction_112
+happyReduction_112 (happy_x_5 `HappyStk`
+ happy_x_4 `HappyStk`
+ happy_x_3 `HappyStk`
+ happy_x_2 `HappyStk`
+ happy_x_1 `HappyStk`
+ happyRest)
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn7
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_113 = happyReduce 6# 4# happyReduction_113
+happyReduction_113 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn8
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_114 = happyReduce 7# 5# happyReduction_114
+happyReduction_114 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn9
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_115 = happyReduce 8# 6# happyReduction_115
+happyReduction_115 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn10
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_116 = happyReduce 9# 7# happyReduction_116
+happyReduction_116 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn11
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_117 = happyReduce 10# 8# happyReduction_117
+happyReduction_117 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn12
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_118 = happyReduce 11# 9# happyReduction_118
+happyReduction_118 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn13
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_119 = happyReduce 12# 10# happyReduction_119
+happyReduction_119 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn14
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_120 = happyReduce 13# 11# happyReduction_120
+happyReduction_120 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn15
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_121 = happyReduce 14# 12# happyReduction_121
+happyReduction_121 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn16
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_122 = happyReduce 15# 13# happyReduction_122
+happyReduction_122 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn17
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_123 = happyReduce 16# 14# happyReduction_123
+happyReduction_123 (happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn18
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_124 = happyReduce 17# 15# happyReduction_124
+happyReduction_124 (happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn19
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_125 = happyReduce 18# 16# happyReduction_125
+happyReduction_125 (happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn20
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_126 = happyReduce 19# 17# happyReduction_126
+happyReduction_126 (happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn21
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_127 = happyReduce 20# 18# happyReduction_127
+happyReduction_127 (happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn22
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_128 = happyReduce 21# 19# happyReduction_128
+happyReduction_128 (happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn23
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_129 = happyReduce 22# 20# happyReduction_129
+happyReduction_129 (happy_x_22 `HappyStk`
+ happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn24
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_130 = happyReduce 4# 21# happyReduction_130
+happyReduction_130 (happy_x_4 `HappyStk`
+ happy_x_3 `HappyStk`
+ happy_x_2 `HappyStk`
+ happy_x_1 `HappyStk`
+ happyRest)
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn25
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_131 = happyReduce 5# 22# happyReduction_131
+happyReduction_131 (happy_x_5 `HappyStk`
+ happy_x_4 `HappyStk`
+ happy_x_3 `HappyStk`
+ happy_x_2 `HappyStk`
+ happy_x_1 `HappyStk`
+ happyRest)
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn26
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_132 = happyReduce 6# 23# happyReduction_132
+happyReduction_132 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn27
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_133 = happyReduce 7# 24# happyReduction_133
+happyReduction_133 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn28
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_134 = happyReduce 8# 25# happyReduction_134
+happyReduction_134 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn29
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_135 = happyReduce 9# 26# happyReduction_135
+happyReduction_135 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn30
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_136 = happyReduce 10# 27# happyReduction_136
+happyReduction_136 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn31
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_137 = happyReduce 11# 28# happyReduction_137
+happyReduction_137 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn32
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_138 = happyReduce 12# 29# happyReduction_138
+happyReduction_138 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn33
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_139 = happyReduce 13# 30# happyReduction_139
+happyReduction_139 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn34
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_140 = happyReduce 14# 31# happyReduction_140
+happyReduction_140 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn35
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_141 = happyReduce 15# 32# happyReduction_141
+happyReduction_141 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn36
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_142 = happyReduce 16# 33# happyReduction_142
+happyReduction_142 (happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn37
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_143 = happyReduce 17# 34# happyReduction_143
+happyReduction_143 (happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn38
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_144 = happyReduce 18# 35# happyReduction_144
+happyReduction_144 (happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn39
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_145 = happyReduce 19# 36# happyReduction_145
+happyReduction_145 (happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn40
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_146 = happyReduce 20# 37# happyReduction_146
+happyReduction_146 (happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn41
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_147 = happyReduce 21# 38# happyReduction_147
+happyReduction_147 (happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn42
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_148 = happyReduce 22# 39# happyReduction_148
+happyReduction_148 (happy_x_22 `HappyStk`
+ happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn43
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_149 = happyReduce 23# 40# happyReduction_149
+happyReduction_149 (happy_x_23 `HappyStk`
+ happy_x_22 `HappyStk`
+ happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn44
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_150 = happySpecReduce_3 41# happyReduction_150
+happyReduction_150 happy_x_3
+ happy_x_2
+ happy_x_1
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn45
+ (Dummy happy_var_2
+ )}
+
+happyReduce_151 = happyReduce 4# 42# happyReduction_151
+happyReduction_151 (happy_x_4 `HappyStk`
+ happy_x_3 `HappyStk`
+ happy_x_2 `HappyStk`
+ happy_x_1 `HappyStk`
+ happyRest)
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn46
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_152 = happyReduce 5# 43# happyReduction_152
+happyReduction_152 (happy_x_5 `HappyStk`
+ happy_x_4 `HappyStk`
+ happy_x_3 `HappyStk`
+ happy_x_2 `HappyStk`
+ happy_x_1 `HappyStk`
+ happyRest)
+ = case happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn47
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_153 = happyReduce 6# 44# happyReduction_153
+happyReduction_153 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn48
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_154 = happyReduce 7# 45# happyReduction_154
+happyReduction_154 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn49
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_155 = happyReduce 8# 46# happyReduction_155
+happyReduction_155 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn50
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_156 = happyReduce 9# 47# happyReduction_156
+happyReduction_156 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn51
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_157 = happyReduce 10# 48# happyReduction_157
+happyReduction_157 (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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn52
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_158 = happyReduce 11# 49# happyReduction_158
+happyReduction_158 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn53
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_159 = happyReduce 12# 50# happyReduction_159
+happyReduction_159 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn54
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_160 = happyReduce 13# 51# happyReduction_160
+happyReduction_160 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn55
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_161 = happyReduce 14# 52# happyReduction_161
+happyReduction_161 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn56
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_162 = happyReduce 15# 53# happyReduction_162
+happyReduction_162 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn57
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_163 = happyReduce 16# 54# happyReduction_163
+happyReduction_163 (happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn58
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_164 = happyReduce 17# 55# happyReduction_164
+happyReduction_164 (happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn59
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_165 = happyReduce 18# 56# happyReduction_165
+happyReduction_165 (happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn60
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_166 = happyReduce 19# 57# happyReduction_166
+happyReduction_166 (happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn61
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_167 = happyReduce 20# 58# happyReduction_167
+happyReduction_167 (happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn62
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_168 = happyReduce 21# 59# happyReduction_168
+happyReduction_168 (happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn63
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_169 = happyReduce 22# 60# happyReduction_169
+happyReduction_169 (happy_x_22 `HappyStk`
+ happy_x_21 `HappyStk`
+ happy_x_20 `HappyStk`
+ happy_x_19 `HappyStk`
+ happy_x_18 `HappyStk`
+ happy_x_17 `HappyStk`
+ happy_x_16 `HappyStk`
+ happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_2 of { happy_var_2 ->
+ happyIn64
+ (Dummy happy_var_2
+ ) `HappyStk` happyRest}
+
+happyReduce_170 = happyReduce 6# 61# happyReduction_170
+happyReduction_170 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn65
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_171 = happyReduce 7# 62# happyReduction_171
+happyReduction_171 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn66
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_172 = happyReduce 8# 63# happyReduction_172
+happyReduction_172 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn67
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_173 = happyReduce 9# 64# happyReduction_173
+happyReduction_173 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn68
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_174 = happyReduce 10# 65# happyReduction_174
+happyReduction_174 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn69
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_175 = happyReduce 11# 66# happyReduction_175
+happyReduction_175 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn70
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_176 = happyReduce 12# 67# happyReduction_176
+happyReduction_176 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn71
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_177 = happyReduce 13# 68# happyReduction_177
+happyReduction_177 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn72
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_178 = happyReduce 14# 69# happyReduction_178
+happyReduction_178 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn73
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_179 = happyReduce 15# 70# happyReduction_179
+happyReduction_179 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn74
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_180 = happyReduce 6# 71# happyReduction_180
+happyReduction_180 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn75
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_181 = happyReduce 7# 72# happyReduction_181
+happyReduction_181 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn76
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_182 = happyReduce 8# 73# happyReduction_182
+happyReduction_182 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn77
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_183 = happyReduce 9# 74# happyReduction_183
+happyReduction_183 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn78
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_184 = happyReduce 10# 75# happyReduction_184
+happyReduction_184 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn79
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_185 = happyReduce 11# 76# happyReduction_185
+happyReduction_185 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn80
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_186 = happyReduce 12# 77# happyReduction_186
+happyReduction_186 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn81
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_187 = happyReduce 13# 78# happyReduction_187
+happyReduction_187 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn82
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_188 = happyReduce 14# 79# happyReduction_188
+happyReduction_188 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn83
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_189 = happyReduce 15# 80# happyReduction_189
+happyReduction_189 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn84
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_190 = happyReduce 6# 81# happyReduction_190
+happyReduction_190 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn85
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_191 = happyReduce 7# 82# happyReduction_191
+happyReduction_191 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn86
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_192 = happyReduce 8# 83# happyReduction_192
+happyReduction_192 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn87
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_193 = happyReduce 9# 84# happyReduction_193
+happyReduction_193 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn88
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_194 = happyReduce 10# 85# happyReduction_194
+happyReduction_194 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn89
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_195 = happyReduce 11# 86# happyReduction_195
+happyReduction_195 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn90
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_196 = happyReduce 12# 87# happyReduction_196
+happyReduction_196 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn91
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_197 = happyReduce 13# 88# happyReduction_197
+happyReduction_197 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn92
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_198 = happyReduce 14# 89# happyReduction_198
+happyReduction_198 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn93
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_199 = happyReduce 15# 90# happyReduction_199
+happyReduction_199 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn94
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_200 = happyReduce 6# 91# happyReduction_200
+happyReduction_200 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn95
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_201 = happyReduce 7# 92# happyReduction_201
+happyReduction_201 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn96
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_202 = happyReduce 8# 93# happyReduction_202
+happyReduction_202 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn97
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_203 = happyReduce 9# 94# happyReduction_203
+happyReduction_203 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn98
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_204 = happyReduce 10# 95# happyReduction_204
+happyReduction_204 (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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn99
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_205 = happyReduce 11# 96# happyReduction_205
+happyReduction_205 (happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn100
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_206 = happyReduce 12# 97# happyReduction_206
+happyReduction_206 (happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn101
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_207 = happyReduce 13# 98# happyReduction_207
+happyReduction_207 (happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn102
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_208 = happyReduce 14# 99# happyReduction_208
+happyReduction_208 (happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn103
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyReduce_209 = happyReduce 15# 100# happyReduction_209
+happyReduction_209 (happy_x_15 `HappyStk`
+ happy_x_14 `HappyStk`
+ happy_x_13 `HappyStk`
+ happy_x_12 `HappyStk`
+ happy_x_11 `HappyStk`
+ 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 happyOut4 happy_x_4 of { happy_var_4 ->
+ happyIn104
+ (Dummy happy_var_4
+ ) `HappyStk` happyRest}
+
+happyNewToken action sts stk [] =
+ happyDoAction 16# notHappyAtAll action sts stk []
+
+happyNewToken action sts stk (tk:tks) =
+ let cont i = happyDoAction i tk action sts stk tks in
+ case tk of {
+ TokenLet -> cont 1#;
+ TokenIn -> cont 2#;
+ TokenInt happy_dollar_dollar -> cont 3#;
+ TokenSym happy_dollar_dollar -> cont 4#;
+ TokenEq -> cont 5#;
+ TokenPlus -> cont 6#;
+ TokenMinus -> cont 7#;
+ TokenTimes -> cont 8#;
+ TokenDiv -> cont 9#;
+ TokenLParen -> cont 10#;
+ TokenRParen -> cont 11#;
+ TokenLCurl -> cont 12#;
+ TokenRCurl -> cont 13#;
+ TokenLRect -> cont 14#;
+ TokenRRect -> cont 15#;
+ _ -> happyError' ((tk:tks), [])
+ }
+
+happyError_ explist 16# tk tks = happyError' (tks, explist)
+happyError_ explist _ tk tks = happyError' ((tk:tks), explist)
+
+newtype HappyIdentity a = HappyIdentity a
+happyIdentity = HappyIdentity
+happyRunIdentity (HappyIdentity a) = a
+
+instance Functor HappyIdentity where
+ fmap f (HappyIdentity a) = HappyIdentity (f a)
+
+instance Applicative HappyIdentity where
+ pure = HappyIdentity
+ (<*>) = ap
+instance Monad HappyIdentity where
+ return = pure
+ (HappyIdentity p) >>= q = q p
+
+happyThen :: () => HappyIdentity a -> (a -> HappyIdentity b) -> HappyIdentity b
+happyThen = (>>=)
+happyReturn :: () => a -> HappyIdentity a
+happyReturn = (return)
+happyThen1 m k tks = (>>=) m (\a -> k a tks)
+happyReturn1 :: () => a -> b -> HappyIdentity a
+happyReturn1 = \a tks -> (return) a
+happyError' :: () => ([(Token)], [String]) -> HappyIdentity a
+happyError' = HappyIdentity . (\(tokens, _) -> parseError tokens)
+parseCalc tks = happyRunIdentity happySomeParser where
+ happySomeParser = happyThen (happyParse 0# tks) (\x -> happyReturn (happyOut4 x))
+
+happySeq = happyDontSeq
+
+
+parseError :: [Token] -> a
+parseError _ = error "Parse error"
+
+data Exp = Let String Exp Exp
+ | Plus Exp Exp
+ | Minus Exp Exp
+ | Times Exp Exp
+ | Div Exp Exp
+ | Negate Exp
+ | Brack Exp
+ | Int Int
+ | Var String
+ | Dummy Exp
+ deriving Show
+
+data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList
+
+infixr 9 `HappyStk`
+data HappyStk a = HappyStk a (HappyStk a)
+
+-----------------------------------------------------------------------------
+-- starting the parse
+
+happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll
+
+-----------------------------------------------------------------------------
+-- Accepting the parse
+
+-- If the current token is 0#, it means we've just accepted a partial
+-- parse (a %partial parser). We must ignore the saved token on the top of
+-- the stack in this case.
+happyAccept 0# tk st sts (_ `HappyStk` ans `HappyStk` _) =
+ happyReturn1 ans
+happyAccept j tk st sts (HappyStk ans _) =
+ (happyTcHack j (happyTcHack st)) (happyReturn1 ans)
+
+-----------------------------------------------------------------------------
+-- Arrays only: do the next action
+
+
+happyDoAction i tk st
+ = {- nothing -}
+ case action of
+ 0# -> {- nothing -}
+ happyFail (happyExpListPerState ((Happy_GHC_Exts.I# (st)) :: Int)) i tk st
+ -1# -> {- nothing -}
+ happyAccept i tk st
+ n | ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# (0# :: Happy_GHC_Exts.Int#))) :: Bool) -> {- 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 ((Happy_GHC_Exts.tagToEnum# (off_i Happy_GHC_Exts.>=# (0# :: Happy_GHC_Exts.Int#))) :: Bool)
+ then ((Happy_GHC_Exts.tagToEnum# (indexShortOffAddr happyCheck off_i Happy_GHC_Exts.==# i)) :: Bool)
+ 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 = ((Happy_GHC_Exts.tagToEnum# (x Happy_GHC_Exts.<# y)) :: Bool)
+
+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#
+
+-----------------------------------------------------------------------------
+-- 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.
diff --git a/testsuite/tests/hiefile/should_compile/hie003.hs b/testsuite/tests/hiefile/should_compile/hie003.hs
new file mode 100644
index 0000000000..17bca355d7
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie003.hs
@@ -0,0 +1,38 @@
+module Classes where
+
+
+class Foo a where
+ bar :: a -> Int
+ baz :: Int -> (a, a)
+
+instance Foo Int where
+ bar = id
+ baz x = (x, x)
+
+instance Foo [a] where
+ bar = length
+ baz _ = ([], [])
+
+
+class Foo a => Foo' a where
+ quux :: (a, a) -> a
+ quux (x, y) = norf [x, y]
+
+ norf :: [a] -> a
+ norf = quux . baz . sum . map bar
+
+instance Foo' Int where
+ norf = sum
+
+instance Foo' [a] where
+ quux = uncurry (++)
+
+
+class Plugh p where
+ plugh :: p a a -> p b b -> p (a -> b) (b -> a)
+
+instance Plugh Either where
+ plugh (Left a) (Left {}) = Right $ const a
+ plugh (Right a) (Right {}) = Right $ const a
+ plugh _ (Left b) = Left $ const b
+ plugh _ (Right b) = Left $ const b
diff --git a/testsuite/tests/hiefile/should_compile/hie003.stderr b/testsuite/tests/hiefile/should_compile/hie003.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie003.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie004.hs b/testsuite/tests/hiefile/should_compile/hie004.hs
new file mode 100644
index 0000000000..173c3ba7b3
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie004.hs
@@ -0,0 +1,28 @@
+module Identifiers where
+
+
+foo, bar, baz :: Int -> Int -> Int
+foo x y = x + x * bar y x * y + y
+bar x y = y + x - baz x y - x + y
+baz x y = x * y * y * y * x
+
+quux :: Int -> Int
+quux x = foo (bar x x) (bar x x)
+
+norf :: Int -> Int -> Int -> Int
+norf x y z
+ | x < 0 = quux x
+ | y < 0 = quux y
+ | z < 0 = quux z
+ | otherwise = norf (-x) (-y) (-z)
+
+
+main :: IO ()
+main = do
+ putStrLn . show $ foo x y
+ putStrLn . show $ quux z
+ putStrLn . show $ Identifiers.norf x y z
+ where
+ x = 10
+ y = 20
+ z = 30
diff --git a/testsuite/tests/hiefile/should_compile/hie004.stderr b/testsuite/tests/hiefile/should_compile/hie004.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie004.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie005.hs b/testsuite/tests/hiefile/should_compile/hie005.hs
new file mode 100644
index 0000000000..997b661561
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie005.hs
@@ -0,0 +1,17 @@
+module Literals where
+
+
+str :: String
+str = "str literal"
+
+num :: Num a => a
+num = 0 + 1 + 1010011 * 41231 + 12131
+
+frac :: Fractional a => a
+frac = 42.0000001
+
+list :: [[[[a]]]]
+list = [[], [[]], [[[]]]]
+
+pair :: ((), ((), (), ()), ())
+pair = ((), ((), (), ()), ())
diff --git a/testsuite/tests/hiefile/should_compile/hie005.stderr b/testsuite/tests/hiefile/should_compile/hie005.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie005.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie006.hs b/testsuite/tests/hiefile/should_compile/hie006.hs
new file mode 100644
index 0000000000..8e86ab0b71
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie006.hs
@@ -0,0 +1,22 @@
+module Operators where
+
+
+(+++) :: [a] -> [a] -> [a]
+a +++ b = a ++ b ++ a
+
+($$$) :: [a] -> [a] -> [a]
+a $$$ b = b +++ a
+
+(***) :: [a] -> [a] -> [a]
+(***) a [] = a
+(***) a (_:b) = a +++ (a *** b)
+
+(*/\*) :: [[a]] -> [a] -> [a]
+a */\* b = concatMap (*** b) a
+
+(**/\**) :: [[a]] -> [[a]] -> [[a]]
+a **/\** b = zipWith (*/\*) [a +++ b] (a $$$ b)
+
+
+(#.#) :: a -> b -> (c -> (a, b))
+a #.# b = const $ (a, b)
diff --git a/testsuite/tests/hiefile/should_compile/hie006.stderr b/testsuite/tests/hiefile/should_compile/hie006.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie006.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie007.hs b/testsuite/tests/hiefile/should_compile/hie007.hs
new file mode 100644
index 0000000000..3f0103bf2a
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie007.hs
@@ -0,0 +1,66 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+
+module Polymorphism where
+
+
+foo :: a -> a -> a
+foo = undefined
+
+foo' :: forall a. a -> a -> a
+foo' = undefined
+
+bar :: a -> b -> (a, b)
+bar = undefined
+
+bar' :: forall a b. a -> b -> (a, b)
+bar' = undefined
+
+baz :: a -> (a -> [a -> a] -> b) -> b
+baz = undefined
+
+baz' :: forall a b. a -> (a -> [a -> a] -> b) -> b
+baz' = undefined
+
+quux :: a -> (forall a. a -> a) -> a
+quux x f = f x
+
+quux' :: forall a. a -> (forall a. a -> a) -> a
+quux' x f = f x
+
+
+num :: Num a => a -> a -> a
+num = undefined
+
+num' :: forall a. Num a => a -> a -> a
+num' = undefined
+
+eq :: (Eq a, Eq b) => [a] -> [b] -> (a, b)
+eq = undefined
+
+eq' :: forall a b. (Eq a, Eq b) => [a] -> [b] -> (a, b)
+eq' = undefined
+
+mon :: Monad m => (a -> m a) -> m a
+mon = undefined
+
+mon' :: forall m a. Monad m => (a -> m a) -> m a
+mon' = undefined
+
+
+norf :: a -> (forall a. Ord a => a -> a) -> a
+norf x f = x
+
+norf' :: forall a. a -> (forall a. Ord a => a -> a) -> a
+norf' x f = x
+
+
+plugh :: forall a. a -> a
+plugh x = x :: a
+
+thud :: forall a b. (a -> b) -> a -> (a, b)
+thud f x =
+ (x :: a, y) :: (a, b)
+ where
+ y = (f :: a -> b) x :: b
diff --git a/testsuite/tests/hiefile/should_compile/hie007.stderr b/testsuite/tests/hiefile/should_compile/hie007.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie007.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie008.hs b/testsuite/tests/hiefile/should_compile/hie008.hs
new file mode 100644
index 0000000000..40a01121f2
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie008.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE RecordWildCards #-}
+
+
+module Records where
+
+
+data Point = Point
+ { x :: !Int
+ , y :: !Int
+ }
+
+
+point :: Int -> Int -> Point
+point x y = Point { x = x, y = y }
+
+
+lengthSqr :: Point -> Int
+lengthSqr (Point { x = x, y = y }) = x * x + y * y
+
+lengthSqr' :: Point -> Int
+lengthSqr' (Point { x, y }) = y * y + x * x
+
+
+translateX, translateY :: Point -> Int -> Point
+translateX p d = p { x = x p + d }
+translateY p d = p { y = y p + d }
+
+translate :: Int -> Int -> Point -> Point
+translate x y p =
+ aux p
+ where
+ (dx, dy) = (x, y)
+ aux Point{..} = p { x = x + dx, y = y + dy }
diff --git a/testsuite/tests/hiefile/should_compile/hie008.stderr b/testsuite/tests/hiefile/should_compile/hie008.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie008.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie009.hs b/testsuite/tests/hiefile/should_compile/hie009.hs
new file mode 100644
index 0000000000..b63a825b95
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie009.hs
@@ -0,0 +1,42 @@
+{-# LANGUAGE TypeFamilies #-}
+
+
+module Types where
+
+
+data Quux = Bar | Baz
+
+newtype Foo = Foo ()
+
+type FooQuux = (Foo, Quux)
+type QuuxFoo = (Quux, Foo)
+
+
+data family Norf a b
+
+data instance Norf Foo Quux = NFQ Foo Quux
+data instance Norf Quux Foo = NQF Quux Foo
+
+
+type family Norf' a b
+
+type instance Norf' Foo Quux = (Foo, Quux)
+type instance Norf' Quux Foo = (Quux, Foo)
+
+
+norf1 :: Norf Foo Quux -> Int
+norf1 (NFQ (Foo ()) Bar) = 0
+norf1 (NFQ (Foo ()) Baz) = 1
+
+norf2 :: Norf Quux Foo -> Int
+norf2 (NQF Bar (Foo ())) = 0
+norf2 (NQF Baz (Foo ())) = 1
+
+
+norf1' :: Norf' Foo Quux -> Int
+norf1' (Foo (), Bar) = 0
+norf1' (Foo (), Baz) = 1
+
+norf2' :: Norf' Quux Foo -> Int
+norf2' (Bar, Foo ()) = 0
+norf2' (Baz, Foo ()) = 1
diff --git a/testsuite/tests/hiefile/should_compile/hie009.stderr b/testsuite/tests/hiefile/should_compile/hie009.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie009.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/hiefile/should_compile/hie010.hs b/testsuite/tests/hiefile/should_compile/hie010.hs
new file mode 100644
index 0000000000..e231878464
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie010.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE ExplicitForAll #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE DataKinds #-}
+module MoreExplicitForalls where
+
+import Data.Proxy
+
+data family F1 a
+data instance forall (x :: Bool). F1 (Proxy x) = MkF
+
+class C a where
+ type F2 a b
+
+instance forall a. C [a] where
+ type forall b. F2 [a] b = Int
+
+
+type family G a b where
+ forall x y. G [x] (Proxy y) = Double
+ forall z. G z z = Bool
diff --git a/testsuite/tests/hiefile/should_compile/hie010.stderr b/testsuite/tests/hiefile/should_compile/hie010.stderr
new file mode 100644
index 0000000000..f31d37d99f
--- /dev/null
+++ b/testsuite/tests/hiefile/should_compile/hie010.stderr
@@ -0,0 +1,2 @@
+Got valid scopes
+Got no roundtrip errors
diff --git a/testsuite/tests/regalloc/regalloc_unit_tests.hs b/testsuite/tests/regalloc/regalloc_unit_tests.hs
index 66aa51a050..18e0f3b5f4 100644
--- a/testsuite/tests/regalloc/regalloc_unit_tests.hs
+++ b/testsuite/tests/regalloc/regalloc_unit_tests.hs
@@ -143,7 +143,7 @@ compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do
thisMod = mkModule
(stringToUnitId . show . uniqFromSupply $ usc)
(mkModuleName . show . uniqFromSupply $ usd)
- thisModLoc = ModLocation Nothing (cmmFile ++ ".hi") (cmmFile ++ ".o")
+ thisModLoc = ModLocation Nothing (cmmFile ++ ".hi") (cmmFile ++ ".o") (cmmFile ++ ".hie")
-- | The register allocator should be able to see that each variable only
diff --git a/utils/ghc-in-ghci/settings.ghci b/utils/ghc-in-ghci/settings.ghci
index dd914d1491..85296314ce 100644
--- a/utils/ghc-in-ghci/settings.ghci
+++ b/utils/ghc-in-ghci/settings.ghci
@@ -5,6 +5,7 @@
:set -icompiler/coreSyn
:set -icompiler/deSugar
:set -icompiler/ghci
+:set -icompiler/hiefile
:set -icompiler/hsSyn
:set -icompiler/iface
:set -icompiler/llvmGen