Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- defaultPlugin :: Plugin
- type CommandLineOption = String
- purePlugin :: [CommandLineOption] -> IO PluginRecompile
- impurePlugin :: [CommandLineOption] -> IO PluginRecompile
- flagRecompile :: [CommandLineOption] -> IO PluginRecompile
- data PluginRecompile
- data FrontendPlugin = FrontendPlugin {}
- defaultFrontendPlugin :: FrontendPlugin
- type FrontendPluginAction = [String] -> [(String, Maybe Phase)] -> Ghc ()
- type CorePlugin = [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]
- type TcPlugin = [CommandLineOption] -> Maybe TcPlugin
- keepRenamedSource :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
- data PluginWithArgs = PluginWithArgs {}
- plugins :: DynFlags -> [PluginWithArgs]
- pluginRecompile' :: PluginWithArgs -> IO PluginRecompile
- data LoadedPlugin = LoadedPlugin {}
- lpModuleName :: LoadedPlugin -> ModuleName
- data StaticPlugin = StaticPlugin {}
- mapPlugins :: DynFlags -> (Plugin -> [CommandLineOption] -> a) -> [a]
- withPlugins :: Monad m => DynFlags -> PluginOperation m a -> a -> m a
- withPlugins_ :: Monad m => DynFlags -> ConstPluginOperation m a -> a -> m ()
Plugins
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 | |
|
defaultPlugin :: Plugin Source #
Default plugin: does nothing at all! For compatibility reasons you should base all your plugin definitions on this default value.
type CommandLineOption = String Source #
Command line options gathered from the -PModule.Name:stuff syntax are given to you as this type
Recompilation checking
purePlugin :: [CommandLineOption] -> IO PluginRecompile Source #
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 # | |
Plugin types
Frontend plugins
Core plugins
Core plugins allow plugins to register as a Core-to-Core pass.
type CorePlugin = [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo] Source #
Typechecker plugins
Typechecker plugins allow plugins to provide evidence to the typechecker.
Source plugins
GHC offers a number of points where plugins can access and modify its front-end ("source") representation. These include:
- access to the parser result with
parsedResultAction
- access to the renamed AST with
renamedResultAction
- access to the typechecked AST with
typeCheckResultAction
- access to the Template Haskell splices with
spliceRunAction
- access to loaded interface files with
interfaceLoadAction
keepRenamedSource :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn) Source #
A renamer plugin which mades the renamed source available in a typechecker plugin.
Internal
data PluginWithArgs Source #
PluginWithArgs | |
|
plugins :: DynFlags -> [PluginWithArgs] Source #
data LoadedPlugin Source #
A plugin with its arguments. The result of loading the plugin.
LoadedPlugin | |
|
data StaticPlugin Source #
A static plugin with its arguments. For registering compiled-in plugins through the GHC API.
StaticPlugin | |
|
mapPlugins :: DynFlags -> (Plugin -> [CommandLineOption] -> a) -> [a] Source #
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.