3
3
{-# LANGUAGE RankNTypes #-}
4
4
{-# LANGUAGE TypeFamilies #-}
5
5
6
+ {-# LANGUAGE NoMonoLocalBinds #-}
7
+
6
8
module Wingman.LanguageServer where
7
9
8
10
import ConLike
@@ -72,8 +74,8 @@ tcCommandName :: TacticCommand -> T.Text
72
74
tcCommandName = T. pack . show
73
75
74
76
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
77
79
78
80
79
81
runCurrentIde
@@ -82,11 +84,13 @@ runCurrentIde
82
84
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
83
85
, Show r , Typeable r , NFData r
84
86
)
85
- => IdeState
87
+ => String
88
+ -> IdeState
86
89
-> NormalizedFilePath
87
90
-> a
88
91
-> 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
90
94
91
95
92
96
runStaleIde
@@ -95,11 +99,13 @@ runStaleIde
95
99
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
96
100
, Show r , Typeable r , NFData r
97
101
)
98
- => IdeState
102
+ => String
103
+ -> IdeState
99
104
-> NormalizedFilePath
100
105
-> a
101
106
-> 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
103
109
104
110
105
111
unsafeRunStaleIde
@@ -108,12 +114,13 @@ unsafeRunStaleIde
108
114
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
109
115
, Show r , Typeable r , NFData r
110
116
)
111
- => IdeState
117
+ => String
118
+ -> IdeState
112
119
-> NormalizedFilePath
113
120
-> a
114
121
-> 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
117
124
pure r
118
125
119
126
@@ -164,7 +171,7 @@ getIdeDynflags
164
171
getIdeDynflags state nfp = do
165
172
-- Ok to use the stale 'ModIface', since all we need is its 'DynFlags'
166
173
-- which don't change very often.
167
- msr <- unsafeRunStaleIde state nfp GetModSummaryWithoutTimestamps
174
+ msr <- unsafeRunStaleIde " getIdeDynflags " state nfp GetModSummaryWithoutTimestamps
168
175
pure $ ms_hspp_opts $ msrModSummary msr
169
176
170
177
@@ -178,15 +185,17 @@ judgementForHole
178
185
-> FeatureSet
179
186
-> MaybeT IO (Tracked 'Current Range , Judgement , Context , DynFlags )
180
187
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
182
191
case unTrack asts of
183
192
HAR _ _ _ _ (HieFromDisk _) -> fail " Need a fresh hie file"
184
193
HAR _ (unsafeCopyAge asts -> hf) _ _ HieFresh -> do
185
194
range' <- liftMaybe $ mapAgeFrom amapping range
186
- binds <- runStaleIde state nfp GetBindings
195
+ binds <- stale GetBindings
187
196
tcg <- fmap (fmap tmrTypechecked)
188
- $ runStaleIde state nfp TypeCheck
189
- hscenv <- runStaleIde state nfp GhcSessionDeps
197
+ $ stale TypeCheck
198
+ hscenv <- stale GhcSessionDeps
190
199
191
200
(rss, g) <- liftMaybe $ getSpanAndTypeAtHole range' hf
192
201
new_rss <- liftMaybe $ mapAgeTo amapping rss
0 commit comments