@@ -22,11 +22,13 @@ import Data.Either (fromRight,
22
22
import Data.Functor ((<&>) )
23
23
import Data.IORef.Extra
24
24
import qualified Data.Map as Map
25
- import Data.Maybe (fromMaybe )
25
+ import Data.Maybe (fromMaybe ,
26
+ maybeToList )
26
27
import qualified Data.Text as T
27
28
import qualified Data.Text.Utf16.Rope.Mixed as Rope
28
29
import Development.IDE hiding
29
30
(pluginHandlers )
31
+ import Development.IDE.Core.PluginUtils (activeDiagnosticsInRange )
30
32
import Development.IDE.Core.Shake
31
33
import Development.IDE.GHC.Compat
32
34
import Development.IDE.GHC.ExactPrint
@@ -53,38 +55,42 @@ type GhcideCodeAction = ExceptT PluginError (ReaderT CodeActionArgs IO) GhcideCo
53
55
-------------------------------------------------------------------------------------------------
54
56
55
57
runGhcideCodeAction :: IdeState -> MessageParams Method_TextDocumentCodeAction -> GhcideCodeAction -> HandlerM Config GhcideCodeActionResult
56
- runGhcideCodeAction state (CodeActionParams _ _ (TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics = diags}) codeAction = do
57
- let mbFile = toNormalizedFilePath' <$> uriToFilePath uri
58
- runRule key = runAction (" GhcideCodeActions." <> show key) state $ runMaybeT $ MaybeT (pure mbFile) >>= MaybeT . use key
59
- caaGhcSession <- onceIO $ runRule GhcSession
60
- caaExportsMap <-
61
- onceIO $
62
- caaGhcSession >>= \ case
63
- Just env -> do
64
- pkgExports <- envPackageExports env
65
- localExports <- readTVarIO (exportsMap $ shakeExtras state)
66
- pure $ localExports <> pkgExports
67
- _ -> pure mempty
68
- caaIdeOptions <- onceIO $ runAction " GhcideCodeActions.getIdeOptions" state getIdeOptions
69
- caaParsedModule <- onceIO $ runRule GetParsedModuleWithComments
70
- caaContents <-
71
- onceIO $
72
- runRule GetFileContents <&> \ case
73
- Just (_, mbContents) -> fmap Rope. toText mbContents
74
- Nothing -> Nothing
75
- caaDf <- onceIO $ fmap (ms_hspp_opts . pm_mod_summary) <$> caaParsedModule
76
- caaAnnSource <- onceIO $ runRule GetAnnotatedParsedSource
77
- caaTmr <- onceIO $ runRule TypeCheck
78
- caaHar <- onceIO $ runRule GetHieAst
79
- caaBindings <- onceIO $ runRule GetBindings
80
- caaGblSigs <- onceIO $ runRule GetGlobalBindingTypeSigs
81
- results <- liftIO $
82
- sequence
83
- [ runReaderT (runExceptT codeAction) CodeActionArgs {.. }
84
- | caaDiagnostic <- diags
85
- ]
86
- let (_errs, successes) = partitionEithers results
87
- pure $ concat successes
58
+ runGhcideCodeAction state (CodeActionParams _ _ (TextDocumentIdentifier uri) _range _) codeAction
59
+ | Just nfp <- toNormalizedFilePath' <$> uriToFilePath uri = do
60
+ let runRule key = runAction (" GhcideCodeActions." <> show key) state $ runMaybeT $ MaybeT (pure (Just nfp)) >>= MaybeT . use key
61
+ caaGhcSession <- onceIO $ runRule GhcSession
62
+ caaExportsMap <-
63
+ onceIO $
64
+ caaGhcSession >>= \ case
65
+ Just env -> do
66
+ pkgExports <- envPackageExports env
67
+ localExports <- readTVarIO (exportsMap $ shakeExtras state)
68
+ pure $ localExports <> pkgExports
69
+ _ -> pure mempty
70
+ caaIdeOptions <- onceIO $ runAction " GhcideCodeActions.getIdeOptions" state getIdeOptions
71
+ caaParsedModule <- onceIO $ runRule GetParsedModuleWithComments
72
+ caaContents <-
73
+ onceIO $
74
+ runRule GetFileContents <&> \ case
75
+ Just (_, mbContents) -> fmap Rope. toText mbContents
76
+ Nothing -> Nothing
77
+ caaDf <- onceIO $ fmap (ms_hspp_opts . pm_mod_summary) <$> caaParsedModule
78
+ caaAnnSource <- onceIO $ runRule GetAnnotatedParsedSource
79
+ caaTmr <- onceIO $ runRule TypeCheck
80
+ caaHar <- onceIO $ runRule GetHieAst
81
+ caaBindings <- onceIO $ runRule GetBindings
82
+ caaGblSigs <- onceIO $ runRule GetGlobalBindingTypeSigs
83
+ diags <- concat . maybeToList <$> activeDiagnosticsInRange (shakeExtras state) nfp _range
84
+ results <- liftIO $
85
+ sequence
86
+ [
87
+ runReaderT (runExceptT codeAction) CodeActionArgs {.. }
88
+ | caaDiagnostic <- diags
89
+ ]
90
+ let (_errs, successes) = partitionEithers results
91
+ pure $ concat successes
92
+ | otherwise = pure []
93
+
88
94
89
95
mkCA :: T. Text -> Maybe CodeActionKind -> Maybe Bool -> [Diagnostic ] -> WorkspaceEdit -> (Command |? CodeAction )
90
96
mkCA title kind isPreferred diags edit =
@@ -145,7 +151,7 @@ data CodeActionArgs = CodeActionArgs
145
151
caaHar :: IO (Maybe HieAstResult ),
146
152
caaBindings :: IO (Maybe Bindings ),
147
153
caaGblSigs :: IO (Maybe GlobalBindingTypeSigsResult ),
148
- caaDiagnostic :: Diagnostic
154
+ caaDiagnostic :: FileDiagnostic
149
155
}
150
156
151
157
-- | There's no concurrency in each provider,
@@ -223,6 +229,9 @@ instance ToCodeAction r => ToCodeAction (IdeOptions -> r) where
223
229
toCodeAction = toCodeAction3 caaIdeOptions
224
230
225
231
instance ToCodeAction r => ToCodeAction (Diagnostic -> r ) where
232
+ toCodeAction f = ExceptT . ReaderT $ \ caa@ CodeActionArgs {caaDiagnostic = x} -> flip runReaderT caa . runExceptT . toCodeAction $ f (fdLspDiagnostic x)
233
+
234
+ instance ToCodeAction r => ToCodeAction (FileDiagnostic -> r ) where
226
235
toCodeAction f = ExceptT . ReaderT $ \ caa@ CodeActionArgs {caaDiagnostic = x} -> flip runReaderT caa . runExceptT . toCodeAction $ f x
227
236
228
237
instance ToCodeAction r => ToCodeAction (Maybe ParsedModule -> r ) where
0 commit comments