Skip to content

Commit 6e3682b

Browse files
committed
implement #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 6c14163 commit 6e3682b

File tree

9 files changed

+101
-23
lines changed

9 files changed

+101
-23
lines changed

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

Lines changed: 31 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ import Data.Functor ((<&>))
2626
import Data.Generics.Aliases (mkQ)
2727
import Data.Generics.Schemes (everything)
2828
import Data.List
29+
import qualified Data.Foldable as F
2930
import Data.Map (Map)
3031
import qualified Data.Map as M
3132
import Data.Maybe
@@ -103,6 +104,10 @@ commandProvider Auto = provide Auto ""
103104
commandProvider Intros =
104105
filterGoalType isFunction $
105106
provide Intros ""
107+
commandProvider Split =
108+
filterGoalType (isJust . algebraicTyCon) $
109+
foldMapGoalType (F.fold . tyDataCons) $ \dc ->
110+
provide Split $ T.pack $ occNameString $ getOccName dc
106111
commandProvider Destruct =
107112
filterBindingType destructFilter $ \occ _ ->
108113
provide Destruct $ T.pack $ occNameString occ
@@ -121,11 +126,12 @@ commandProvider HomomorphismLambdaCase =
121126

122127
------------------------------------------------------------------------------
123128
-- | A mapping from tactic commands to actual tactics for refinery.
124-
commandTactic :: TacticCommand -> OccName -> TacticsM ()
129+
commandTactic :: TacticCommand -> String -> TacticsM ()
125130
commandTactic Auto = const auto
126131
commandTactic Intros = const intros
127-
commandTactic Destruct = destruct
128-
commandTactic Homomorphism = homo
132+
commandTactic Split = splitDataCon' . mkDataOcc
133+
commandTactic Destruct = destruct . mkVarOcc
134+
commandTactic Homomorphism = homo . mkVarOcc
129135
commandTactic DestructLambdaCase = const destructLambdaCase
130136
commandTactic HomomorphismLambdaCase = const homoLambdaCase
131137

@@ -196,6 +202,14 @@ requireExtension ext tp dflags plId uri range jdg =
196202
False -> pure []
197203

198204

205+
------------------------------------------------------------------------------
206+
-- | Create a 'TacticProvider' for each occurance of an 'a' in the foldable container
207+
-- extracted from the goal type. Useful instantiations for 't' include 'Maybe' or '[]'.
208+
foldMapGoalType :: Foldable t => (Type -> t a) -> (a -> TacticProvider) -> TacticProvider
209+
foldMapGoalType f tpa dflags plId uri range jdg =
210+
foldMap tpa (f $ unCType $ jGoal jdg) dflags plId uri range jdg
211+
212+
199213
------------------------------------------------------------------------------
200214
-- | Restrict a 'TacticProvider', making sure it appears only when the given
201215
-- predicate holds for the goal.
@@ -289,7 +303,7 @@ spliceProvenance provs =
289303
overProvenance (maybe id const $ M.lookup name provs) hi
290304

291305

292-
tacticCmd :: (OccName -> TacticsM ()) -> CommandFunction TacticParams
306+
tacticCmd :: (String -> TacticsM ()) -> CommandFunction TacticParams
293307
tacticCmd tac lf state (TacticParams uri range var_name)
294308
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri =
295309
fromMaybeT (Right Null, Nothing) $ do
@@ -298,20 +312,19 @@ tacticCmd tac lf state (TacticParams uri range var_name)
298312
pm <- MaybeT $ useAnnotatedSource "tacticsCmd" state nfp
299313
x <- lift $ timeout 2e8 $
300314
case runTactic ctx jdg
301-
$ tac
302-
$ mkVarOcc
303-
$ T.unpack var_name of
304-
Left err ->
305-
pure $ (, Nothing)
306-
$ Left
307-
$ ResponseError InvalidRequest (T.pack $ show err) Nothing
308-
Right rtr -> do
309-
traceMX "solns" $ rtr_other_solns rtr
310-
let g = graft (RealSrcSpan span) $ rtr_extract rtr
311-
response = transform dflags (clientCapabilities lf) uri g pm
312-
pure $ case response of
313-
Right res -> (Right Null , Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams res))
314-
Left err -> (Left $ ResponseError InternalError (T.pack err) Nothing, Nothing)
315+
$ tac
316+
$ T.unpack var_name of
317+
Left err ->
318+
pure $ (, Nothing)
319+
$ Left
320+
$ ResponseError InvalidRequest (T.pack $ show err) Nothing
321+
Right rtr -> do
322+
traceMX "solns" $ rtr_other_solns rtr
323+
let g = graft (RealSrcSpan span) $ rtr_extract rtr
324+
response = transform dflags (clientCapabilities lf) uri g pm
325+
pure $ case response of
326+
Right res -> (Right Null , Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams res))
327+
Left err -> (Left $ ResponseError InternalError (T.pack err) Nothing, Nothing)
315328
pure $ case x of
316329
Just y -> y
317330
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
@@ -186,10 +186,9 @@ split :: TacticsM ()
186186
split = tracing "split(user)" $ do
187187
jdg <- goal
188188
let g = jGoal jdg
189-
case splitTyConApp_maybe $ unCType g of
190-
Nothing -> throwError $ GoalMismatch "split" g
191-
Just (tc, _) -> do
192-
let dcs = tyConDataCons tc
189+
case tyDataCons $ unCType g of
190+
Nothing -> throwError $ GoalMismatch "split(user)" g
191+
Just dcs -> do
193192
choice $ fmap splitDataCon dcs
194193

195194

@@ -238,6 +237,22 @@ splitDataCon dc =
238237
Nothing -> throwError $ GoalMismatch "splitDataCon" g
239238

240239

240+
------------------------------------------------------------------------------
241+
-- | Attempt to instantiate the named data constructor to solve the goal.
242+
splitDataCon' :: OccName -> TacticsM ()
243+
splitDataCon' dcn = do
244+
let tacname = "splitDataCon'(" ++ unsafeRender dcn ++ ")"
245+
jdg <- goal
246+
let g = jGoal jdg
247+
case tyDataCons $ unCType g of
248+
Nothing -> throwError $ GoalMismatch tacname g
249+
Just dcs -> do
250+
let mdc = find ((== dcn) . getOccName) dcs
251+
case mdc of
252+
Nothing -> throwError $ GoalMismatch tacname g
253+
Just dc -> splitDataCon dc
254+
255+
241256
------------------------------------------------------------------------------
242257
-- | @matching f@ takes a function from a judgement to a @Tactic@, and
243258
-- 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: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,27 @@ tests = testGroup
8585
"T3.hs" 7 13
8686
[ (id, DestructLambdaCase, "")
8787
]
88+
, ignoreTestBecause "Not implemented, see isovector/haskell-language-server#31" $ mkTest
89+
"Splits Int with I# when -XMagicHash is enabled"
90+
"T3.hs" 10 14
91+
[ (id, Split, "I#")
92+
]
93+
, mkTest
94+
"Produces datatype split action for single-constructor types"
95+
"T2.hs" 16 14
96+
[ (id, Split, "T")
97+
]
98+
, mkTest
99+
"Produces datatype split action for multiple constructors"
100+
"T2.hs" 21 15
101+
[ (id, Split, "T21")
102+
, (id, Split, "T22")
103+
]
104+
, mkTest
105+
"Doesn't suggest MagicHash constructors without -XMagicHash"
106+
"T2.hs" 24 14
107+
[ (not, Split, "I#")
108+
]
88109
, mkTest
89110
"Doesn't suggest lambdacase without -XLambdaCase"
90111
"T2.hs" 11 25
@@ -115,6 +136,7 @@ tests = testGroup
115136
$ goldenTest "GoldenApplicativeThen.hs" 2 11 Auto ""
116137
, goldenTest "GoldenSafeHead.hs" 2 12 Auto ""
117138
, expectFail "GoldenFish.hs" 5 18 Auto ""
139+
, goldenTest "GoldenSplitPair.hs" 2 11 Split "(,)"
118140
]
119141

120142

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)