[commit: ghc] master: Plugins: Add documentation and missing exports (49f5c6c)
git at git.haskell.org
git at git.haskell.org
Sun Oct 28 17:41:15 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/49f5c6c33a6668152f0fb306075c891f317249d7/ghc
>---------------------------------------------------------------
commit 49f5c6c33a6668152f0fb306075c891f317249d7
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Sun Oct 28 12:36:15 2018 -0400
Plugins: Add documentation and missing exports
Summary:
Previously the TcPlugin and CorePlugin type synonyms were not exporting,
resulting in much confusion.
Reviewers: mpickering
Reviewed By: mpickering
Subscribers: rwbarton, carter
Differential Revision: https://phabricator.haskell.org/D5237
>---------------------------------------------------------------
49f5c6c33a6668152f0fb306075c891f317249d7
compiler/main/Plugins.hs | 36 ++++++++++++++++++++++++++++++++----
compiler/typecheck/TcRnDriver.hs | 2 +-
2 files changed, 33 insertions(+), 5 deletions(-)
diff --git a/compiler/main/Plugins.hs b/compiler/main/Plugins.hs
index 01a9841..430b079 100644
--- a/compiler/main/Plugins.hs
+++ b/compiler/main/Plugins.hs
@@ -1,11 +1,39 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
module Plugins (
- FrontendPlugin(..), defaultFrontendPlugin, FrontendPluginAction
- , Plugin(..), CommandLineOption, LoadedPlugin(..), lpModuleName
- , defaultPlugin, keepRenamedSource, withPlugins, withPlugins_
- , PluginRecompile(..)
+ -- * Plugins
+ Plugin(..)
+ , defaultPlugin
+ , CommandLineOption
+ -- ** Recompilation checking
, purePlugin, impurePlugin, flagRecompile
+ , PluginRecompile(..)
+
+ -- * Plugin types
+ -- ** Frontend plugins
+ , FrontendPlugin(..), defaultFrontendPlugin, FrontendPluginAction
+ -- ** Core plugins
+ -- | Core plugins allow plugins to register as a Core-to-Core pass.
+ , CorePlugin
+ -- ** Typechecker plugins
+ -- | Typechecker plugins allow plugins to provide evidence to the
+ -- typechecker.
+ , TcPlugin
+ -- ** 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
+
+ -- * Internal
+ , LoadedPlugin(..), lpModuleName
+ , withPlugins, withPlugins_
) where
import GhcPrelude
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 1c04327..a0a837e 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -2821,7 +2821,7 @@ withTcPlugins hsc_env m =
do s <- runTcPluginM start ev_binds_var
return (solve s, stop s)
-getTcPlugins :: DynFlags -> [TcPlugin]
+getTcPlugins :: DynFlags -> [TcRnMonad.TcPlugin]
getTcPlugins dflags = catMaybes $ map get_plugin (plugins dflags)
where get_plugin p = tcPlugin (lpPlugin p) (lpArguments p)
More information about the ghc-commits
mailing list