{-# LANGUAGE CPP #-}
module GHC.SourceGen.Binds.Internal where
import BasicTypes (Origin(Generated))
import Bag (listToBag)
import HsBinds
import HsExpr (MatchGroup(..), Match(..), GRHSs(..))
import SrcLoc (Located)
#if !MIN_VERSION_ghc(8,6,0)
import PlaceHolder (PlaceHolder(..))
#endif
import GHC.SourceGen.Syntax
import GHC.SourceGen.Syntax.Internal
data RawValBind
= SigV Sig'
| BindV HsBind'
valBinds :: [RawValBind] -> HsLocalBinds'
valBinds [] = noExt EmptyLocalBinds
valBinds vbs =
noExt HsValBinds
#if MIN_VERSION_ghc(8,6,0)
$ noExt ValBinds
#else
$ noExt ValBindsIn
#endif
(listToBag $ map builtLoc binds)
(map builtLoc sigs)
where
sigs = [s | SigV s <- vbs]
binds = [b | BindV b <- vbs]
data RawMatch = RawMatch
{ rawMatchPats :: [Pat']
, rawMatchGRHSs :: RawGRHSs
}
data RawGRHSs = RawGRHSs
{ rawGRHSs :: [GuardedExpr]
, rawGRHSWhere :: [RawValBind]
}
matchGroup :: HsMatchContext' -> [RawMatch] -> MatchGroup' (Located HsExpr')
matchGroup context matches =
noExt MG (builtLoc $ map (builtLoc . mkMatch) matches)
#if !MIN_VERSION_ghc(8,6,0)
[] PlaceHolder
#endif
Generated
where
mkMatch :: RawMatch -> Match' (Located HsExpr')
mkMatch r = noExt Match context (map builtPat $ rawMatchPats r)
#if !MIN_VERSION_ghc(8,4,0)
Nothing
#endif
(mkGRHSs $ rawMatchGRHSs r)
mkGRHSs :: RawGRHSs -> GRHSs' (Located HsExpr')
mkGRHSs g = noExt GRHSs
(map builtLoc $ rawGRHSs g)
(builtLoc $ valBinds $ rawGRHSWhere g)
type GuardedExpr = GRHS' (Located HsExpr')