{-# LANGUAGE FlexibleInstances, CPP #-}
module HIE.Bios.Ghc.Gap (
    WarnFlags
  , emptyWarnFlags
  , makeUserStyle
  , getModuleName
  , getTyThing
  , fixInfo
  , getModSummaries
  , mapOverIncludePaths
  , LExpression
  , LBinding
  , LPattern
  , inTypes
  , outType
  , mapMG
  , mgModSummaries
  , numLoadedPlugins
  , initializePlugins
  , unsetLogAction
  ) where
import DynFlags (DynFlags, includePaths)
import GHC(LHsBind, LHsExpr, LPat, Type, ModSummary, ModuleGraph, HscEnv, setLogAction, GhcMonad)
import Outputable (PrintUnqualified, PprStyle, Depth(AllTheWay), mkUserStyle)
#if __GLASGOW_HASKELL__ >= 808
import qualified DynamicLoading (initializePlugins)
import qualified Plugins (plugins)
#endif
#if __GLASGOW_HASKELL__ >= 804
import DynFlags (WarningFlag)
import qualified EnumSet as E (EnumSet, empty)
import GHC (mgModSummaries, mapMG)
#endif
#if __GLASGOW_HASKELL__ >= 806
import DynFlags (IncludeSpecs(..))
#endif
#if __GLASGOW_HASKELL__ >= 810
import GHC.Hs.Extension (GhcTc)
import GHC.Hs.Expr (MatchGroup, MatchGroupTc(..), mg_ext)
#elif __GLASGOW_HASKELL__ >= 806
import HsExtension (GhcTc)
import HsExpr (MatchGroup, MatchGroupTc(..))
import GHC (mg_ext)
#elif __GLASGOW_HASKELL__ >= 804
import HsExtension (GhcTc)
import HsExpr (MatchGroup)
import GHC (mg_res_ty, mg_arg_tys)
#else
import HsExtension (GhcTc)
import HsExpr (MatchGroup)
#endif
makeUserStyle :: DynFlags -> PrintUnqualified -> PprStyle
#if __GLASGOW_HASKELL__ >= 804
makeUserStyle :: DynFlags -> PrintUnqualified -> PprStyle
makeUserStyle dflags :: DynFlags
dflags style :: PrintUnqualified
style = DynFlags -> PrintUnqualified -> Depth -> PprStyle
mkUserStyle DynFlags
dflags PrintUnqualified
style Depth
AllTheWay
#endif
#if __GLASGOW_HASKELL__ >= 804
getModuleName :: (a, b) -> a
getModuleName :: (a, b) -> a
getModuleName = (a, b) -> a
forall a b. (a, b) -> a
fst
#endif
#if __GLASGOW_HASKELL__ >= 804
type WarnFlags = E.EnumSet WarningFlag
emptyWarnFlags :: WarnFlags
emptyWarnFlags :: WarnFlags
emptyWarnFlags = WarnFlags
forall a. EnumSet a
E.empty
#endif
#if __GLASGOW_HASKELL__ >= 804
getModSummaries :: ModuleGraph -> [ModSummary]
getModSummaries :: ModuleGraph -> [ModSummary]
getModSummaries = ModuleGraph -> [ModSummary]
mgModSummaries
getTyThing :: (a, b, c, d, e) -> a
getTyThing :: (a, b, c, d, e) -> a
getTyThing (t :: a
t,_,_,_,_) = a
t
fixInfo :: (a, b, c, d, e) -> (a, b, c, d)
fixInfo :: (a, b, c, d, e) -> (a, b, c, d)
fixInfo (t :: a
t,f :: b
f,cs :: c
cs,fs :: d
fs,_) = (a
t,b
f,c
cs,d
fs)
#endif
mapOverIncludePaths :: (FilePath -> FilePath) -> DynFlags -> DynFlags
mapOverIncludePaths :: (FilePath -> FilePath) -> DynFlags -> DynFlags
mapOverIncludePaths f :: FilePath -> FilePath
f df :: DynFlags
df = DynFlags
df
  { includePaths :: IncludeSpecs
includePaths = 
#if __GLASGOW_HASKELL__ > 804
      [FilePath] -> [FilePath] -> IncludeSpecs
IncludeSpecs
          ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
f ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ IncludeSpecs -> [FilePath]
includePathsQuote  (DynFlags -> IncludeSpecs
includePaths DynFlags
df))
          ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
f ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ IncludeSpecs -> [FilePath]
includePathsGlobal (DynFlags -> IncludeSpecs
includePaths DynFlags
df))
#else
      map f (includePaths df)
#endif
  }
#if __GLASGOW_HASKELL__ >= 806
type LExpression = LHsExpr GhcTc
type LBinding    = LHsBind GhcTc
type LPattern    = LPat    GhcTc
inTypes :: MatchGroup GhcTc LExpression -> [Type]
inTypes :: MatchGroup GhcTc LExpression -> [Type]
inTypes = MatchGroupTc -> [Type]
mg_arg_tys (MatchGroupTc -> [Type])
-> (MatchGroup GhcTc LExpression -> MatchGroupTc)
-> MatchGroup GhcTc LExpression
-> [Type]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MatchGroup GhcTc LExpression -> MatchGroupTc
forall p body. MatchGroup p body -> XMG p body
mg_ext
outType :: MatchGroup GhcTc LExpression -> Type
outType :: MatchGroup GhcTc LExpression -> Type
outType = MatchGroupTc -> Type
mg_res_ty (MatchGroupTc -> Type)
-> (MatchGroup GhcTc LExpression -> MatchGroupTc)
-> MatchGroup GhcTc LExpression
-> Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MatchGroup GhcTc LExpression -> MatchGroupTc
forall p body. MatchGroup p body -> XMG p body
mg_ext
#elif __GLASGOW_HASKELL__ >= 804
type LExpression = LHsExpr GhcTc
type LBinding    = LHsBind GhcTc
type LPattern    = LPat    GhcTc
inTypes :: MatchGroup GhcTc LExpression -> [Type]
inTypes = mg_arg_tys
outType :: MatchGroup GhcTc LExpression -> Type
outType = mg_res_ty
#endif
numLoadedPlugins :: DynFlags -> Int
#if __GLASGOW_HASKELL__ >= 808
numLoadedPlugins :: DynFlags -> Int
numLoadedPlugins = [PluginWithArgs] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([PluginWithArgs] -> Int)
-> (DynFlags -> [PluginWithArgs]) -> DynFlags -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynFlags -> [PluginWithArgs]
Plugins.plugins
#else
numLoadedPlugins _ = 0
#endif
initializePlugins :: HscEnv -> DynFlags -> IO DynFlags
#if __GLASGOW_HASKELL__ >= 808
initializePlugins :: HscEnv -> DynFlags -> IO DynFlags
initializePlugins = HscEnv -> DynFlags -> IO DynFlags
DynamicLoading.initializePlugins
#else
initializePlugins _ df = return df
#endif
unsetLogAction :: GhcMonad m => m ()
unsetLogAction :: m ()
unsetLogAction =
    LogAction -> m ()
forall (m :: * -> *). GhcMonad m => LogAction -> m ()
setLogAction (\_df :: DynFlags
_df _wr :: WarnReason
_wr _s :: Severity
_s _ss :: SrcSpan
_ss _pp :: PprStyle
_pp _m :: MsgDoc
_m -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
#if __GLASGOW_HASKELL__ < 806
        (\_df -> return ())
#endif