summaryrefslogtreecommitdiff
path: root/compiler/typecheck/TcRnDriver.hs
diff options
context:
space:
mode:
authorMatthías Páll Gissurarson <pallm@chalmers.se>2019-01-20 19:44:15 -0500
committerMatthías Páll Gissurarson <pallm@chalmers.se>2019-06-21 03:21:21 +0200
commitc311277bf640a4aeb929f3080eaaf656c0e0611c (patch)
tree2955570d4650a066be2c80dd9fba6de47453bfe9 /compiler/typecheck/TcRnDriver.hs
parentfe819dd637842fb564524a7cf80612a3673ce14c (diff)
downloadhaskell-c311277bf640a4aeb929f3080eaaf656c0e0611c.tar.gz
Add HoleFitPlugins and RawHoleFitswip/D5373
This patch adds a new kind of plugin, Hole fit plugins. These plugins can change what candidates are considered when looking for valid hole fits, and add hole fits of their own. The type of a plugin is relatively simple, ``` type FitPlugin = TypedHole -> [HoleFit] -> TcM [HoleFit] type CandPlugin = TypedHole -> [HoleFitCandidate] -> TcM [HoleFitCandidate] data HoleFitPlugin = HoleFitPlugin { candPlugin :: CandPlugin , fitPlugin :: FitPlugin } data TypedHole = TyH { tyHRelevantCts :: Cts -- ^ Any relevant Cts to the hole , tyHImplics :: [Implication] -- ^ The nested implications of the hole with the -- innermost implication first. , tyHCt :: Maybe Ct -- ^ The hole constraint itself, if available. } This allows users and plugin writers to interact with the candidates and fits as they wish, even going as far as to allow them to reimplement the current functionality (since `TypedHole` contains all the relevant information). As an example, consider the following plugin: ``` module HolePlugin where import GhcPlugins import TcHoleErrors import Data.List (intersect, stripPrefix) import RdrName (importSpecModule) import TcRnTypes import System.Process plugin :: Plugin plugin = defaultPlugin { holeFitPlugin = hfp, pluginRecompile = purePlugin } hfp :: [CommandLineOption] -> Maybe HoleFitPluginR hfp opts = Just (fromPureHFPlugin $ HoleFitPlugin (candP opts) (fp opts)) toFilter :: Maybe String -> Maybe String toFilter = flip (>>=) (stripPrefix "_module_") replace :: Eq a => a -> a -> [a] -> [a] replace match repl str = replace' [] str where replace' sofar (x:xs) | x == match = replace' (repl:sofar) xs replace' sofar (x:xs) = replace' (x:sofar) xs replace' sofar [] = reverse sofar -- | This candidate plugin filters the candidates by module, -- using the name of the hole as module to search in candP :: [CommandLineOption] -> CandPlugin candP _ hole cands = do let he = case tyHCt hole of Just (CHoleCan _ h) -> Just (occNameString $ holeOcc h) _ -> Nothing case toFilter he of Just undscModName -> do let replaced = replace '_' '.' undscModName let res = filter (greNotInOpts [replaced]) cands return $ res _ -> return cands where greNotInOpts opts (GreHFCand gre) = not $ null $ intersect (inScopeVia gre) opts greNotInOpts _ _ = True inScopeVia = map (moduleNameString . importSpecModule) . gre_imp -- Yes, it's pretty hacky, but it is just an example :) searchHoogle :: String -> IO [String] searchHoogle ty = lines <$> (readProcess "hoogle" [(show ty)] []) fp :: [CommandLineOption] -> FitPlugin fp ("hoogle":[]) hole hfs = do dflags <- getDynFlags let tyString = showSDoc dflags . ppr . ctPred <$> tyHCt hole res <- case tyString of Just ty -> liftIO $ searchHoogle ty _ -> return [] return $ (take 2 $ map (RawHoleFit . text . ("Hoogle says: " ++)) res) ++ hfs fp _ _ hfs = return hfs ``` with this plugin available, you can compile the following file ``` {-# OPTIONS -fplugin=HolePlugin -fplugin-opt=HolePlugin:hoogle #-} module Main where import Prelude hiding (head, last) import Data.List (head, last) t :: [Int] -> Int t = _module_Prelude g :: [Int] -> Int g = _module_Data_List main :: IO () main = print $ t [1,2,3] ``` and get the following output: ``` Main.hs:14:5: error: • Found hole: _module_Prelude :: [Int] -> Int Or perhaps ‘_module_Prelude’ is mis-spelled, or not in scope • In the expression: _module_Prelude In an equation for ‘t’: t = _module_Prelude • Relevant bindings include t :: [Int] -> Int (bound at Main.hs:14:1) Valid hole fits include Hoogle says: GHC.List length :: [a] -> Int Hoogle says: GHC.OldList length :: [a] -> Int t :: [Int] -> Int (bound at Main.hs:14:1) g :: [Int] -> Int (bound at Main.hs:17:1) length :: forall (t :: * -> *) a. Foldable t => t a -> Int with length @[] @Int (imported from ‘Prelude’ at Main.hs:5:1-34 (and originally defined in ‘Data.Foldable’)) maximum :: forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a with maximum @[] @Int (imported from ‘Prelude’ at Main.hs:5:1-34 (and originally defined in ‘Data.Foldable’)) (Some hole fits suppressed; use -fmax-valid-hole-fits=N or -fno-max-valid-hole-fits) | 14 | t = _module_Prelude | ^^^^^^^^^^^^^^^ Main.hs:17:5: error: • Found hole: _module_Data_List :: [Int] -> Int Or perhaps ‘_module_Data_List’ is mis-spelled, or not in scope • In the expression: _module_Data_List In an equation for ‘g’: g = _module_Data_List • Relevant bindings include g :: [Int] -> Int (bound at Main.hs:17:1) Valid hole fits include Hoogle says: GHC.List length :: [a] -> Int Hoogle says: GHC.OldList length :: [a] -> Int g :: [Int] -> Int (bound at Main.hs:17:1) head :: forall a. [a] -> a with head @Int (imported from ‘Data.List’ at Main.hs:7:19-22 (and originally defined in ‘GHC.List’)) last :: forall a. [a] -> a with last @Int (imported from ‘Data.List’ at Main.hs:7:25-28 (and originally defined in ‘GHC.List’)) | 17 | g = _module_Data_List ``` This relatively simple plugin has two functions, as an example of what is possible to do with hole fit plugins. The candidate plugin starts by filtering the candidates considered by module, indicated by the name of the hole (`_module_Data_List`). The second function is in the fit plugin, where the plugin invokes a local hoogle instance to search by the type of the hole. By adding the `RawHoleFit` type, we can also allow these completely free suggestions, used in the plugin above to display fits found by Hoogle. Additionally, the `HoleFitPluginR` wrapper can be used for plugins to maintain state between invocations, which can be used to speed up invocation of plugins that have expensive initialization. ``` -- | 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. data HoleFitPluginR = forall s. HoleFitPluginR { hfPluginInit :: TcM (TcRef s) -- ^ Initializes the TcRef to be passed to the plugin , hfPluginRun :: TcRef s -> HoleFitPlugin -- ^ The function defining the plugin itself , hfPluginStop :: TcRef s -> TcM () -- ^ Cleanup of state, guaranteed to be called even on error } ``` Of course, the syntax here is up for debate, but hole fit plugins allow us to experiment relatively easily with ways to interact with typed-holes without having to dig deep into GHC. Reviewers: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5373
Diffstat (limited to 'compiler/typecheck/TcRnDriver.hs')
-rw-r--r--compiler/typecheck/TcRnDriver.hs31
1 files changed, 29 insertions, 2 deletions
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 3ffc5df61e..55c229766f 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -140,6 +140,9 @@ import qualified Data.Set as S
import Control.DeepSeq
import Control.Monad
+import TcHoleFitTypes ( HoleFitPluginR (..) )
+
+
#include "HsVersions.h"
{-
@@ -164,7 +167,7 @@ tcRnModule hsc_env mod_sum save_rn_syntax
(text "Renamer/typechecker"<+>brackets (ppr this_mod))
(const ()) $
initTc hsc_env hsc_src save_rn_syntax this_mod real_loc $
- withTcPlugins hsc_env $
+ withTcPlugins hsc_env $ withHoleFitPlugins hsc_env $
tcRnModuleTcRnM hsc_env mod_sum parsedModule pair
@@ -1840,7 +1843,7 @@ runTcInteractive :: HscEnv -> TcRn a -> IO (Messages, Maybe a)
-- Initialise the tcg_inst_env with instances from all home modules.
-- This mimics the more selective call to hptInstances in tcRnImports
runTcInteractive hsc_env thing_inside
- = initTcInteractive hsc_env $ withTcPlugins hsc_env $
+ = initTcInteractive hsc_env $ withTcPlugins hsc_env $ withHoleFitPlugins hsc_env $
do { traceTc "setInteractiveContext" $
vcat [ text "ic_tythings:" <+> vcat (map ppr (ic_tythings icxt))
, text "ic_insts:" <+> vcat (map (pprBndr LetBind . instanceDFunId) ic_insts)
@@ -2880,6 +2883,30 @@ withTcPlugins hsc_env m =
getTcPlugins :: DynFlags -> [TcRnMonad.TcPlugin]
getTcPlugins dflags = catMaybes $ mapPlugins dflags (\p args -> tcPlugin p args)
+
+withHoleFitPlugins :: HscEnv -> TcM a -> TcM a
+withHoleFitPlugins hsc_env m =
+ case (getHfPlugins (hsc_dflags hsc_env)) of
+ [] -> m -- Common fast case
+ plugins -> do (plugins,stops) <- unzip `fmap` mapM startPlugin plugins
+ -- This ensures that hfPluginStop is called even if a type
+ -- error occurs during compilation.
+ eitherRes <- tryM $ do
+ updGblEnv (\e -> e { tcg_hf_plugins = plugins }) m
+ sequence_ stops
+ case eitherRes of
+ Left _ -> failM
+ Right res -> return res
+ where
+ startPlugin (HoleFitPluginR init plugin stop) =
+ do ref <- init
+ return (plugin ref, stop ref)
+
+getHfPlugins :: DynFlags -> [HoleFitPluginR]
+getHfPlugins dflags =
+ catMaybes $ mapPlugins dflags (\p args -> holeFitPlugin p args)
+
+
runRenamerPlugin :: TcGblEnv
-> HsGroup GhcRn
-> TcM (TcGblEnv, HsGroup GhcRn)