Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data FrontendPlugin = FrontendPlugin {}
- defaultFrontendPlugin :: FrontendPlugin
- type FrontendPluginAction = [String] -> [(String, Maybe Phase)] -> Ghc ()
- data Plugin = Plugin {
- installCoreToDos :: CorePlugin
- tcPlugin :: TcPlugin
- pluginRecompile :: [CommandLineOption] -> IO PluginRecompile
- parsedResultAction :: [CommandLineOption] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule
- renamedResultAction :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
- typeCheckResultAction :: [CommandLineOption] -> ModSummary -> TcGblEnv -> TcM TcGblEnv
- spliceRunAction :: [CommandLineOption] -> LHsExpr GhcTc -> TcM (LHsExpr GhcTc)
- interfaceLoadAction :: forall lcl. [CommandLineOption] -> ModIface -> IfM lcl ModIface
- type CommandLineOption = String
- data LoadedPlugin = LoadedPlugin {}
- lpModuleName :: LoadedPlugin -> ModuleName
- defaultPlugin :: Plugin
- keepRenamedSource :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
- withPlugins :: Monad m => DynFlags -> PluginOperation m a -> a -> m a
- withPlugins_ :: Monad m => DynFlags -> ConstPluginOperation m a -> a -> m ()
- data PluginRecompile
- purePlugin :: [CommandLineOption] -> IO PluginRecompile
- impurePlugin :: [CommandLineOption] -> IO PluginRecompile
- flagRecompile :: [CommandLineOption] -> IO PluginRecompile
Documentation
Plugin
is the compiler plugin data type. Try to avoid
constructing one of these directly, and just modify some fields of
defaultPlugin
instead: this is to try and preserve source-code
compatibility when we add fields to this.
Nonetheless, this API is preliminary and highly likely to change in the future.
Plugin | |
|
type CommandLineOption = String Source #
Command line options gathered from the -PModule.Name:stuff syntax are given to you as this type
data LoadedPlugin Source #
A plugin with its arguments. The result of loading the plugin.
LoadedPlugin | |
|
defaultPlugin :: Plugin Source #
Default plugin: does nothing at all! For compatibility reasons you should base all your plugin definitions on this default value.
keepRenamedSource :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn) Source #
A renamer plugin which mades the renamed source available in a typechecker plugin.
withPlugins :: Monad m => DynFlags -> PluginOperation m a -> a -> m a Source #
Perform an operation by using all of the plugins in turn.
withPlugins_ :: Monad m => DynFlags -> ConstPluginOperation m a -> a -> m () Source #
Perform a constant operation by using all of the plugins in turn.
data PluginRecompile Source #
Instances
Semigroup PluginRecompile # | |
Defined in Plugins (<>) :: PluginRecompile -> PluginRecompile -> PluginRecompile Source # sconcat :: NonEmpty PluginRecompile -> PluginRecompile Source # stimes :: Integral b => b -> PluginRecompile -> PluginRecompile Source # | |
Monoid PluginRecompile # | |
Defined in Plugins | |
Outputable PluginRecompile # | |
purePlugin :: [CommandLineOption] -> IO PluginRecompile Source #