Skip to content

Commit 4e6e964

Browse files
Make getCurrentDefinitions return polymorphic types (#1945)
Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 48fcaf1 commit 4e6e964

File tree

9 files changed

+55
-17
lines changed

9 files changed

+55
-17
lines changed

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

+1-2
Original file line numberDiff line numberDiff line change
@@ -5,10 +5,9 @@ import Control.Monad.Reader.Class (asks)
55
import Control.Monad.State (gets)
66
import qualified Data.Set as S
77
import Refinery.Tactic
8-
import Wingman.Context
98
import Wingman.Judgements
109
import Wingman.KnownStrategies
11-
import Wingman.Machinery (tracing)
10+
import Wingman.Machinery (tracing, getCurrentDefinitions)
1211
import Wingman.Tactics
1312
import Wingman.Types
1413

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

-5
Original file line numberDiff line numberDiff line change
@@ -73,11 +73,6 @@ getFunBindId (AbsBinds _ _ _ abes _ _ _)
7373
getFunBindId _ = []
7474

7575

76-
getCurrentDefinitions :: MonadReader Context m => m [(OccName, CType)]
77-
getCurrentDefinitions = asks ctxDefiningFuncs
78-
79-
80-
8176
------------------------------------------------------------------------------
8277
-- | Determine if there is an instance that exists for the given 'Class' at the
8378
-- specified types. Deeply checks contexts to ensure the instance is actually

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

+1-2
Original file line numberDiff line numberDiff line change
@@ -4,10 +4,9 @@ import Control.Monad.Error.Class
44
import Data.Foldable (for_)
55
import OccName (mkVarOcc, mkClsOcc)
66
import Refinery.Tactic
7-
import Wingman.Context (getCurrentDefinitions)
87
import Wingman.Judgements (jGoal)
98
import Wingman.KnownStrategies.QuickCheck (deriveArbitrary)
10-
import Wingman.Machinery (tracing, getKnownInstance)
9+
import Wingman.Machinery (tracing, getKnownInstance, getCurrentDefinitions)
1110
import Wingman.Tactics
1211
import Wingman.Types
1312

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

+10-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
{-# LANGUAGE RecordWildCards #-}
1+
{-# LANGUAGE RecordWildCards #-}
2+
{-# LANGUAGE TupleSections #-}
23

34
module Wingman.Machinery where
45

@@ -21,6 +22,7 @@ import Data.Maybe (mapMaybe)
2122
import Data.Monoid (getSum)
2223
import Data.Ord (Down (..), comparing)
2324
import qualified Data.Set as S
25+
import Data.Traversable (for)
2426
import Development.IDE.Core.Compile (lookupName)
2527
import Development.IDE.GHC.Compat
2628
import GhcPlugins (GlobalRdrElt (gre_name), lookupOccEnv, varType)
@@ -403,3 +405,10 @@ getOccNameType occ = do
403405
Just (AnId v) -> pure $ varType v
404406
_ -> throwError $ NotInScope occ
405407

408+
409+
getCurrentDefinitions :: TacticsM [(OccName, CType)]
410+
getCurrentDefinitions = do
411+
ctx_funcs <- asks ctxDefiningFuncs
412+
for ctx_funcs $ \res@(occ, _) ->
413+
pure . maybe res (occ,) =<< lookupNameInContext occ
414+

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

+1-2
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,7 @@ import qualified Data.Text as T
1515
import qualified Refinery.Tactic as R
1616
import qualified Text.Megaparsec as P
1717
import Wingman.Auto
18-
import Wingman.Context (getCurrentDefinitions)
19-
import Wingman.Machinery (useNameFromHypothesis, getOccNameType, createImportedHyInfo, useNameFromContext, lookupNameInContext)
18+
import Wingman.Machinery (useNameFromHypothesis, getOccNameType, createImportedHyInfo, useNameFromContext, lookupNameInContext, getCurrentDefinitions)
2019
import Wingman.Metaprogramming.Lexer
2120
import Wingman.Metaprogramming.Parser.Documentation
2221
import Wingman.Metaprogramming.ProofState (proofState, layout)

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

-5
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,6 @@ import TcType
3737
import Type hiding (Var)
3838
import TysPrim (betaTy, alphaTy, betaTyVar, alphaTyVar)
3939
import Wingman.CodeGen
40-
import Wingman.Context
4140
import Wingman.GHC
4241
import Wingman.Judgements
4342
import Wingman.Machinery
@@ -85,10 +84,6 @@ use sat occ = do
8584
recursion :: TacticsM ()
8685
-- TODO(sandy): This tactic doesn't fire for the @AutoThetaFix@ golden test,
8786
-- presumably due to running afoul of 'requireConcreteHole'. Look into this!
88-
89-
-- TODO(sandy): There's a bug here! This should use the polymorphic defining
90-
-- types, not the ones available via 'getCurrentDefinitions'. As it is, this
91-
-- tactic doesn't support polymorphic recursion.
9287
recursion = requireConcreteHole $ tracing "recursion" $ do
9388
defs <- getCurrentDefinitions
9489
attemptOn (const defs) $ \(name, ty) -> markRecursion $ do

plugins/hls-tactics-plugin/test/CodeAction/AutoSpec.hs

+1
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ spec = do
4747
autoTest 2 17 "AutoInfixApply"
4848
autoTest 2 19 "AutoInfixApplyMany"
4949
autoTest 2 25 "AutoInfixInfix"
50+
autoTest 19 12 "AutoTypeLevel"
5051

5152
failing "flaky in CI" $
5253
autoTest 2 11 "GoldenApplicativeThen"
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE KindSignatures #-}
4+
{-# LANGUAGE TypeOperators #-}
5+
6+
import Data.Kind
7+
8+
data Nat = Z | S Nat
9+
10+
data HList (ls :: [Type]) where
11+
HNil :: HList '[]
12+
HCons :: t -> HList ts -> HList (t ': ts)
13+
14+
data ElemAt (n :: Nat) t (ts :: [Type]) where
15+
AtZ :: ElemAt 'Z t (t ': ts)
16+
AtS :: ElemAt k t ts -> ElemAt ('S k) t (u ': ts)
17+
18+
lookMeUp :: ElemAt i ty tys -> HList tys -> ty
19+
lookMeUp AtZ (HCons t _) = t
20+
lookMeUp (AtS ea') (HCons _ hl') = lookMeUp ea' hl'
21+
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE KindSignatures #-}
4+
{-# LANGUAGE TypeOperators #-}
5+
6+
import Data.Kind
7+
8+
data Nat = Z | S Nat
9+
10+
data HList (ls :: [Type]) where
11+
HNil :: HList '[]
12+
HCons :: t -> HList ts -> HList (t ': ts)
13+
14+
data ElemAt (n :: Nat) t (ts :: [Type]) where
15+
AtZ :: ElemAt 'Z t (t ': ts)
16+
AtS :: ElemAt k t ts -> ElemAt ('S k) t (u ': ts)
17+
18+
lookMeUp :: ElemAt i ty tys -> HList tys -> ty
19+
lookMeUp = _
20+

0 commit comments

Comments
 (0)