{-# LANGUAGE CPP #-}

-- | Plugin Compat utils.
module Development.IDE.GHC.Compat.Plugins (
    -- * Plugin Compat Types, and initialisation
    Plugin(..),
    defaultPlugin,
    PluginWithArgs(..),
    applyPluginsParsedResultAction,
    initializePlugins,
    initPlugins,

    -- * Static plugins
    StaticPlugin(..),
    hsc_static_plugins,

    -- * Plugin messages
    PsMessages(..),
    getPsMessages
    ) where

#if MIN_VERSION_ghc(9,0,0)
#if MIN_VERSION_ghc(9,2,0)
import qualified GHC.Driver.Env                        as Env
#endif
import           GHC.Driver.Plugins                    (Plugin (..),
                                                        PluginWithArgs (..),
                                                        StaticPlugin (..),
                                                        defaultPlugin,
                                                        withPlugins)
#if MIN_VERSION_ghc(9,3,0)
import           GHC.Driver.Plugins                    (ParsedResult (..),
                                                        PsMessages (..),
                                                        staticPlugins)
import qualified GHC.Parser.Lexer                      as Lexer
#else
import           Data.Bifunctor                        (bimap)
#endif
import qualified GHC.Runtime.Loader                    as Loader
#else
import qualified DynamicLoading                        as Loader
import           Plugins
#endif
import           Development.IDE.GHC.Compat.Core
import           Development.IDE.GHC.Compat.Env        (hscSetFlags, hsc_dflags)
import           Development.IDE.GHC.Compat.Outputable as Out
import           Development.IDE.GHC.Compat.Parser     as Parser
import           Development.IDE.GHC.Compat.Util       (Bag)


#if !MIN_VERSION_ghc(9,3,0)
type PsMessages = (Bag WarnMsg, Bag ErrMsg)
#endif

getPsMessages :: PState -> DynFlags -> PsMessages
getPsMessages :: PState -> DynFlags -> PsMessages
getPsMessages PState
pst DynFlags
dflags =
#if MIN_VERSION_ghc(9,3,0)
  uncurry PsMessages $ Lexer.getPsMessages pst
#else
#if MIN_VERSION_ghc(9,2,0)
                 forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsWarning -> MsgEnvelope DecoratedSDoc
pprWarning) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsError -> MsgEnvelope DecoratedSDoc
pprError) forall a b. (a -> b) -> a -> b
$
#endif
                 PState -> (Bag PsWarning, Bag PsError)
getMessages PState
pst
#if !MIN_VERSION_ghc(9,2,0)
                   dflags
#endif
#endif

applyPluginsParsedResultAction :: HscEnv -> DynFlags -> ModSummary -> Parser.ApiAnns -> ParsedSource -> PsMessages -> IO (ParsedSource, PsMessages)
applyPluginsParsedResultAction :: HscEnv
-> DynFlags
-> ModSummary
-> ApiAnns
-> ParsedSource
-> PsMessages
-> IO (ParsedSource, PsMessages)
applyPluginsParsedResultAction HscEnv
env DynFlags
dflags ModSummary
ms ApiAnns
hpm_annotations ParsedSource
parsed PsMessages
msgs = do
  -- Apply parsedResultAction of plugins
  let applyPluginAction :: Plugin
-> [CommandLineOption] -> HsParsedModule -> Hsc HsParsedModule
applyPluginAction Plugin
p [CommandLineOption]
opts = Plugin
-> [CommandLineOption]
-> ModSummary
-> HsParsedModule
-> Hsc HsParsedModule
parsedResultAction Plugin
p [CommandLineOption]
opts ModSummary
ms
#if MIN_VERSION_ghc(9,3,0)
  fmap (\result -> (hpm_module (parsedResultModule result), (parsedResultMessages result))) $ runHsc env $ withPlugins
#else
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\HsParsedModule
parsed_module -> (HsParsedModule -> ParsedSource
hpm_module HsParsedModule
parsed_module, PsMessages
msgs)) forall a b. (a -> b) -> a -> b
$ forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
env forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
HscEnv -> PluginOperation m a -> a -> m a
withPlugins
#endif
#if MIN_VERSION_ghc(9,3,0)
      (Env.hsc_plugins env)
#elif MIN_VERSION_ghc(9,2,0)
      HscEnv
env
#else
      dflags
#endif
      Plugin
-> [CommandLineOption] -> HsParsedModule -> Hsc HsParsedModule
applyPluginAction
#if MIN_VERSION_ghc(9,3,0)
      (ParsedResult (HsParsedModule parsed [] hpm_annotations) msgs)
#else
      (ParsedSource -> [CommandLineOption] -> ApiAnns -> HsParsedModule
HsParsedModule ParsedSource
parsed [] ApiAnns
hpm_annotations)
#endif

initializePlugins :: HscEnv -> IO HscEnv
initializePlugins :: HscEnv -> IO HscEnv
initializePlugins HscEnv
env = do
#if MIN_VERSION_ghc(9,2,0)
    HscEnv -> IO HscEnv
Loader.initializePlugins HscEnv
env
#else
    newDf <- Loader.initializePlugins env (hsc_dflags env)
    pure $ hscSetFlags newDf env
#endif

-- | Plugins aren't stored in ModSummary anymore since GHC 9.2, but this
-- function still returns it for compatibility with 8.10
initPlugins :: HscEnv -> ModSummary -> IO (ModSummary, HscEnv)
initPlugins :: HscEnv -> ModSummary -> IO (ModSummary, HscEnv)
initPlugins HscEnv
session ModSummary
modSummary = do
    HscEnv
session1 <- HscEnv -> IO HscEnv
initializePlugins (DynFlags -> HscEnv -> HscEnv
hscSetFlags (ModSummary -> DynFlags
ms_hspp_opts ModSummary
modSummary) HscEnv
session)
    forall (m :: * -> *) a. Monad m => a -> m a
return (ModSummary
modSummary{ms_hspp_opts :: DynFlags
ms_hspp_opts = HscEnv -> DynFlags
hsc_dflags HscEnv
session1}, HscEnv
session1)

hsc_static_plugins :: HscEnv -> [StaticPlugin]
#if MIN_VERSION_ghc(9,3,0)
hsc_static_plugins = staticPlugins . Env.hsc_plugins
#elif MIN_VERSION_ghc(9,2,0)
hsc_static_plugins :: HscEnv -> [StaticPlugin]
hsc_static_plugins = HscEnv -> [StaticPlugin]
Env.hsc_static_plugins
#else
hsc_static_plugins = staticPlugins . hsc_dflags
#endif