Skip to content

Commit 7dcd1c3

Browse files
Add heralds to Wingman's use of runAction (#1740)
Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 2683a92 commit 7dcd1c3

File tree

3 files changed

+36
-19
lines changed

3 files changed

+36
-19
lines changed

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

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
{-# LANGUAGE OverloadedStrings #-}
22

3+
{-# LANGUAGE NoMonoLocalBinds #-}
4+
35
module Wingman.EmptyCase where
46

57
import Control.Applicative (empty)
@@ -56,14 +58,16 @@ workspaceEditHandler _ideState wedit = do
5658
codeLensProvider :: PluginMethodHandler IdeState TextDocumentCodeLens
5759
codeLensProvider state plId (CodeLensParams _ _ (TextDocumentIdentifier uri))
5860
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
61+
let stale a = runStaleIde "codeLensProvider" state nfp a
62+
5963
cfg <- getTacticConfig plId
6064
ccs <- getClientCapabilities
6165
liftIO $ fromMaybeT (Right $ List []) $ do
6266
guard $ hasFeature FeatureEmptyCase $ cfg_feature_set cfg
6367

6468
dflags <- getIdeDynflags state nfp
65-
TrackedStale pm _ <- runStaleIde state nfp GetAnnotatedParsedSource
66-
TrackedStale binds bind_map <- runStaleIde state nfp GetBindings
69+
TrackedStale pm _ <- stale GetAnnotatedParsedSource
70+
TrackedStale binds bind_map <- stale GetBindings
6771
holes <- emptyCaseScrutinees state nfp
6872

6973
fmap (Right . List) $ for holes $ \(ss, ty) -> do
@@ -134,9 +138,11 @@ emptyCaseScrutinees
134138
-> NormalizedFilePath
135139
-> MaybeT IO [(Tracked 'Current RealSrcSpan, Type)]
136140
emptyCaseScrutinees state nfp = do
137-
TrackedStale tcg tcg_map <- fmap (fmap tmrTypechecked) $ runStaleIde state nfp TypeCheck
141+
let stale a = runStaleIde "emptyCaseScrutinees" state nfp a
142+
143+
TrackedStale tcg tcg_map <- fmap (fmap tmrTypechecked) $ stale TypeCheck
138144
let tcg' = unTrack tcg
139-
hscenv <- runStaleIde state nfp GhcSessionDeps
145+
hscenv <- stale GhcSessionDeps
140146

141147
let scrutinees = traverse (emptyCaseQ . tcg_binds) tcg
142148
for scrutinees $ \aged@(unTrack -> (ss, scrutinee)) -> do

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

Lines changed: 23 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
{-# LANGUAGE RankNTypes #-}
44
{-# LANGUAGE TypeFamilies #-}
55

6+
{-# LANGUAGE NoMonoLocalBinds #-}
7+
68
module Wingman.LanguageServer where
79

810
import ConLike
@@ -72,8 +74,8 @@ tcCommandName :: TacticCommand -> T.Text
7274
tcCommandName = T.pack . show
7375

7476

75-
runIde :: IdeState -> Action a -> IO a
76-
runIde state = runAction "tactic" state
77+
runIde :: String -> String -> IdeState -> Action a -> IO a
78+
runIde herald action state = runAction ("Wingman." <> herald <> "." <> action) state
7779

7880

7981
runCurrentIde
@@ -82,11 +84,13 @@ runCurrentIde
8284
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
8385
, Show r, Typeable r, NFData r
8486
)
85-
=> IdeState
87+
=> String
88+
-> IdeState
8689
-> NormalizedFilePath
8790
-> a
8891
-> MaybeT IO (Tracked 'Current r)
89-
runCurrentIde state nfp a = MaybeT $ fmap (fmap unsafeMkCurrent) $ runIde state $ use a nfp
92+
runCurrentIde herald state nfp a =
93+
MaybeT $ fmap (fmap unsafeMkCurrent) $ runIde herald (show a) state $ use a nfp
9094

9195

9296
runStaleIde
@@ -95,11 +99,13 @@ runStaleIde
9599
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
96100
, Show r, Typeable r, NFData r
97101
)
98-
=> IdeState
102+
=> String
103+
-> IdeState
99104
-> NormalizedFilePath
100105
-> a
101106
-> MaybeT IO (TrackedStale r)
102-
runStaleIde state nfp a = MaybeT $ runIde state $ useWithStale a nfp
107+
runStaleIde herald state nfp a =
108+
MaybeT $ runIde herald (show a) state $ useWithStale a nfp
103109

104110

105111
unsafeRunStaleIde
@@ -108,12 +114,13 @@ unsafeRunStaleIde
108114
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
109115
, Show r, Typeable r, NFData r
110116
)
111-
=> IdeState
117+
=> String
118+
-> IdeState
112119
-> NormalizedFilePath
113120
-> a
114121
-> MaybeT IO r
115-
unsafeRunStaleIde state nfp a = do
116-
(r, _) <- MaybeT $ runIde state $ IDE.useWithStale a nfp
122+
unsafeRunStaleIde herald state nfp a = do
123+
(r, _) <- MaybeT $ runIde herald (show a) state $ IDE.useWithStale a nfp
117124
pure r
118125

119126

@@ -164,7 +171,7 @@ getIdeDynflags
164171
getIdeDynflags state nfp = do
165172
-- Ok to use the stale 'ModIface', since all we need is its 'DynFlags'
166173
-- which don't change very often.
167-
msr <- unsafeRunStaleIde state nfp GetModSummaryWithoutTimestamps
174+
msr <- unsafeRunStaleIde "getIdeDynflags" state nfp GetModSummaryWithoutTimestamps
168175
pure $ ms_hspp_opts $ msrModSummary msr
169176

170177

@@ -178,15 +185,17 @@ judgementForHole
178185
-> FeatureSet
179186
-> MaybeT IO (Tracked 'Current Range, Judgement, Context, DynFlags)
180187
judgementForHole state nfp range features = do
181-
TrackedStale asts amapping <- runStaleIde state nfp GetHieAst
188+
let stale a = runStaleIde "judgementForHole" state nfp a
189+
190+
TrackedStale asts amapping <- stale GetHieAst
182191
case unTrack asts of
183192
HAR _ _ _ _ (HieFromDisk _) -> fail "Need a fresh hie file"
184193
HAR _ (unsafeCopyAge asts -> hf) _ _ HieFresh -> do
185194
range' <- liftMaybe $ mapAgeFrom amapping range
186-
binds <- runStaleIde state nfp GetBindings
195+
binds <- stale GetBindings
187196
tcg <- fmap (fmap tmrTypechecked)
188-
$ runStaleIde state nfp TypeCheck
189-
hscenv <- runStaleIde state nfp GhcSessionDeps
197+
$ stale TypeCheck
198+
hscenv <- stale GhcSessionDeps
190199

191200
(rss, g) <- liftMaybe $ getSpanAndTypeAtHole range' hf
192201
new_rss <- liftMaybe $ mapAgeTo amapping rss

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

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,13 +96,15 @@ showUserFacingMessage ufm = do
9696
tacticCmd :: (OccName -> TacticsM ()) -> PluginId -> CommandFunction IdeState TacticParams
9797
tacticCmd tac pId state (TacticParams uri range var_name)
9898
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
99+
let stale a = runStaleIde "tacticCmd" state nfp a
100+
99101
features <- getFeatureSet pId
100102
ccs <- getClientCapabilities
101103
cfg <- getTacticConfig pId
102104
res <- liftIO $ runMaybeT $ do
103105
(range', jdg, ctx, dflags) <- judgementForHole state nfp range features
104106
let span = fmap (rangeToRealSrcSpan (fromNormalizedFilePath nfp)) range'
105-
TrackedStale pm pmmap <- runStaleIde state nfp GetAnnotatedParsedSource
107+
TrackedStale pm pmmap <- stale GetAnnotatedParsedSource
106108
pm_span <- liftMaybe $ mapAgeFrom pmmap span
107109

108110
timingOut (cfg_timeout_seconds cfg * seconds) $ join $

0 commit comments

Comments
 (0)