[commit: ghc] wip/D5373: Add HoleFitPlugins and RawHoleFits (28909a1)

git at git.haskell.org git at git.haskell.org
Mon Jan 21 00:49:50 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/D5373
Link       : http://ghc.haskell.org/trac/ghc/changeset/28909a1a3ac54209a70c673ed1ceda1a2ba268e5/ghc

>---------------------------------------------------------------

commit 28909a1a3ac54209a70c673ed1ceda1a2ba268e5
Author: Matthías Páll Gissurarson <pallm at chalmers.se>
Date:   Sun Jan 20 19:44:15 2019 -0500

    Add HoleFitPlugins and RawHoleFits
    
    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 { relevantCts :: Cts -- ^ Any relevant Cts to the
    hole , implics :: [Implication] -- ^ The nested implications of the hole
    with the --   innermost implication first.  , holeCt :: 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 HoleFitPlugin
    hfp opts = Just (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 holeCt 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 <$> holeCt 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.
    
    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


>---------------------------------------------------------------

28909a1a3ac54209a70c673ed1ceda1a2ba268e5
 compiler/main/Plugins.hs                |   9 +-
 compiler/typecheck/TcHoleErrors.hs      | 218 +++++++++++++++++++-------------
 compiler/typecheck/TcHoleErrors.hs-boot |   2 +
 3 files changed, 141 insertions(+), 88 deletions(-)

Diff suppressed because of size. To see it, use:

    git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 28909a1a3ac54209a70c673ed1ceda1a2ba268e5


More information about the ghc-commits mailing list