Skip to content

Commit b3f7ec8

Browse files
authored
Discover skolems in the hypothesis, not just goal (#542)
The tactics plugin was only discovering skolem types present in the hole, rather than anywhere in the hypothesis. #541 gives the following repro: ```haskell foo :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) foo f g a = _ ``` here, the hole has type `_ :: m c`, which means tactics doesn't realize `a` and `b` are skolems, and instead treats them as unifiable variables. Thus the insane solution of `f a`. Fixes #541
1 parent e8871ab commit b3f7ec8

File tree

5 files changed

+71
-17
lines changed

5 files changed

+71
-17
lines changed

Diff for: plugins/tactics/src/Ide/Plugin/Tactic/Auto.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -1,22 +1,25 @@
11
module Ide.Plugin.Tactic.Auto where
22

3+
import Control.Monad.State (gets)
34
import Ide.Plugin.Tactic.Context
45
import Ide.Plugin.Tactic.Judgements
56
import Ide.Plugin.Tactic.KnownStrategies
7+
import Ide.Plugin.Tactic.Machinery (tracing)
68
import Ide.Plugin.Tactic.Tactics
79
import Ide.Plugin.Tactic.Types
810
import Refinery.Tactic
9-
import Ide.Plugin.Tactic.Machinery (tracing)
1011

1112

1213
------------------------------------------------------------------------------
1314
-- | Automatically solve a goal.
1415
auto :: TacticsM ()
1516
auto = do
1617
jdg <- goal
18+
skolems <- gets ts_skolems
1719
current <- getCurrentDefinitions
1820
traceMX "goal" jdg
1921
traceMX "ctx" current
22+
traceMX "skolems" skolems
2023
commit knownStrategies
2124
. tracing "auto"
2225
. localTactic (auto' 4)

Diff for: plugins/tactics/src/Ide/Plugin/Tactic/Context.hs

+31-14
Original file line numberDiff line numberDiff line change
@@ -3,19 +3,21 @@
33

44
module Ide.Plugin.Tactic.Context where
55

6-
import Bag
7-
import Control.Arrow
8-
import Control.Monad.Reader
9-
import Development.IDE.GHC.Compat
10-
import Ide.Plugin.Tactic.Types
11-
import OccName
12-
import TcRnTypes
13-
import Ide.Plugin.Tactic.GHC (tacticsThetaTy)
14-
import Ide.Plugin.Tactic.Machinery (methodHypothesis)
15-
import Data.Maybe (mapMaybe)
16-
import Data.List
17-
import TcType (substTy, tcSplitSigmaTy)
18-
import Unify (tcUnifyTy)
6+
import Bag
7+
import Control.Arrow
8+
import Control.Monad.Reader
9+
import Data.List
10+
import Data.Maybe (mapMaybe)
11+
import Data.Set (Set)
12+
import qualified Data.Set as S
13+
import Development.IDE.GHC.Compat
14+
import Ide.Plugin.Tactic.GHC (tacticsThetaTy)
15+
import Ide.Plugin.Tactic.Machinery (methodHypothesis)
16+
import Ide.Plugin.Tactic.Types
17+
import OccName
18+
import TcRnTypes
19+
import TcType (substTy, tcSplitSigmaTy)
20+
import Unify (tcUnifyTy)
1921

2022

2123
mkContext :: [(OccName, CType)] -> TcGblEnv -> Context
@@ -33,7 +35,8 @@ mkContext locals tcg = Context
3335
-- | Find all of the class methods that exist from the givens in the context.
3436
contextMethodHypothesis :: Context -> [(OccName, CType)]
3537
contextMethodHypothesis ctx
36-
= join
38+
= excludeForbiddenMethods
39+
. join
3740
. concatMap
3841
( mapMaybe methodHypothesis
3942
. tacticsThetaTy
@@ -44,6 +47,20 @@ contextMethodHypothesis ctx
4447
$ ctxDefiningFuncs ctx
4548

4649

50+
------------------------------------------------------------------------------
51+
-- | Many operations are defined in typeclasses for performance reasons, rather
52+
-- than being a true part of the class. This function filters out those, in
53+
-- order to keep our hypothesis space small.
54+
excludeForbiddenMethods :: [(OccName, CType)] -> [(OccName, CType)]
55+
excludeForbiddenMethods = filter (not . flip S.member forbiddenMethods . fst)
56+
where
57+
forbiddenMethods :: Set OccName
58+
forbiddenMethods = S.map mkVarOcc $ S.fromList
59+
[ -- monadfail
60+
"fail"
61+
]
62+
63+
4764
------------------------------------------------------------------------------
4865
-- | Given the name of a function that exists in 'ctxDefiningFuncs', get its
4966
-- theta type.

Diff for: plugins/tactics/src/Ide/Plugin/Tactic/Machinery.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,10 @@ runTactic
7171
-> TacticsM () -- ^ Tactic to use
7272
-> Either [TacticError] RunTacticResults
7373
runTactic ctx jdg t =
74-
let skolems = tyCoVarsOfTypeWellScoped $ unCType $ jGoal jdg
74+
let skolems = nub
75+
$ foldMap (tyCoVarsOfTypeWellScoped . unCType)
76+
$ jGoal jdg
77+
: (toList $ jHypothesis jdg)
7578
unused_topvals = nub $ join $ join $ toList $ _jPositionMaps jdg
7679
tacticState =
7780
defaultTacticState

Diff for: test/functional/Tactic.hs

+27-1
Original file line numberDiff line numberDiff line change
@@ -9,16 +9,20 @@ module Tactic
99
where
1010

1111
import Control.Applicative.Combinators ( skipManyTill )
12+
import Control.Lens hiding ((<.>))
1213
import Control.Monad (unless)
1314
import Control.Monad.IO.Class
15+
import Data.Aeson
16+
import Data.Either (isLeft)
1417
import Data.Foldable
1518
import Data.Maybe
1619
import Data.Text (Text)
1720
import qualified Data.Text as T
1821
import qualified Data.Text.IO as T
1922
import Ide.Plugin.Tactic.TestTypes
2023
import Language.Haskell.LSP.Test
21-
import Language.Haskell.LSP.Types (ApplyWorkspaceEditRequest, Position(..) , Range(..) , CAResult(..) , CodeAction(..))
24+
import Language.Haskell.LSP.Types (ExecuteCommandParams(ExecuteCommandParams), ClientMethod (..), Command, ExecuteCommandResponse, ResponseMessage (..), ApplyWorkspaceEditRequest, Position(..) , Range(..) , CAResult(..) , CodeAction(..))
25+
import Language.Haskell.LSP.Types.Lens hiding (id, capabilities, message, executeCommand, applyEdit, rename)
2226
import System.Directory (doesFileExist)
2327
import System.FilePath
2428
import Test.Hls.Util
@@ -110,6 +114,7 @@ tests = testGroup
110114
, ignoreTestBecause "It is unreliable in circleci builds"
111115
$ goldenTest "GoldenApplicativeThen.hs" 2 11 Auto ""
112116
, goldenTest "GoldenSafeHead.hs" 2 12 Auto ""
117+
, expectFail "GoldenFish.hs" 5 18 Auto ""
113118
]
114119

115120

@@ -160,6 +165,27 @@ goldenTest input line col tc occ =
160165
liftIO $ edited @?= expected
161166

162167

168+
expectFail :: FilePath -> Int -> Int -> TacticCommand -> Text -> TestTree
169+
expectFail input line col tc occ =
170+
testCase (input <> " (golden)") $ do
171+
runSession hlsCommand fullCaps tacticPath $ do
172+
doc <- openDoc input "haskell"
173+
_ <- waitForDiagnostics
174+
actions <- getCodeActions doc $ pointRange line col
175+
Just (CACodeAction (CodeAction {_command = Just c}))
176+
<- pure $ find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions
177+
resp <- executeCommandWithResp c
178+
liftIO $ unless (isLeft $ _result resp) $
179+
assertFailure "didn't fail, but expected one"
180+
181+
163182
tacticPath :: FilePath
164183
tacticPath = "test/testdata/tactic"
165184

185+
186+
executeCommandWithResp :: Command -> Session ExecuteCommandResponse
187+
executeCommandWithResp cmd = do
188+
let args = decode $ encode $ fromJust $ cmd ^. arguments
189+
execParams = ExecuteCommandParams (cmd ^. command) args Nothing
190+
request WorkspaceExecuteCommand execParams
191+

Diff for: test/testdata/tactic/GoldenFish.hs

+5
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
-- There was an old bug where we would only pull skolems from the hole, rather
2+
-- than the entire hypothesis. Because of this, the 'b' here would be
3+
-- considered a univar, which could then be unified with the skolem 'c'.
4+
fish :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
5+
fish amb bmc a = _

0 commit comments

Comments
 (0)