{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
module Plugins (
Plugin(..)
, defaultPlugin
, CommandLineOption
, purePlugin, impurePlugin, flagRecompile
, PluginRecompile(..)
, FrontendPlugin(..), defaultFrontendPlugin, FrontendPluginAction
, CorePlugin
, TcPlugin
, keepRenamedSource
, PluginWithArgs(..), plugins, pluginRecompile'
, LoadedPlugin(..), lpModuleName
, StaticPlugin(..)
, mapPlugins, withPlugins, withPlugins_
) where
import GhcPrelude
import {-# SOURCE #-} CoreMonad ( CoreToDo, CoreM )
import qualified TcRnTypes
import TcRnTypes ( TcGblEnv, IfM, TcM, tcg_rn_decls, tcg_rn_exports )
import HsSyn
import DynFlags
import HscTypes
import GhcMonad
import DriverPhases
import Module ( ModuleName, Module(moduleName))
import Fingerprint
import Data.List
import Outputable (Outputable(..), text, (<+>))
import qualified Data.Semigroup
import Control.Monad
type CommandLineOption = String
data Plugin = Plugin {
Plugin -> CorePlugin
installCoreToDos :: CorePlugin
, Plugin -> TcPlugin
tcPlugin :: TcPlugin
, Plugin -> [CommandLineOption] -> IO PluginRecompile
pluginRecompile :: [CommandLineOption] -> IO PluginRecompile
, Plugin
-> [CommandLineOption]
-> ModSummary
-> HsParsedModule
-> Hsc HsParsedModule
parsedResultAction :: [CommandLineOption] -> ModSummary -> HsParsedModule
-> Hsc HsParsedModule
, Plugin
-> [CommandLineOption]
-> TcGblEnv
-> HsGroup GhcRn
-> TcM (TcGblEnv, HsGroup GhcRn)
renamedResultAction :: [CommandLineOption] -> TcGblEnv
-> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
, Plugin
-> [CommandLineOption] -> ModSummary -> TcGblEnv -> TcM TcGblEnv
typeCheckResultAction :: [CommandLineOption] -> ModSummary -> TcGblEnv
-> TcM TcGblEnv
, Plugin
-> [CommandLineOption] -> LHsExpr GhcTc -> TcM (LHsExpr GhcTc)
spliceRunAction :: [CommandLineOption] -> LHsExpr GhcTc
-> TcM (LHsExpr GhcTc)
, Plugin
-> forall lcl. [CommandLineOption] -> ModIface -> IfM lcl ModIface
interfaceLoadAction :: forall lcl . [CommandLineOption] -> ModIface
-> IfM lcl ModIface
}
data PluginWithArgs = PluginWithArgs
{ PluginWithArgs -> Plugin
paPlugin :: Plugin
, PluginWithArgs -> [CommandLineOption]
paArguments :: [CommandLineOption]
}
data LoadedPlugin = LoadedPlugin
{ LoadedPlugin -> PluginWithArgs
lpPlugin :: PluginWithArgs
, LoadedPlugin -> ModIface
lpModule :: ModIface
}
data StaticPlugin = StaticPlugin
{ StaticPlugin -> PluginWithArgs
spPlugin :: PluginWithArgs
}
lpModuleName :: LoadedPlugin -> ModuleName
lpModuleName :: LoadedPlugin -> ModuleName
lpModuleName = Module -> ModuleName
moduleName (Module -> ModuleName)
-> (LoadedPlugin -> Module) -> LoadedPlugin -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface -> Module
mi_module (ModIface -> Module)
-> (LoadedPlugin -> ModIface) -> LoadedPlugin -> Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoadedPlugin -> ModIface
lpModule
pluginRecompile' :: PluginWithArgs -> IO PluginRecompile
pluginRecompile' :: PluginWithArgs -> IO PluginRecompile
pluginRecompile' (PluginWithArgs plugin :: Plugin
plugin args :: [CommandLineOption]
args) = Plugin -> [CommandLineOption] -> IO PluginRecompile
pluginRecompile Plugin
plugin [CommandLineOption]
args
data PluginRecompile = ForceRecompile | NoForceRecompile | MaybeRecompile Fingerprint
instance Outputable PluginRecompile where
ppr :: PluginRecompile -> SDoc
ppr ForceRecompile = CommandLineOption -> SDoc
text "ForceRecompile"
ppr NoForceRecompile = CommandLineOption -> SDoc
text "NoForceRecompile"
ppr (MaybeRecompile fp :: Fingerprint
fp) = CommandLineOption -> SDoc
text "MaybeRecompile" SDoc -> SDoc -> SDoc
<+> Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
fp
instance Semigroup PluginRecompile where
ForceRecompile <> :: PluginRecompile -> PluginRecompile -> PluginRecompile
<> _ = PluginRecompile
ForceRecompile
NoForceRecompile <> r :: PluginRecompile
r = PluginRecompile
r
MaybeRecompile fp :: Fingerprint
fp <> NoForceRecompile = Fingerprint -> PluginRecompile
MaybeRecompile Fingerprint
fp
MaybeRecompile fp :: Fingerprint
fp <> MaybeRecompile fp' :: Fingerprint
fp' = Fingerprint -> PluginRecompile
MaybeRecompile ([Fingerprint] -> Fingerprint
fingerprintFingerprints [Fingerprint
fp, Fingerprint
fp'])
MaybeRecompile _fp :: Fingerprint
_fp <> ForceRecompile = PluginRecompile
ForceRecompile
instance Monoid PluginRecompile where
mempty :: PluginRecompile
mempty = PluginRecompile
NoForceRecompile
type CorePlugin = [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]
type TcPlugin = [CommandLineOption] -> Maybe TcRnTypes.TcPlugin
purePlugin, impurePlugin, flagRecompile :: [CommandLineOption] -> IO PluginRecompile
purePlugin :: [CommandLineOption] -> IO PluginRecompile
purePlugin _args :: [CommandLineOption]
_args = PluginRecompile -> IO PluginRecompile
forall (m :: * -> *) a. Monad m => a -> m a
return PluginRecompile
NoForceRecompile
impurePlugin :: [CommandLineOption] -> IO PluginRecompile
impurePlugin _args :: [CommandLineOption]
_args = PluginRecompile -> IO PluginRecompile
forall (m :: * -> *) a. Monad m => a -> m a
return PluginRecompile
ForceRecompile
flagRecompile :: [CommandLineOption] -> IO PluginRecompile
flagRecompile =
PluginRecompile -> IO PluginRecompile
forall (m :: * -> *) a. Monad m => a -> m a
return (PluginRecompile -> IO PluginRecompile)
-> ([CommandLineOption] -> PluginRecompile)
-> [CommandLineOption]
-> IO PluginRecompile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fingerprint -> PluginRecompile
MaybeRecompile (Fingerprint -> PluginRecompile)
-> ([CommandLineOption] -> Fingerprint)
-> [CommandLineOption]
-> PluginRecompile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Fingerprint] -> Fingerprint
fingerprintFingerprints ([Fingerprint] -> Fingerprint)
-> ([CommandLineOption] -> [Fingerprint])
-> [CommandLineOption]
-> Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommandLineOption -> Fingerprint)
-> [CommandLineOption] -> [Fingerprint]
forall a b. (a -> b) -> [a] -> [b]
map CommandLineOption -> Fingerprint
fingerprintString ([CommandLineOption] -> [Fingerprint])
-> ([CommandLineOption] -> [CommandLineOption])
-> [CommandLineOption]
-> [Fingerprint]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CommandLineOption] -> [CommandLineOption]
forall a. Ord a => [a] -> [a]
sort
defaultPlugin :: Plugin
defaultPlugin :: Plugin
defaultPlugin = Plugin :: CorePlugin
-> TcPlugin
-> ([CommandLineOption] -> IO PluginRecompile)
-> ([CommandLineOption]
-> ModSummary -> HsParsedModule -> Hsc HsParsedModule)
-> ([CommandLineOption]
-> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn))
-> ([CommandLineOption] -> ModSummary -> TcGblEnv -> TcM TcGblEnv)
-> ([CommandLineOption] -> LHsExpr GhcTc -> TcM (LHsExpr GhcTc))
-> (forall lcl.
[CommandLineOption] -> ModIface -> IfM lcl ModIface)
-> Plugin
Plugin {
installCoreToDos :: CorePlugin
installCoreToDos = ([CoreToDo] -> CoreM [CoreToDo]) -> CorePlugin
forall a b. a -> b -> a
const [CoreToDo] -> CoreM [CoreToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return
, tcPlugin :: TcPlugin
tcPlugin = Maybe TcPlugin -> TcPlugin
forall a b. a -> b -> a
const Maybe TcPlugin
forall a. Maybe a
Nothing
, pluginRecompile :: [CommandLineOption] -> IO PluginRecompile
pluginRecompile = [CommandLineOption] -> IO PluginRecompile
impurePlugin
, renamedResultAction :: [CommandLineOption]
-> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
renamedResultAction = \_ env :: TcGblEnv
env grp :: HsGroup GhcRn
grp -> (TcGblEnv, HsGroup GhcRn) -> TcM (TcGblEnv, HsGroup GhcRn)
forall (m :: * -> *) a. Monad m => a -> m a
return (TcGblEnv
env, HsGroup GhcRn
grp)
, parsedResultAction :: [CommandLineOption]
-> ModSummary -> HsParsedModule -> Hsc HsParsedModule
parsedResultAction = \_ _ -> HsParsedModule -> Hsc HsParsedModule
forall (m :: * -> *) a. Monad m => a -> m a
return
, typeCheckResultAction :: [CommandLineOption] -> ModSummary -> TcGblEnv -> TcM TcGblEnv
typeCheckResultAction = \_ _ -> TcGblEnv -> TcM TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
return
, spliceRunAction :: [CommandLineOption] -> LHsExpr GhcTc -> TcM (LHsExpr GhcTc)
spliceRunAction = \_ -> LHsExpr GhcTc -> TcM (LHsExpr GhcTc)
forall (m :: * -> *) a. Monad m => a -> m a
return
, interfaceLoadAction :: forall lcl. [CommandLineOption] -> ModIface -> IfM lcl ModIface
interfaceLoadAction = \_ -> ModIface -> IOEnv (Env IfGblEnv lcl) ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return
}
keepRenamedSource :: [CommandLineOption] -> TcGblEnv
-> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
keepRenamedSource :: [CommandLineOption]
-> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
keepRenamedSource _ gbl_env :: TcGblEnv
gbl_env group :: HsGroup GhcRn
group =
(TcGblEnv, HsGroup GhcRn) -> TcM (TcGblEnv, HsGroup GhcRn)
forall (m :: * -> *) a. Monad m => a -> m a
return (TcGblEnv
gbl_env { tcg_rn_decls :: Maybe (HsGroup GhcRn)
tcg_rn_decls = Maybe (HsGroup GhcRn) -> Maybe (HsGroup GhcRn)
forall (p :: Pass).
Maybe (HsGroup (GhcPass p)) -> Maybe (HsGroup (GhcPass p))
update (TcGblEnv -> Maybe (HsGroup GhcRn)
tcg_rn_decls TcGblEnv
gbl_env)
, tcg_rn_exports :: Maybe [(Located (IE GhcRn), Avails)]
tcg_rn_exports = Maybe [(Located (IE GhcRn), Avails)]
-> Maybe [(Located (IE GhcRn), Avails)]
forall a. Maybe [a] -> Maybe [a]
update_exports (TcGblEnv -> Maybe [(Located (IE GhcRn), Avails)]
tcg_rn_exports TcGblEnv
gbl_env) }, HsGroup GhcRn
group)
where
update_exports :: Maybe [a] -> Maybe [a]
update_exports Nothing = [a] -> Maybe [a]
forall a. a -> Maybe a
Just []
update_exports m :: Maybe [a]
m = Maybe [a]
m
update :: Maybe (HsGroup (GhcPass p)) -> Maybe (HsGroup (GhcPass p))
update Nothing = HsGroup (GhcPass p) -> Maybe (HsGroup (GhcPass p))
forall a. a -> Maybe a
Just HsGroup (GhcPass p)
forall (p :: Pass). HsGroup (GhcPass p)
emptyRnGroup
update m :: Maybe (HsGroup (GhcPass p))
m = Maybe (HsGroup (GhcPass p))
m
type PluginOperation m a = Plugin -> [CommandLineOption] -> a -> m a
type ConstPluginOperation m a = Plugin -> [CommandLineOption] -> a -> m ()
plugins :: DynFlags -> [PluginWithArgs]
plugins :: DynFlags -> [PluginWithArgs]
plugins df :: DynFlags
df =
(LoadedPlugin -> PluginWithArgs)
-> [LoadedPlugin] -> [PluginWithArgs]
forall a b. (a -> b) -> [a] -> [b]
map LoadedPlugin -> PluginWithArgs
lpPlugin (DynFlags -> [LoadedPlugin]
cachedPlugins DynFlags
df) [PluginWithArgs] -> [PluginWithArgs] -> [PluginWithArgs]
forall a. [a] -> [a] -> [a]
++
(StaticPlugin -> PluginWithArgs)
-> [StaticPlugin] -> [PluginWithArgs]
forall a b. (a -> b) -> [a] -> [b]
map StaticPlugin -> PluginWithArgs
spPlugin (DynFlags -> [StaticPlugin]
staticPlugins DynFlags
df)
withPlugins :: Monad m => DynFlags -> PluginOperation m a -> a -> m a
withPlugins :: DynFlags -> PluginOperation m a -> a -> m a
withPlugins df :: DynFlags
df transformation :: PluginOperation m a
transformation input :: a
input = (a -> PluginWithArgs -> m a) -> a -> [PluginWithArgs] -> m a
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM a -> PluginWithArgs -> m a
go a
input (DynFlags -> [PluginWithArgs]
plugins DynFlags
df)
where
go :: a -> PluginWithArgs -> m a
go arg :: a
arg (PluginWithArgs p :: Plugin
p opts :: [CommandLineOption]
opts) = PluginOperation m a
transformation Plugin
p [CommandLineOption]
opts a
arg
mapPlugins :: DynFlags -> (Plugin -> [CommandLineOption] -> a) -> [a]
mapPlugins :: DynFlags -> (Plugin -> [CommandLineOption] -> a) -> [a]
mapPlugins df :: DynFlags
df f :: Plugin -> [CommandLineOption] -> a
f = (PluginWithArgs -> a) -> [PluginWithArgs] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (\(PluginWithArgs p :: Plugin
p opts :: [CommandLineOption]
opts) -> Plugin -> [CommandLineOption] -> a
f Plugin
p [CommandLineOption]
opts) (DynFlags -> [PluginWithArgs]
plugins DynFlags
df)
withPlugins_ :: Monad m => DynFlags -> ConstPluginOperation m a -> a -> m ()
withPlugins_ :: DynFlags -> ConstPluginOperation m a -> a -> m ()
withPlugins_ df :: DynFlags
df transformation :: ConstPluginOperation m a
transformation input :: a
input
= (PluginWithArgs -> m ()) -> [PluginWithArgs] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(PluginWithArgs p :: Plugin
p opts :: [CommandLineOption]
opts) -> ConstPluginOperation m a
transformation Plugin
p [CommandLineOption]
opts a
input)
(DynFlags -> [PluginWithArgs]
plugins DynFlags
df)
type FrontendPluginAction = [String] -> [(String, Maybe Phase)] -> Ghc ()
data FrontendPlugin = FrontendPlugin {
FrontendPlugin -> FrontendPluginAction
frontend :: FrontendPluginAction
}
defaultFrontendPlugin :: FrontendPlugin
defaultFrontendPlugin :: FrontendPlugin
defaultFrontendPlugin = FrontendPlugin :: FrontendPluginAction -> FrontendPlugin
FrontendPlugin { frontend :: FrontendPluginAction
frontend = \_ _ -> () -> Ghc ()
forall (m :: * -> *) a. Monad m => a -> m a
return () }