{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module GHC.SourceGen.Syntax.Internal where
import SrcLoc (SrcSpan, Located, GenLocated(..), mkGeneralSrcSpan)
#if MIN_VERSION_ghc(8,8,0)
import BasicTypes (PromotionFlag(..))
#else
import HsTypes (Promoted(..))
#endif
#if MIN_VERSION_ghc(8,6,0)
import HsExtension (NoExt(NoExt))
#else
import PlaceHolder(PlaceHolder(..))
#endif
import GHC.SourceGen.Syntax
#if MIN_VERSION_ghc(8,6,0)
noExt :: (NoExt -> a) -> a
noExt = ($ NoExt)
noExtOrPlaceHolder :: (NoExt -> a) -> a
noExtOrPlaceHolder = noExt
withPlaceHolder :: a -> a
withPlaceHolder = id
#else
noExt :: a -> a
noExt = id
noExtOrPlaceHolder :: (PlaceHolder -> a) -> a
noExtOrPlaceHolder = withPlaceHolder
withPlaceHolder :: (PlaceHolder -> a) -> a
withPlaceHolder = ($ PlaceHolder)
#endif
builtSpan :: SrcSpan
builtSpan = mkGeneralSrcSpan "<ghc-source-gen>"
builtLoc :: e -> Located e
builtLoc = L builtSpan
#if MIN_VERSION_ghc(8,8,0)
builtPat :: Pat' -> Pat'
builtPat = id
#else
builtPat :: Pat' -> Located Pat'
builtPat = builtLoc
#endif
#if MIN_VERSION_ghc(8,8,0)
promoted, notPromoted :: PromotionFlag
promoted = IsPromoted
notPromoted = NotPromoted
#else
promoted, notPromoted :: Promoted
promoted = Promoted
notPromoted = NotPromoted
#endif