Skip to content

Commit 43b97cd

Browse files
committed
implement isovector#21 : splitting on datatypeOne code action per datatype constructor is produced.test cases for splittingdon't suggest constructors with hash by defaultsuggesting I# for Int probably is not what you want99% of the timealso reuse tyDataCons, tacnameuse 'algebraicTyCon' as filter for now
1 parent de4e387 commit 43b97cd

File tree

10 files changed

+102
-22
lines changed

10 files changed

+102
-22
lines changed

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

Lines changed: 30 additions & 17 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.
@@ -280,7 +294,7 @@ judgementForHole state nfp range = do
280294

281295

282296

283-
tacticCmd :: (OccName -> TacticsM ()) -> CommandFunction TacticParams
297+
tacticCmd :: (String -> TacticsM ()) -> CommandFunction TacticParams
284298
tacticCmd tac lf state (TacticParams uri range var_name)
285299
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri =
286300
fromMaybeT (Right Null, Nothing) $ do
@@ -289,19 +303,18 @@ tacticCmd tac lf state (TacticParams uri range var_name)
289303
pm <- MaybeT $ useAnnotatedSource "tacticsCmd" state nfp
290304
x <- lift $ timeout 2e8 $
291305
case runTactic ctx jdg
292-
$ tac
293-
$ mkVarOcc
294-
$ T.unpack var_name of
295-
Left err ->
296-
pure $ (, Nothing)
297-
$ Left
298-
$ ResponseError InvalidRequest (T.pack $ show err) Nothing
299-
Right (_, ext) -> do
300-
let g = graft (RealSrcSpan span) ext
301-
response = transform dflags (clientCapabilities lf) uri g pm
302-
pure $ case response of
303-
Right res -> (Right Null , Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams res))
304-
Left err -> (Left $ ResponseError InternalError (T.pack err) Nothing, Nothing)
306+
$ tac
307+
$ T.unpack var_name of
308+
Left err ->
309+
pure $ (, Nothing)
310+
$ Left
311+
$ ResponseError InvalidRequest (T.pack $ show err) Nothing
312+
Right (_, ext) -> do
313+
let g = graft (RealSrcSpan span) ext
314+
response = transform dflags (clientCapabilities lf) uri g pm
315+
pure $ case response of
316+
Right res -> (Right Null , Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams res))
317+
Left err -> (Left $ ResponseError InternalError (T.pack err) Nothing, Nothing)
305318
pure $ case x of
306319
Just y -> y
307320
Nothing -> (, Nothing)

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

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module Ide.Plugin.Tactic.GHC where
77
import Data.Maybe (isJust)
88
import Development.IDE.GHC.Compat
99
import OccName
10+
import DataCon
1011
import TcType
1112
import TyCoRep
1213
import Type
@@ -106,3 +107,10 @@ getPatName (fromPatCompat -> p0) =
106107
#endif
107108
_ -> Nothing
108109

110+
------------------------------------------------------------------------------
111+
-- | What data-constructor, if any, does the type have?
112+
tyDataCons :: Type -> Maybe [DataCon]
113+
tyDataCons g = do
114+
(tc, _) <- splitTyConApp_maybe g
115+
pure $ tyConDataCons tc
116+

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

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

203202

@@ -235,6 +234,22 @@ splitDataCon dc = tracing ("splitDataCon:" <> show dc) $ rule $ \jdg -> do
235234
Nothing -> throwError $ GoalMismatch "splitDataCon" g
236235

237236

237+
------------------------------------------------------------------------------
238+
-- | Attempt to instantiate the named data constructor to solve the goal.
239+
splitDataCon' :: OccName -> TacticsM ()
240+
splitDataCon' dcn = do
241+
let tacname = "splitDataCon'(" ++ unsafeRender dcn ++ ")"
242+
jdg <- goal
243+
let g = jGoal jdg
244+
case tyDataCons $ unCType g of
245+
Nothing -> throwError $ GoalMismatch tacname g
246+
Just dcs -> do
247+
let mdc = find ((== dcn) . getOccName) dcs
248+
case mdc of
249+
Nothing -> throwError $ GoalMismatch tacname g
250+
Just dc -> splitDataCon dc
251+
252+
238253
------------------------------------------------------------------------------
239254
-- | @matching f@ takes a function from a judgement to a @Tactic@, and
240255
-- 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"

stack.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ packages:
44
- .
55
- ./ghcide/
66
- ./hls-plugin-api
7+
- ./plugins/tactics
78

89
ghc-options:
910
"$everything": -haddock

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
@@ -101,6 +123,7 @@ tests = testGroup
101123
, goldenTest "GoldenGADTDestruct.hs" 7 17 Destruct "gadt"
102124
, goldenTest "GoldenGADTAuto.hs" 7 13 Auto ""
103125
, goldenTest "GoldenSwapMany.hs" 2 12 Auto ""
126+
, goldenTest "GoldenSplitPair.hs" 2 11 Split "(,)"
104127
]
105128

106129

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)