{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module GHC.SourceGen.Syntax.Internal where
import GHC.Hs
( HsDecl
, HsExpr(..)
, HsLit
, HsModule
, HsType(..)
, HsBind
, HsTyVarBndr
, HsOverLit
, HsValBinds
, HsMatchContext
, IE
, LHsExpr
, LHsQTyVars
, Match
, MatchGroup
, GRHS
, GRHSs
, Stmt
, ConDecl
, LHsSigType
, ImportDecl
, LHsSigWcType
, LHsWcType
, TyFamInstDecl
#if !MIN_VERSION_ghc(8,8,0)
, LHsRecField
, LHsRecUpdField
#endif
#if MIN_VERSION_ghc(9,0,0)
, HsPatSigType
#endif
#if MIN_VERSION_ghc(9,2,0)
, HsConDeclH98Details
#else
, HsConDeclDetails
#endif
)
import GHC.Hs.Binds (Sig, HsLocalBinds)
#if MIN_VERSION_ghc(8,6,0)
import GHC.Hs.Decls (DerivStrategy)
#else
import BasicTypes (DerivStrategy)
#endif
import GHC.Hs.Decls (HsDerivingClause)
import GHC.Hs.Pat
#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.SrcLoc (SrcSpan, Located, GenLocated(..), mkGeneralSrcSpan)
#else
import RdrName (RdrName)
import SrcLoc (SrcSpan, Located, GenLocated(..), mkGeneralSrcSpan)
#endif
#if MIN_VERSION_ghc(9,2,0)
import GHC.Parser.Annotation
( SrcSpanAnn'(..)
, AnnSortKey(..)
, EpAnn(..)
, EpAnnComments
, emptyComments
)
#endif
#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.Basic (PromotionFlag(..))
#elif MIN_VERSION_ghc(8,8,0)
import BasicTypes (PromotionFlag(..))
#else
import GHC.Hs.Type (Promoted(..))
#endif
#if MIN_VERSION_ghc(8,10,0)
import qualified GHC.Hs as GHC
#elif MIN_VERSION_ghc(8,6,0)
import qualified GHC.Hs.Extension as GHC
#else
import qualified HsExtension as GHC
import qualified PlaceHolder as GHC
#endif
#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.Var (Specificity)
#endif
import GHC.Hs.Extension (GhcPs)
#if MIN_VERSION_ghc(8,10,0)
type NoExtField = GHC.NoExtField
#elif MIN_VERSION_ghc(8,6,0)
type NoExtField = GHC.NoExt
#endif
#if MIN_VERSION_ghc(8,10,0)
noExt :: (NoExtField -> a) -> a
noExt :: (NoExtField -> a) -> a
noExt = ((NoExtField -> a) -> NoExtField -> a
forall a b. (a -> b) -> a -> b
$ NoExtField
GHC.NoExtField)
#elif MIN_VERSION_ghc(8,6,0)
noExt :: (NoExtField -> a) -> a
noExt = ($ GHC.NoExt)
#else
noExt :: a -> a
noExt = id
#endif
#if MIN_VERSION_ghc(8,6,0)
noExtOrPlaceHolder :: (NoExtField -> a) -> a
noExtOrPlaceHolder :: (NoExtField -> a) -> a
noExtOrPlaceHolder = (NoExtField -> a) -> a
forall a. (NoExtField -> a) -> a
noExt
#else
noExtOrPlaceHolder :: (GHC.PlaceHolder -> a) -> a
noExtOrPlaceHolder = withPlaceHolder
#endif
#if MIN_VERSION_ghc(9,2,0)
withEpAnnNotUsed :: (EpAnn ann -> a) -> a
withEpAnnNotUsed = ($ EpAnnNotUsed)
#elif MIN_VERSION_ghc(8,6,0)
withEpAnnNotUsed :: (NoExtField -> a) -> a
withEpAnnNotUsed :: (NoExtField -> a) -> a
withEpAnnNotUsed = (NoExtField -> a) -> a
forall a. (NoExtField -> a) -> a
noExt
#else
withEpAnnNotUsed :: a -> a
withEpAnnNotUsed = id
#endif
#if MIN_VERSION_ghc(9,2,0)
withNoAnnSortKey :: (AnnSortKey -> a) -> a
withNoAnnSortKey = ($ NoAnnSortKey)
#elif MIN_VERSION_ghc(8,6,0)
withNoAnnSortKey :: (NoExtField -> a) -> a
withNoAnnSortKey :: (NoExtField -> a) -> a
withNoAnnSortKey = (NoExtField -> a) -> a
forall a. (NoExtField -> a) -> a
noExt
#else
withNoAnnSortKey :: a -> a
withNoAnnSortKey = id
#endif
#if MIN_VERSION_ghc(9,2,0)
withEmptyEpAnnComments :: (EpAnnComments -> a) -> a
withEmptyEpAnnComments = ($ emptyComments)
#elif MIN_VERSION_ghc(8,6,0)
withEmptyEpAnnComments :: (NoExtField -> a) -> a
= (NoExtField -> a) -> a
forall a. (NoExtField -> a) -> a
noExt
#else
withEmptyEpAnnComments :: a -> a
withEmptyEpAnnComments = id
#endif
#if MIN_VERSION_ghc(8,6,0)
withPlaceHolder :: a -> a
withPlaceHolder :: a -> a
withPlaceHolder = a -> a
forall a. a -> a
id
#else
withPlaceHolder :: (GHC.PlaceHolder -> a) -> a
withPlaceHolder = ($ GHC.PlaceHolder)
#endif
#if MIN_VERSION_ghc(8,6,0)
withPlaceHolders :: a -> a
withPlaceHolders :: a -> a
withPlaceHolders = a -> a
forall a. a -> a
id
#else
withPlaceHolders :: ([GHC.PlaceHolder] -> a) -> a
withPlaceHolders = ($ [])
#endif
builtSpan :: SrcSpan
builtSpan :: SrcSpan
builtSpan = FastString -> SrcSpan
mkGeneralSrcSpan FastString
"<ghc-source-gen>"
builtLoc :: e -> Located e
builtLoc :: e -> Located e
builtLoc = SrcSpan -> e -> Located e
forall l e. l -> e -> GenLocated l e
L SrcSpan
builtSpan
#if MIN_VERSION_ghc(9,2,0)
type SrcSpanAnn ann = GHC.SrcSpanAnn' (EpAnn ann)
#else
type SrcSpanAnn ann = SrcSpan
#endif
mkLocated :: a -> GenLocated (SrcSpanAnn ann) a
mkLocated :: a -> GenLocated SrcSpan a
mkLocated = SrcSpan -> a -> GenLocated SrcSpan a
forall l e. l -> e -> GenLocated l e
L (SrcSpan -> SrcSpan
forall a. a -> a
toAnn SrcSpan
builtSpan)
where
#if MIN_VERSION_ghc(9,2,0)
toAnn = SrcSpanAnn EpAnnNotUsed
#else
toAnn :: a -> a
toAnn = a -> a
forall a. a -> a
id
#endif
builtPat :: Pat' -> LPat'
#if MIN_VERSION_ghc(9,2,0)
builtPat = mkLocated
#elif MIN_VERSION_ghc(8,8,0) && !MIN_VERSION_ghc(8,10,0)
builtPat = id
#else
builtPat :: Pat' -> LPat'
builtPat = Pat' -> LPat'
forall e. e -> Located e
builtLoc
#endif
#if MIN_VERSION_ghc(8,8,0)
promoted, notPromoted :: PromotionFlag
promoted :: PromotionFlag
promoted = PromotionFlag
IsPromoted
notPromoted :: PromotionFlag
notPromoted = PromotionFlag
NotPromoted
#else
promoted, notPromoted :: Promoted
promoted = Promoted
notPromoted = NotPromoted
#endif
type HsType' = HsType GhcPs
type Pat' = Pat GhcPs
type HsExpr' = HsExpr GhcPs
type LHsExpr' = LHsExpr GhcPs
type HsDecl' = HsDecl GhcPs
type IE' = IE GhcPs
#if MIN_VERSION_ghc(9,0,0)
type HsTyVarBndr' = HsTyVarBndr () GhcPs
type HsTyVarBndrS' = HsTyVarBndr Specificity GhcPs
#else
type HsTyVarBndr' = HsTyVarBndr GhcPs
type HsTyVarBndrS' = HsTyVarBndr GhcPs
#endif
type HsLit' = HsLit GhcPs
#if MIN_VERSION_ghc(9,0,0)
type HsModule' = HsModule
#else
type HsModule' = HsModule GhcPs
#endif
type HsBind' = HsBind GhcPs
type HsLocalBinds' = HsLocalBinds GhcPs
type HsValBinds' = HsValBinds GhcPs
type Sig' = Sig GhcPs
#if MIN_VERSION_ghc(9,0,0)
type HsMatchContext' = HsMatchContext GhcPs
#else
type HsMatchContext' = HsMatchContext RdrName
#endif
type Match' = Match GhcPs
type MatchGroup' = MatchGroup GhcPs
type GRHS' = GRHS GhcPs
type GRHSs' = GRHSs GhcPs
type Stmt' = Stmt GhcPs LHsExpr'
type HsOverLit' = HsOverLit GhcPs
type LHsQTyVars' = LHsQTyVars GhcPs
type ConDecl' = ConDecl GhcPs
#if MIN_VERSION_ghc(9,2,0)
type HsConDeclDetails' = HsConDeclH98Details GhcPs
#else
type HsConDeclDetails' = HsConDeclDetails GhcPs
#endif
type LHsSigType' = LHsSigType GhcPs
type ImportDecl' = ImportDecl GhcPs
type LHsSigWcType' = LHsSigWcType GhcPs
type LHsWcType' = LHsWcType GhcPs
type HsDerivingClause' = HsDerivingClause GhcPs
type LHsRecField' arg = LHsRecField GhcPs arg
type LHsRecUpdField' = LHsRecUpdField GhcPs
type LPat' = LPat GhcPs
type TyFamInstDecl' = TyFamInstDecl GhcPs
#if MIN_VERSION_ghc(8,6,0)
type DerivStrategy' = DerivStrategy GhcPs
#else
type DerivStrategy' = DerivStrategy
#endif
#if MIN_VERSION_ghc(9,0,0)
type HsPatSigType' = HsPatSigType GhcPs
#else
type HsPatSigType' = LHsSigWcType'
#endif
#if MIN_VERSION_ghc(9,2,0)
type LIdP = GHC.LIdP GHC.GhcPs
#else
type LIdP = Located (GHC.IdP GHC.GhcPs)
#endif