| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Driver.Plugins
Description
Definitions for writing plugins for GHC. Plugins can hook into
 several areas of the compiler. See the Plugin type. These plugins
 include type-checker plugins, source plugins, and core-to-core plugins.
Synopsis
- data Plugins = Plugins {- staticPlugins :: ![StaticPlugin]
- loadedPlugins :: ![LoadedPlugin]
- loadedPluginDeps :: !([Linkable], PkgsLoaded)
 
- emptyPlugins :: Plugins
- data Plugin = Plugin {- installCoreToDos :: CorePlugin
- tcPlugin :: TcPlugin
- defaultingPlugin :: DefaultingPlugin
- holeFitPlugin :: HoleFitPlugin
- driverPlugin :: [CommandLineOption] -> HscEnv -> IO HscEnv
- pluginRecompile :: [CommandLineOption] -> IO PluginRecompile
- parsedResultAction :: [CommandLineOption] -> ModSummary -> ParsedResult -> Hsc ParsedResult
- 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
- data PsMessages = PsMessages {}
- data ParsedResult = ParsedResult {}
- 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)
- type DefaultingPlugin = [CommandLineOption] -> Maybe DefaultingPlugin
- data HoleFitPluginR
- data PluginWithArgs = PluginWithArgs {}
- pluginsWithArgs :: Plugins -> [PluginWithArgs]
- pluginRecompile' :: PluginWithArgs -> IO PluginRecompile
- data LoadedPlugin = LoadedPlugin {}
- lpModuleName :: LoadedPlugin -> ModuleName
- data StaticPlugin = StaticPlugin {}
- mapPlugins :: Plugins -> (Plugin -> [CommandLineOption] -> a) -> [a]
- withPlugins :: Monad m => Plugins -> PluginOperation m a -> a -> m a
- withPlugins_ :: Monad m => Plugins -> ConstPluginOperation m a -> a -> m ()
Plugins
Constructors
| Plugins | |
| Fields 
 | |
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.
Constructors
| Plugin | |
| Fields 
 | |
defaultPlugin :: Plugin Source #
Default plugin: does nothing at all, except for marking that safe
 inference has failed unless -fplugin-trustworthy is passed. For
 compatibility reason 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
data ParsedResult Source #
Result of running the parser and the parser plugin
Constructors
| ParsedResult | |
| Fields 
 | |
Recompilation checking
purePlugin :: [CommandLineOption] -> IO PluginRecompile Source #
data PluginRecompile Source #
Constructors
| ForceRecompile | |
| NoForceRecompile | |
| MaybeRecompile Fingerprint | 
Instances
| Monoid PluginRecompile Source # | |
| Defined in GHC.Driver.Plugins Methods mappend :: PluginRecompile -> PluginRecompile -> PluginRecompile # mconcat :: [PluginRecompile] -> PluginRecompile # | |
| Semigroup PluginRecompile Source # | |
| Defined in GHC.Driver.Plugins Methods (<>) :: PluginRecompile -> PluginRecompile -> PluginRecompile # sconcat :: NonEmpty PluginRecompile -> PluginRecompile # stimes :: Integral b => b -> PluginRecompile -> PluginRecompile # | |
| Outputable PluginRecompile Source # | |
| Defined in GHC.Driver.Plugins Methods ppr :: PluginRecompile -> SDoc Source # | |
Plugin types
Frontend plugins
data FrontendPlugin Source #
Constructors
| FrontendPlugin | |
| Fields | |
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.
Defaulting plugins
Defaulting plugins can add candidate types to the defaulting mechanism.
type DefaultingPlugin = [CommandLineOption] -> Maybe DefaultingPlugin Source #
Hole fit plugins
hole fit plugins allow plugins to change the behavior of valid hole fit suggestions
data HoleFitPluginR Source #
HoleFitPluginR adds a TcRef to hole fit plugins so that plugins can track internal state. Note the existential quantification, ensuring that the state cannot be modified from outside the plugin.
Internal
data PluginWithArgs Source #
Constructors
| PluginWithArgs | |
| Fields 
 | |
pluginsWithArgs :: Plugins -> [PluginWithArgs] Source #
data LoadedPlugin Source #
A plugin with its arguments. The result of loading the plugin.
Constructors
| LoadedPlugin | |
| Fields 
 | |
data StaticPlugin Source #
A static plugin with its arguments. For registering compiled-in plugins through the GHC API.
Constructors
| StaticPlugin | |
| Fields 
 | |
mapPlugins :: Plugins -> (Plugin -> [CommandLineOption] -> a) -> [a] Source #
withPlugins :: Monad m => Plugins -> PluginOperation m a -> a -> m a Source #
Perform an operation by using all of the plugins in turn.
withPlugins_ :: Monad m => Plugins -> ConstPluginOperation m a -> a -> m () Source #
Perform a constant operation by using all of the plugins in turn.