Skip to content

Commit 18a8996

Browse files
authored
Wingman: Fix TODO(sandy) when performing subsequent actions (#2580)
* Add subsequent tactic test * Fix nfp tracking * Remove unrelated changes
1 parent 4386396 commit 18a8996

File tree

8 files changed

+80
-58
lines changed

8 files changed

+80
-58
lines changed

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

+18-22
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,8 @@ runContinuation plId cont state (fc, b) = do
9393
, _xdata = Nothing
9494
} ) $ do
9595
env@LspEnv{..} <- buildEnv state plId fc
96-
let stale a = runStaleIde "runContinuation" state (fc_nfp le_fileContext) a
96+
nfp <- getNfp $ fc_uri le_fileContext
97+
let stale a = runStaleIde "runContinuation" state nfp a
9798
args <- fetchTargetArgs @a env
9899
res <- c_runCommand cont env args fc b
99100

@@ -151,7 +152,8 @@ buildEnv
151152
-> MaybeT (LspM Plugin.Config) LspEnv
152153
buildEnv state plId fc = do
153154
cfg <- lift $ getTacticConfig plId
154-
dflags <- mapMaybeT liftIO $ getIdeDynflags state $ fc_nfp fc
155+
nfp <- getNfp $ fc_uri fc
156+
dflags <- mapMaybeT liftIO $ getIdeDynflags state nfp
155157
pure $ LspEnv
156158
{ le_ideState = state
157159
, le_pluginId = plId
@@ -173,22 +175,19 @@ codeActionProvider
173175
)
174176
-> PluginMethodHandler IdeState TextDocumentCodeAction
175177
codeActionProvider sort k state plId
176-
(CodeActionParams _ _ (TextDocumentIdentifier uri) range _)
177-
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
178-
fromMaybeT (Right $ List []) $ do
179-
let fc = FileContext
180-
{ fc_uri = uri
181-
, fc_nfp = nfp
182-
, fc_range = Just $ unsafeMkCurrent range
183-
}
184-
env <- buildEnv state plId fc
185-
args <- fetchTargetArgs @target env
186-
actions <- k env args
187-
pure
188-
$ Right
189-
$ List
190-
$ fmap (InR . uncurry (makeCodeAction plId fc sort)) actions
191-
codeActionProvider _ _ _ _ _ = pure $ Right $ List []
178+
(CodeActionParams _ _ (TextDocumentIdentifier uri) range _) = do
179+
fromMaybeT (Right $ List []) $ do
180+
let fc = FileContext
181+
{ fc_uri = uri
182+
, fc_range = Just $ unsafeMkCurrent range
183+
}
184+
env <- buildEnv state plId fc
185+
args <- fetchTargetArgs @target env
186+
actions <- k env args
187+
pure
188+
$ Right
189+
$ List
190+
$ fmap (InR . uncurry (makeCodeAction plId fc sort)) actions
192191

193192

194193
------------------------------------------------------------------------------
@@ -203,12 +202,10 @@ codeLensProvider
203202
)
204203
-> PluginMethodHandler IdeState TextDocumentCodeLens
205204
codeLensProvider sort k state plId
206-
(CodeLensParams _ _ (TextDocumentIdentifier uri))
207-
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
205+
(CodeLensParams _ _ (TextDocumentIdentifier uri)) = do
208206
fromMaybeT (Right $ List []) $ do
209207
let fc = FileContext
210208
{ fc_uri = uri
211-
, fc_nfp = nfp
212209
, fc_range = Nothing
213210
}
214211
env <- buildEnv state plId fc
@@ -218,7 +215,6 @@ codeLensProvider sort k state plId
218215
$ Right
219216
$ List
220217
$ fmap (uncurry3 $ makeCodeLens plId sort fc) actions
221-
codeLensProvider _ _ _ _ _ = pure $ Right $ List []
222218

223219

224220
------------------------------------------------------------------------------

plugins/hls-tactics-plugin/src/Wingman/AbstractLSP/TacticActions.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -45,9 +45,10 @@ makeTacticInteraction cmd =
4545
}
4646
)
4747
$ \LspEnv{..} HoleJudgment{..} FileContext{..} var_name -> do
48-
let stale a = runStaleIde "tacticCmd" le_ideState fc_nfp a
48+
nfp <- getNfp fc_uri
49+
let stale a = runStaleIde "tacticCmd" le_ideState nfp a
4950

50-
let span = fmap (rangeToRealSrcSpan (fromNormalizedFilePath fc_nfp)) hj_range
51+
let span = fmap (rangeToRealSrcSpan (fromNormalizedFilePath nfp)) hj_range
5152
TrackedStale _ pmmap <- mapMaybeT liftIO $ stale GetAnnotatedParsedSource
5253
pm_span <- liftMaybe $ mapAgeFrom pmmap span
5354
IdeOptions{optTesting = IdeTesting isTesting} <-

plugins/hls-tactics-plugin/src/Wingman/AbstractLSP/Types.hs

+5-7
Original file line numberDiff line numberDiff line change
@@ -121,19 +121,13 @@ data Continuation sort target payload = Continuation
121121
-- | What file are we looking at, and what bit of it?
122122
data FileContext = FileContext
123123
{ fc_uri :: Uri
124-
, fc_nfp :: NormalizedFilePath
125124
, fc_range :: Maybe (Tracked 'Current Range)
126125
-- ^ For code actions, this is 'Just'. For code lenses, you'll get
127126
-- a 'Nothing' in the request, and a 'Just' in the response.
128127
}
129128
deriving stock (Eq, Ord, Show, Generic)
130129
deriving anyclass (A.ToJSON, A.FromJSON)
131130

132-
deriving anyclass instance A.ToJSON NormalizedFilePath
133-
deriving anyclass instance A.ToJSON NormalizedUri
134-
deriving anyclass instance A.FromJSON NormalizedFilePath
135-
deriving anyclass instance A.FromJSON NormalizedUri
136-
137131

138132
------------------------------------------------------------------------------
139133
-- | Everything we need to resolve continuations.
@@ -162,10 +156,14 @@ class IsTarget t where
162156
data HoleTarget = HoleTarget
163157
deriving stock (Eq, Ord, Show, Enum, Bounded)
164158

159+
getNfp :: Applicative m => Uri -> MaybeT m NormalizedFilePath
160+
getNfp = MaybeT . pure . uriToNormalizedFilePath . toNormalizedUri
161+
165162
instance IsTarget HoleTarget where
166163
type TargetArgs HoleTarget = HoleJudgment
167164
fetchTargetArgs LspEnv{..} = do
168165
let FileContext{..} = le_fileContext
169166
range <- MaybeT $ pure fc_range
170-
mapMaybeT liftIO $ judgementForHole le_ideState fc_nfp range le_config
167+
nfp <- getNfp fc_uri
168+
mapMaybeT liftIO $ judgementForHole le_ideState nfp range le_config
171169

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

+3-2
Original file line numberDiff line numberDiff line change
@@ -50,13 +50,14 @@ emptyCaseInteraction = Interaction $
5050
Continuation @EmptyCaseT @EmptyCaseT @WorkspaceEdit EmptyCaseT
5151
(SynthesizeCodeLens $ \LspEnv{..} _ -> do
5252
let FileContext{..} = le_fileContext
53+
nfp <- getNfp fc_uri
5354

54-
let stale a = runStaleIde "codeLensProvider" le_ideState fc_nfp a
55+
let stale a = runStaleIde "codeLensProvider" le_ideState nfp a
5556

5657
ccs <- lift getClientCapabilities
5758
TrackedStale pm _ <- mapMaybeT liftIO $ stale GetAnnotatedParsedSource
5859
TrackedStale binds bind_map <- mapMaybeT liftIO $ stale GetBindings
59-
holes <- mapMaybeT liftIO $ emptyCaseScrutinees le_ideState fc_nfp
60+
holes <- mapMaybeT liftIO $ emptyCaseScrutinees le_ideState nfp
6061

6162
for holes $ \(ss, ty) -> do
6263
binds_ss <- liftMaybe $ mapAgeFrom bind_map ss

plugins/hls-tactics-plugin/test/ProviderSpec.hs

+6
Original file line numberDiff line numberDiff line change
@@ -20,3 +20,9 @@ spec = do
2020
"T2" 8 8
2121
[ (not, Intros, "")
2222
]
23+
24+
goldenTestMany "SubsequentTactics"
25+
[ InvokeTactic Intros "" 4 5
26+
, InvokeTactic Destruct "du" 4 8
27+
, InvokeTactic Auto "" 4 15
28+
]

plugins/hls-tactics-plugin/test/Utils.hs

+35-25
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
{-# LANGUAGE ScopedTypeVariables #-}
55
{-# LANGUAGE TypeOperators #-}
66
{-# LANGUAGE ViewPatterns #-}
7+
{-# LANGUAGE RecordWildCards #-}
78

89
module Utils where
910

@@ -96,39 +97,45 @@ mkTest name fp line col ts = it name $ do
9697
liftIO $
9798
(title `elem` titles) `shouldSatisfy` f
9899

100+
data InvokeTactic = InvokeTactic
101+
{ it_command :: TacticCommand
102+
, it_argument :: Text
103+
, it_line :: Int
104+
, it_col :: Int
105+
}
106+
107+
invokeTactic :: TextDocumentIdentifier -> InvokeTactic -> Session ()
108+
invokeTactic doc InvokeTactic{..} = do
109+
-- wait for the entire build to finish, so that Tactics code actions that
110+
-- use stale data will get uptodate stuff
111+
void waitForDiagnostics
112+
void $ waitForTypecheck doc
113+
actions <- getCodeActions doc $ pointRange it_line it_col
114+
case find ((== Just (tacticTitle it_command it_argument)) . codeActionTitle) actions of
115+
Just (InR CodeAction {_command = Just c}) -> do
116+
executeCommand c
117+
void $ skipManyTill anyMessage $ message SWorkspaceApplyEdit
118+
_ -> error $ show actions
99119

100120

101121
mkGoldenTest
102122
:: (Text -> Text -> Assertion)
103-
-> TacticCommand
104-
-> Text
105-
-> Int
106-
-> Int
123+
-> [InvokeTactic]
107124
-> FilePath
108125
-> SpecWith ()
109-
mkGoldenTest eq tc occ line col input =
126+
mkGoldenTest eq invocations input =
110127
it (input <> " (golden)") $ do
111128
resetGlobalHoleRef
112129
runSessionForTactics $ do
113130
doc <- openDoc (input <.> "hs") "haskell"
114-
-- wait for diagnostics to start coming
115-
void waitForDiagnostics
116-
-- wait for the entire build to finish, so that Tactics code actions that
117-
-- use stale data will get uptodate stuff
118-
void $ waitForTypecheck doc
119-
actions <- getCodeActions doc $ pointRange line col
120-
case find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions of
121-
Just (InR CodeAction {_command = Just c}) -> do
122-
executeCommand c
123-
_resp <- skipManyTill anyMessage (message SWorkspaceApplyEdit)
124-
edited <- documentContents doc
125-
let expected_name = input <.> "expected" <.> "hs"
126-
-- Write golden tests if they don't already exist
127-
liftIO $ (doesFileExist expected_name >>=) $ flip unless $ do
128-
T.writeFile expected_name edited
129-
expected <- liftIO $ T.readFile expected_name
130-
liftIO $ edited `eq` expected
131-
_ -> error $ show actions
131+
traverse_ (invokeTactic doc) invocations
132+
edited <- documentContents doc
133+
let expected_name = input <.> "expected" <.> "hs"
134+
-- Write golden tests if they don't already exist
135+
liftIO $ (doesFileExist expected_name >>=) $ flip unless $ do
136+
T.writeFile expected_name edited
137+
expected <- liftIO $ T.readFile expected_name
138+
liftIO $ edited `eq` expected
132139

133140
mkCodeLensTest
134141
:: FilePath
@@ -197,10 +204,13 @@ mkShowMessageTest tc occ line col input ufm =
197204

198205

199206
goldenTest :: TacticCommand -> Text -> Int -> Int -> FilePath -> SpecWith ()
200-
goldenTest = mkGoldenTest shouldBe
207+
goldenTest tc occ line col = mkGoldenTest shouldBe [InvokeTactic tc occ line col]
208+
209+
goldenTestMany :: FilePath -> [InvokeTactic] -> SpecWith ()
210+
goldenTestMany = flip $ mkGoldenTest shouldBe
201211

202212
goldenTestNoWhitespace :: TacticCommand -> Text -> Int -> Int -> FilePath -> SpecWith ()
203-
goldenTestNoWhitespace = mkGoldenTest shouldBeIgnoringSpaces
213+
goldenTestNoWhitespace tc occ line col = mkGoldenTest shouldBeIgnoringSpaces [InvokeTactic tc occ line col]
204214

205215

206216
shouldBeIgnoringSpaces :: Text -> Text -> Assertion
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
data Dummy a = Dummy a
2+
3+
f :: Dummy Int -> Int
4+
f (Dummy n) = n
5+
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
data Dummy a = Dummy a
2+
3+
f :: Dummy Int -> Int
4+
f = _
5+

0 commit comments

Comments
 (0)