Skip to content

Commit 53747d1

Browse files
Allow module-local and imported functions in Wingman metaprograms (#1856)
* Perform lookups of terms in scope and context * Fix imports * Add tests * Cleanup and haddock * mkFunTys' * Wrangle some imports for GHC 8.6 Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 4344617 commit 53747d1

19 files changed

+308
-50
lines changed

plugins/hls-tactics-plugin/src/Wingman/Context.hs

Lines changed: 16 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ import Bag
44
import Control.Arrow
55
import Control.Monad.Reader
66
import Data.Foldable.Extra (allM)
7-
import Data.Maybe (fromMaybe, isJust)
7+
import Data.Maybe (fromMaybe, isJust, mapMaybe)
88
import qualified Data.Set as S
99
import Development.IDE.GHC.Compat
1010
import GhcPlugins (ExternalPackageState (eps_inst_env), piResultTys)
@@ -27,11 +27,13 @@ mkContext
2727
-> Context
2828
mkContext cfg locals tcg eps kt ev = Context
2929
{ ctxDefiningFuncs = locals
30-
, ctxModuleFuncs = fmap splitId
31-
. (getFunBindId =<<)
32-
. fmap unLoc
33-
. bagToList
34-
$ tcg_binds tcg
30+
, ctxModuleFuncs
31+
= fmap splitId
32+
. mappend (locallyDefinedMethods tcg)
33+
. (getFunBindId =<<)
34+
. fmap unLoc
35+
. bagToList
36+
$ tcg_binds tcg
3537
, ctxConfig = cfg
3638
, ctxInstEnvs =
3739
InstEnvs
@@ -43,6 +45,14 @@ mkContext cfg locals tcg eps kt ev = Context
4345
}
4446

4547

48+
locallyDefinedMethods :: TcGblEnv -> [Id]
49+
locallyDefinedMethods
50+
= foldMap classMethods
51+
. mapMaybe tyConClass_maybe
52+
. tcg_tcs
53+
54+
55+
4656
splitId :: Id -> (OccName, CType)
4757
splitId = occName &&& CType . idType
4858

plugins/hls-tactics-plugin/src/Wingman/GHC.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ isFunction _ = True
7373
-- context.
7474
tacticsSplitFunTy :: Type -> ([TyVar], ThetaType, [Type], Type)
7575
tacticsSplitFunTy t
76-
= let (vars, theta, t') = tcSplitSigmaTy t
76+
= let (vars, theta, t') = tcSplitNestedSigmaTys t
7777
(args, res) = tcSplitFunTys t'
7878
in (vars, theta, args, res)
7979

plugins/hls-tactics-plugin/src/Wingman/Judgements.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -229,6 +229,7 @@ provAncestryOf (PatternMatchPrv (PatVal mo so _ _)) =
229229
provAncestryOf (ClassMethodPrv _) = mempty
230230
provAncestryOf UserPrv = mempty
231231
provAncestryOf RecursivePrv = mempty
232+
provAncestryOf ImportPrv = mempty
232233
provAncestryOf (DisallowedPrv _ p2) = provAncestryOf p2
233234

234235

plugins/hls-tactics-plugin/src/Wingman/LanguageServer.hs

Lines changed: 33 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE RankNTypes #-}
4+
{-# LANGUAGE TupleSections #-}
45
{-# LANGUAGE TypeFamilies #-}
56

67
{-# LANGUAGE NoMonoLocalBinds #-}
@@ -43,6 +44,7 @@ import Development.IDE.Spans.LocalBindings (Bindings, getDefiningBindi
4344
import qualified FastString
4445
import GHC.Generics (Generic)
4546
import Generics.SYB hiding (Generic)
47+
import GhcPlugins (extractModule)
4648
import GhcPlugins (tupleDataCon, consDataCon, substTyAddInScope, ExternalPackageState, HscEnv (hsc_EPS), unpackFS)
4749
import qualified Ide.Plugin.Config as Plugin
4850
import Ide.Plugin.Properties
@@ -57,13 +59,14 @@ import OccName
5759
import Prelude hiding (span)
5860
import Retrie (transformA)
5961
import SrcLoc (containsSpan)
60-
import TcRnTypes (tcg_binds, TcGblEnv)
62+
import TcRnTypes (tcg_binds, TcGblEnv (tcg_rdr_env))
6163
import Wingman.Context
6264
import Wingman.FeatureSet
6365
import Wingman.GHC
6466
import Wingman.Judgements
6567
import Wingman.Judgements.SYB (everythingContaining, metaprogramQ)
6668
import Wingman.Judgements.Theta
69+
import Wingman.Metaprogramming.Lexer (ParserContext(..))
6770
import Wingman.Range
6871
import Wingman.StaticPlugin (pattern WingmanMetaprogram, pattern MetaprogramSyntax)
6972
import Wingman.Types
@@ -576,6 +579,10 @@ mkWorkspaceEdits dflags ccs uri pm g = do
576579
in first (InfrastructureError . T.pack) response
577580

578581

582+
------------------------------------------------------------------------------
583+
-- | Add ExactPrint annotations to every metaprogram in the source tree.
584+
-- Usually the ExactPrint module can do this for us, but we've enabled
585+
-- QuasiQuotes, so the round-trip print/parse journey will crash.
579586
annotateMetaprograms :: Data a => a -> Transform a
580587
annotateMetaprograms = everywhereM $ mkM $ \case
581588
L ss (WingmanMetaprogram mp) -> do
@@ -585,6 +592,9 @@ annotateMetaprograms = everywhereM $ mkM $ \case
585592
pure x
586593
(x :: LHsExpr GhcPs) -> pure x
587594

595+
596+
------------------------------------------------------------------------------
597+
-- | Find the source of a tactic metaprogram at the given span.
588598
getMetaprogramAtSpan
589599
:: Tracked age SrcSpan
590600
-> Tracked age TcGblEnv
@@ -596,3 +606,25 @@ getMetaprogramAtSpan (unTrack -> ss)
596606
. tcg_binds
597607
. unTrack
598608

609+
610+
------------------------------------------------------------------------------
611+
-- | The metaprogram parser needs the ability to lookup terms from the module
612+
-- and imports. The 'ParserContext' contains everything we need to find that
613+
-- stuff.
614+
getParserState
615+
:: IdeState
616+
-> NormalizedFilePath
617+
-> Context
618+
-> MaybeT IO ParserContext
619+
getParserState state nfp ctx = do
620+
let stale a = runStaleIde "getParserState" state nfp a
621+
622+
TrackedStale (unTrack -> tcmod) _ <- stale TypeCheck
623+
TrackedStale (unTrack -> hscenv) _ <- stale GhcSessionDeps
624+
625+
let tcgblenv = tmrTypechecked tcmod
626+
modul = extractModule tcgblenv
627+
rdrenv = tcg_rdr_env tcgblenv
628+
629+
pure $ ParserContext (hscEnv hscenv) rdrenv modul ctx
630+

plugins/hls-tactics-plugin/src/Wingman/LanguageServer/Metaprogram.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Wingman.LanguageServer.Metaprogram
1010

1111
import Control.Applicative (empty)
1212
import Control.Monad
13+
import Control.Monad.Reader (runReaderT)
1314
import Control.Monad.Trans
1415
import Control.Monad.Trans.Maybe
1516
import Data.List (find)
@@ -30,8 +31,8 @@ import Prelude hiding (span)
3031
import TcRnTypes (tcg_binds)
3132
import Wingman.GHC
3233
import Wingman.Judgements.SYB (metaprogramQ)
33-
import Wingman.Metaprogramming.Parser (attempt_it)
3434
import Wingman.LanguageServer
35+
import Wingman.Metaprogramming.Parser (attempt_it)
3536
import Wingman.Types
3637

3738

@@ -53,12 +54,12 @@ hoverProvider state plId (HoverParams (TextDocumentIdentifier uri) (unsafeMkCurr
5354
Just (trss, program) -> do
5455
let tr_range = fmap realSrcSpanToRange trss
5556
HoleJudgment{hj_jdg=jdg, hj_ctx=ctx} <- judgementForHole state nfp tr_range cfg
57+
ps <- getParserState state nfp ctx
58+
z <- liftIO $ flip runReaderT ps $ attempt_it ctx jdg $ T.unpack program
5659
pure $ Hover
5760
{ _contents = HoverContents
5861
$ MarkupContent MkMarkdown
59-
$ either T.pack T.pack
60-
$ attempt_it ctx jdg
61-
$ T.unpack program
62+
$ either T.pack T.pack z
6263
, _range = Just $ unTrack tr_range
6364
}
6465
Nothing -> empty

plugins/hls-tactics-plugin/src/Wingman/LanguageServer/TacticProviders.hs

Lines changed: 15 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -34,26 +34,28 @@ import Wingman.FeatureSet
3434
import Wingman.GHC
3535
import Wingman.Judgements
3636
import Wingman.Machinery (useNameFromHypothesis)
37+
import Wingman.Metaprogramming.Lexer (ParserContext)
3738
import Wingman.Metaprogramming.Parser (parseMetaprogram)
3839
import Wingman.Tactics
3940
import Wingman.Types
41+
import Control.Monad.Reader (runReaderT)
4042

4143

4244
------------------------------------------------------------------------------
4345
-- | A mapping from tactic commands to actual tactics for refinery.
44-
commandTactic :: TacticCommand -> T.Text -> TacticsM ()
45-
commandTactic Auto = const auto
46-
commandTactic Intros = const intros
47-
commandTactic Destruct = useNameFromHypothesis destruct . mkVarOcc . T.unpack
48-
commandTactic DestructPun = useNameFromHypothesis destructPun . mkVarOcc . T.unpack
49-
commandTactic Homomorphism = useNameFromHypothesis homo . mkVarOcc . T.unpack
50-
commandTactic DestructLambdaCase = const destructLambdaCase
51-
commandTactic HomomorphismLambdaCase = const homoLambdaCase
52-
commandTactic DestructAll = const destructAll
53-
commandTactic UseDataCon = userSplit . mkVarOcc . T.unpack
54-
commandTactic Refine = const refine
55-
commandTactic BeginMetaprogram = const metaprogram
56-
commandTactic RunMetaprogram = parseMetaprogram
46+
commandTactic :: ParserContext -> TacticCommand -> T.Text -> IO (TacticsM ())
47+
commandTactic _ Auto = pure . const auto
48+
commandTactic _ Intros = pure . const intros
49+
commandTactic _ Destruct = pure . useNameFromHypothesis destruct . mkVarOcc . T.unpack
50+
commandTactic _ DestructPun = pure . useNameFromHypothesis destructPun . mkVarOcc . T.unpack
51+
commandTactic _ Homomorphism = pure . useNameFromHypothesis homo . mkVarOcc . T.unpack
52+
commandTactic _ DestructLambdaCase = pure . const destructLambdaCase
53+
commandTactic _ HomomorphismLambdaCase = pure . const homoLambdaCase
54+
commandTactic _ DestructAll = pure . const destructAll
55+
commandTactic _ UseDataCon = pure . userSplit . mkVarOcc . T.unpack
56+
commandTactic _ Refine = pure . const refine
57+
commandTactic _ BeginMetaprogram = pure . const metaprogram
58+
commandTactic c RunMetaprogram = flip runReaderT c . parseMetaprogram
5759

5860

5961
------------------------------------------------------------------------------

plugins/hls-tactics-plugin/src/Wingman/Machinery.hs

Lines changed: 54 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
module Wingman.Machinery where
44

55
import Class (Class (classTyVars))
6+
import Control.Applicative (empty)
67
import Control.Lens ((<>~))
78
import Control.Monad.Error.Class
89
import Control.Monad.Reader
@@ -22,13 +23,15 @@ import Data.Monoid (getSum)
2223
import Data.Ord (Down (..), comparing)
2324
import Data.Set (Set)
2425
import qualified Data.Set as S
26+
import Development.IDE.Core.Compile (lookupName)
2527
import Development.IDE.GHC.Compat
26-
import OccName (HasOccName (occName))
28+
import GhcPlugins (GlobalRdrElt (gre_name), lookupOccEnv, varType)
29+
import OccName (HasOccName (occName), OccEnv)
2730
import Refinery.ProofState
2831
import Refinery.Tactic
2932
import Refinery.Tactic.Internal
3033
import TcType
31-
import Type
34+
import Type (tyCoVarsOfTypeWellScoped, splitTyConApp_maybe)
3235
import Unify
3336
import Wingman.Judgements
3437
import Wingman.Simplify (simplify)
@@ -315,3 +318,52 @@ useNameFromHypothesis f name = do
315318
Just hi -> f hi
316319
Nothing -> throwError $ NotInScope name
317320

321+
------------------------------------------------------------------------------
322+
-- | Lift a function over 'HyInfo's to one that takes an 'OccName' and tries to
323+
-- look it up in the hypothesis.
324+
useNameFromContext :: (HyInfo CType -> TacticsM a) -> OccName -> TacticsM a
325+
useNameFromContext f name = do
326+
lookupNameInContext name >>= \case
327+
Just ty -> f $ createImportedHyInfo name ty
328+
Nothing -> throwError $ NotInScope name
329+
330+
331+
------------------------------------------------------------------------------
332+
-- | Find the type of an 'OccName' that is defined in the current module.
333+
lookupNameInContext :: MonadReader Context m => OccName -> m (Maybe CType)
334+
lookupNameInContext name = do
335+
ctx <- asks ctxModuleFuncs
336+
pure $ case find ((== name) . fst) ctx of
337+
Just (_, ty) -> pure ty
338+
Nothing -> empty
339+
340+
341+
------------------------------------------------------------------------------
342+
-- | Build a 'HyInfo' for an imported term.
343+
createImportedHyInfo :: OccName -> CType -> HyInfo CType
344+
createImportedHyInfo on ty = HyInfo
345+
{ hi_name = on
346+
, hi_provenance = ImportPrv
347+
, hi_type = ty
348+
}
349+
350+
351+
------------------------------------------------------------------------------
352+
-- | Lookup the type of any 'OccName' that was imported. Necessarily done in
353+
-- IO, so we only expose this functionality to the parser. Internal Haskell
354+
-- code that wants to lookup terms should do it via 'KnownThings'.
355+
getOccNameType
356+
:: HscEnv
357+
-> OccEnv [GlobalRdrElt]
358+
-> Module
359+
-> OccName
360+
-> IO (Maybe Type)
361+
getOccNameType hscenv rdrenv modul occ =
362+
case lookupOccEnv rdrenv occ of
363+
Just (elt : _) -> do
364+
mvar <- lookupName hscenv modul $ gre_name elt
365+
pure $ case mvar of
366+
Just (AnId v) -> pure $ varType v
367+
_ -> Nothing
368+
_ -> pure Nothing
369+

plugins/hls-tactics-plugin/src/Wingman/Metaprogramming/Lexer.hs

Lines changed: 16 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,16 +7,31 @@ module Wingman.Metaprogramming.Lexer where
77

88
import Control.Applicative
99
import Control.Monad
10+
import Control.Monad.Reader (ReaderT)
1011
import Data.Text (Text)
1112
import qualified Data.Text as T
1213
import Data.Void
14+
import Development.IDE.GHC.Compat (HscEnv, Module)
15+
import GhcPlugins (GlobalRdrElt)
1316
import Name
1417
import qualified Text.Megaparsec as P
1518
import qualified Text.Megaparsec.Char as P
1619
import qualified Text.Megaparsec.Char.Lexer as L
20+
import Wingman.Types (Context)
21+
22+
23+
------------------------------------------------------------------------------
24+
-- | Everything we need in order to call 'Wingman.Machinery.getOccNameType'.
25+
data ParserContext = ParserContext
26+
{ ps_hscEnv :: HscEnv
27+
, ps_occEnv :: OccEnv [GlobalRdrElt]
28+
, ps_module :: Module
29+
, ps_context :: Context
30+
}
31+
32+
type Parser = P.ParsecT Void Text (ReaderT ParserContext IO)
1733

1834

19-
type Parser = P.Parsec Void Text
2035

2136
lineComment :: Parser ()
2237
lineComment = L.skipLineComment "--"

0 commit comments

Comments
 (0)