Skip to content

Commit 18d4237

Browse files
committed
implement isovector#21 : splitting on datatype
One code action per datatype constructor is produced. test cases for splitting don't suggest constructors with hash by default suggesting I# for Int probably is not what you want 99% of the time also reuse tyDataCons, tacname use 'algebraicTyCon' as filter for now
1 parent 91d2711 commit 18d4237

File tree

9 files changed

+102
-23
lines changed

9 files changed

+102
-23
lines changed

plugins/tactics/src/Ide/Plugin/Tactic.hs

Lines changed: 31 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import Data.Coerce
2525
import Data.Generics.Aliases (mkQ)
2626
import Data.Generics.Schemes (everything)
2727
import Data.List
28+
import qualified Data.Foldable as F
2829
import qualified Data.Map as M
2930
import Data.Maybe
3031
import Data.Monoid
@@ -101,6 +102,10 @@ commandProvider Auto = provide Auto ""
101102
commandProvider Intros =
102103
filterGoalType isFunction $
103104
provide Intros ""
105+
commandProvider Split =
106+
filterGoalType (isJust . algebraicTyCon) $
107+
foldMapGoalType (F.fold . tyDataCons) $ \dc ->
108+
provide Split $ T.pack $ occNameString $ getOccName dc
104109
commandProvider Destruct =
105110
filterBindingType destructFilter $ \occ _ ->
106111
provide Destruct $ T.pack $ occNameString occ
@@ -119,11 +124,12 @@ commandProvider HomomorphismLambdaCase =
119124

120125
------------------------------------------------------------------------------
121126
-- | A mapping from tactic commands to actual tactics for refinery.
122-
commandTactic :: TacticCommand -> OccName -> TacticsM ()
127+
commandTactic :: TacticCommand -> String -> TacticsM ()
123128
commandTactic Auto = const auto
124129
commandTactic Intros = const intros
125-
commandTactic Destruct = destruct
126-
commandTactic Homomorphism = homo
130+
commandTactic Split = splitDataCon' . mkDataOcc
131+
commandTactic Destruct = destruct . mkVarOcc
132+
commandTactic Homomorphism = homo . mkVarOcc
127133
commandTactic DestructLambdaCase = const destructLambdaCase
128134
commandTactic HomomorphismLambdaCase = const homoLambdaCase
129135

@@ -194,6 +200,14 @@ requireExtension ext tp dflags plId uri range jdg =
194200
False -> pure []
195201

196202

203+
------------------------------------------------------------------------------
204+
-- | Create a 'TacticProvider' for each occurance of an 'a' in the foldable container
205+
-- extracted from the goal type. Useful instantiations for 't' include 'Maybe' or '[]'.
206+
foldMapGoalType :: Foldable t => (Type -> t a) -> (a -> TacticProvider) -> TacticProvider
207+
foldMapGoalType f tpa dflags plId uri range jdg =
208+
foldMap tpa (f $ unCType $ jGoal jdg) dflags plId uri range jdg
209+
210+
197211
------------------------------------------------------------------------------
198212
-- | Restrict a 'TacticProvider', making sure it appears only when the given
199213
-- predicate holds for the goal.
@@ -282,7 +296,7 @@ judgementForHole state nfp range = do
282296

283297

284298

285-
tacticCmd :: (OccName -> TacticsM ()) -> CommandFunction TacticParams
299+
tacticCmd :: (String -> TacticsM ()) -> CommandFunction TacticParams
286300
tacticCmd tac lf state (TacticParams uri range var_name)
287301
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri =
288302
fromMaybeT (Right Null, Nothing) $ do
@@ -291,20 +305,19 @@ tacticCmd tac lf state (TacticParams uri range var_name)
291305
pm <- MaybeT $ useAnnotatedSource "tacticsCmd" state nfp
292306
x <- lift $ timeout 2e8 $
293307
case runTactic ctx jdg
294-
$ tac
295-
$ mkVarOcc
296-
$ T.unpack var_name of
297-
Left err ->
298-
pure $ (, Nothing)
299-
$ Left
300-
$ ResponseError InvalidRequest (T.pack $ show err) Nothing
301-
Right rtr -> do
302-
traceMX "solns" $ rtr_other_solns rtr
303-
let g = graft (RealSrcSpan span) $ rtr_extract rtr
304-
response = transform dflags (clientCapabilities lf) uri g pm
305-
pure $ case response of
306-
Right res -> (Right Null , Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams res))
307-
Left err -> (Left $ ResponseError InternalError (T.pack err) Nothing, Nothing)
308+
$ tac
309+
$ T.unpack var_name of
310+
Left err ->
311+
pure $ (, Nothing)
312+
$ Left
313+
$ ResponseError InvalidRequest (T.pack $ show err) Nothing
314+
Right rtr -> do
315+
traceMX "solns" $ rtr_other_solns rtr
316+
let g = graft (RealSrcSpan span) $ rtr_extract rtr
317+
response = transform dflags (clientCapabilities lf) uri g pm
318+
pure $ case response of
319+
Right res -> (Right Null , Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams res))
320+
Left err -> (Left $ ResponseError InternalError (T.pack err) Nothing, Nothing)
308321
pure $ case x of
309322
Just y -> y
310323
Nothing -> (, Nothing)

plugins/tactics/src/Ide/Plugin/Tactic/GHC.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
module Ide.Plugin.Tactic.GHC where
77

88
import Control.Monad.State
9+
import DataCon
910
import qualified Data.Map as M
1011
import Data.Maybe (isJust)
1112
import Data.Traversable
@@ -148,3 +149,10 @@ getPatName (fromPatCompat -> p0) =
148149
#endif
149150
_ -> Nothing
150151

152+
------------------------------------------------------------------------------
153+
-- | What data-constructor, if any, does the type have?
154+
tyDataCons :: Type -> Maybe [DataCon]
155+
tyDataCons g = do
156+
(tc, _) <- splitTyConApp_maybe g
157+
pure $ tyConDataCons tc
158+

plugins/tactics/src/Ide/Plugin/Tactic/Tactics.hs

Lines changed: 19 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -193,10 +193,9 @@ split :: TacticsM ()
193193
split = tracing "split(user)" $ do
194194
jdg <- goal
195195
let g = jGoal jdg
196-
case splitTyConApp_maybe $ unCType g of
197-
Nothing -> throwError $ GoalMismatch "split" g
198-
Just (tc, _) -> do
199-
let dcs = tyConDataCons tc
196+
case tyDataCons $ unCType g of
197+
Nothing -> throwError $ GoalMismatch "split(user)" g
198+
Just dcs -> do
200199
choice $ fmap splitDataCon dcs
201200

202201

@@ -245,6 +244,22 @@ splitDataCon dc =
245244
Nothing -> throwError $ GoalMismatch "splitDataCon" g
246245

247246

247+
------------------------------------------------------------------------------
248+
-- | Attempt to instantiate the named data constructor to solve the goal.
249+
splitDataCon' :: OccName -> TacticsM ()
250+
splitDataCon' dcn = do
251+
let tacname = "splitDataCon'(" ++ unsafeRender dcn ++ ")"
252+
jdg <- goal
253+
let g = jGoal jdg
254+
case tyDataCons $ unCType g of
255+
Nothing -> throwError $ GoalMismatch tacname g
256+
Just dcs -> do
257+
let mdc = find ((== dcn) . getOccName) dcs
258+
case mdc of
259+
Nothing -> throwError $ GoalMismatch tacname g
260+
Just dc -> splitDataCon dc
261+
262+
248263
------------------------------------------------------------------------------
249264
-- | @matching f@ takes a function from a judgement to a @Tactic@, and
250265
-- then applies the resulting @Tactic@.

plugins/tactics/src/Ide/Plugin/Tactic/TestTypes.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ import qualified Data.Text as T
1111
data TacticCommand
1212
= Auto
1313
| Intros
14+
| Split
1415
| Destruct
1516
| Homomorphism
1617
| DestructLambdaCase
@@ -21,6 +22,7 @@ data TacticCommand
2122
tacticTitle :: TacticCommand -> T.Text -> T.Text
2223
tacticTitle Auto _ = "Attempt to fill hole"
2324
tacticTitle Intros _ = "Introduce lambda"
25+
tacticTitle Split cname = "Introduce constructor " <> cname
2426
tacticTitle Destruct var = "Case split on " <> var
2527
tacticTitle Homomorphism var = "Homomorphic case split on " <> var
2628
tacticTitle DestructLambdaCase _ = "Lambda case split"

test/functional/Tactic.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ import Language.Haskell.LSP.Types (ApplyWorkspaceEditRequest, Position
2121
import Test.Hls.Util
2222
import Test.Tasty
2323
import Test.Tasty.HUnit
24+
import Test.Tasty.ExpectedFailure (ignoreTestBecause)
2425
import System.FilePath
2526
import System.Directory (doesFileExist)
2627
import Control.Monad (unless)
@@ -80,6 +81,27 @@ tests = testGroup
8081
"T3.hs" 7 13
8182
[ (id, DestructLambdaCase, "")
8283
]
84+
, ignoreTestBecause "Not implemented, see isovector/haskell-language-server#31" $ mkTest
85+
"Splits Int with I# when -XMagicHash is enabled"
86+
"T3.hs" 10 14
87+
[ (id, Split, "I#")
88+
]
89+
, mkTest
90+
"Produces datatype split action for single-constructor types"
91+
"T2.hs" 16 14
92+
[ (id, Split, "T")
93+
]
94+
, mkTest
95+
"Produces datatype split action for multiple constructors"
96+
"T2.hs" 21 15
97+
[ (id, Split, "T21")
98+
, (id, Split, "T22")
99+
]
100+
, mkTest
101+
"Doesn't suggest MagicHash constructors without -XMagicHash"
102+
"T2.hs" 24 14
103+
[ (not, Split, "I#")
104+
]
83105
, mkTest
84106
"Doesn't suggest lambdacase without -XLambdaCase"
85107
"T2.hs" 11 25
@@ -107,6 +129,7 @@ tests = testGroup
107129
, goldenTest "GoldenShowMapChar.hs" 2 8 Auto ""
108130
, goldenTest "GoldenSuperclass.hs" 7 8 Auto ""
109131
, goldenTest "GoldenApplicativeThen.hs" 2 11 Auto ""
132+
, goldenTest "GoldenSplitPair.hs" 2 11 Split "(,)"
110133
]
111134

112135

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
thePair :: (Int, Int)
2+
thePair = _
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
thePair :: (Int, Int)
2+
thePair = (_, _)

test/testdata/tactic/T2.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,3 +10,15 @@ foo = _
1010
dontSuggestLambdaCase :: Either a b -> Int
1111
dontSuggestLambdaCase = _
1212

13+
data T = T !(Int, Int)
14+
15+
suggestCon :: T
16+
suggestCon = _
17+
18+
data T2 = T21 Int | T22 Int Int
19+
20+
suggestCons :: T2
21+
suggestCons = _
22+
23+
suggestInt :: Int
24+
suggestInt = _

test/testdata/tactic/T3.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,10 @@
1-
{-# LANGUAGE LambdaCase #-}
1+
{-# LANGUAGE LambdaCase, MagicHash #-}
22

33
suggestHomomorphicLC :: Either a b -> Either a b
44
suggestHomomorphicLC = _
55

66
suggestLC :: Either a b -> Int
77
suggestLC = _
88

9+
suggestInt :: Int
10+
suggestInt = _

0 commit comments

Comments
 (0)