1
1
{-# LANGUAGE CPP #-}
2
2
{-# LANGUAGE DataKinds #-}
3
3
{-# LANGUAGE DuplicateRecordFields #-}
4
+ {-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE MultiWayIf #-}
5
6
{-# LANGUAGE OverloadedStrings #-}
6
7
{-# LANGUAGE ViewPatterns #-}
@@ -27,12 +28,17 @@ import qualified Data.Text as T
27
28
import Development.IDE hiding (line )
28
29
import Development.IDE.Core.Compile (sourceParser ,
29
30
sourceTypecheck )
31
+ import Development.IDE.Core.FileStore (getVersionedTextDoc )
30
32
import Development.IDE.Core.PluginUtils
31
33
import Development.IDE.GHC.Compat
34
+ import Development.IDE.GHC.Compat.Error (msgEnvelopeErrorL )
32
35
import Development.IDE.Plugin.Completions (ghcideCompletionsPluginPriority )
33
36
import Development.IDE.Plugin.Completions.Logic (getCompletionPrefixFromRope )
34
37
import Development.IDE.Plugin.Completions.Types (PosPrefixInfo (.. ))
35
38
import qualified Development.IDE.Spans.Pragmas as Pragmas
39
+ import GHC.Types.Error (GhcHint (SuggestExtension ),
40
+ LanguageExtensionHint (.. ),
41
+ diagnosticHints )
36
42
import Ide.Plugin.Error
37
43
import Ide.Types
38
44
import qualified Language.LSP.Protocol.Lens as L
@@ -69,13 +75,34 @@ data Pragma = LangExt T.Text | OptGHC T.Text
69
75
deriving (Show , Eq , Ord )
70
76
71
77
suggestPragmaProvider :: PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
72
- suggestPragmaProvider = mkCodeActionProvider suggest
78
+ suggestPragmaProvider = if ghcVersion /= GHC96 then
79
+ mkCodeActionProvider suggestAddPragma
80
+ else mkCodeActionProvider96 suggestAddPragma96
73
81
74
82
suggestDisableWarningProvider :: PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
75
83
suggestDisableWarningProvider = mkCodeActionProvider $ const suggestDisableWarning
76
84
77
- mkCodeActionProvider :: (Maybe DynFlags -> Diagnostic -> [PragmaEdit ]) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
85
+ mkCodeActionProvider :: (Maybe DynFlags -> FileDiagnostic -> [PragmaEdit ]) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
78
86
mkCodeActionProvider mkSuggest state _plId
87
+ (LSP. CodeActionParams _ _ docId@ LSP. TextDocumentIdentifier { _uri = uri } caRange _) = do
88
+ verTxtDocId <- liftIO $ runAction " classplugin.codeAction.getVersionedTextDoc" state $ getVersionedTextDoc docId
89
+ normalizedFilePath <- getNormalizedFilePathE (verTxtDocId ^. L. uri)
90
+ -- ghc session to get some dynflags even if module isn't parsed
91
+ (hscEnv -> hsc_dflags -> sessionDynFlags, _) <-
92
+ runActionE " Pragmas.GhcSession" state $ useWithStaleE GhcSession normalizedFilePath
93
+ fileContents <- liftIO $ runAction " Pragmas.GetFileContents" state $ getFileContents normalizedFilePath
94
+ parsedModule <- liftIO $ runAction " Pragmas.GetParsedModule" state $ getParsedModule normalizedFilePath
95
+
96
+
97
+ let parsedModuleDynFlags = ms_hspp_opts . pm_mod_summary <$> parsedModule
98
+ nextPragmaInfo = Pragmas. getNextPragmaInfo sessionDynFlags fileContents
99
+ activeDiagnosticsInRange (shakeExtras state) normalizedFilePath caRange >>= \ case
100
+ Nothing -> pure $ LSP. InL []
101
+ Just fileDiags -> do
102
+ let actions = concatMap (mkSuggest parsedModuleDynFlags) fileDiags
103
+ pure $ LSP. InL $ pragmaEditToAction uri nextPragmaInfo <$> nubOrdOn snd actions
104
+ mkCodeActionProvider96 :: (Maybe DynFlags -> Diagnostic -> [PragmaEdit ]) -> PluginMethodHandler IdeState 'LSP.Method_TextDocumentCodeAction
105
+ mkCodeActionProvider96 mkSuggest state _plId
79
106
(LSP. CodeActionParams _ _ LSP. TextDocumentIdentifier { _uri = uri } _ (LSP. CodeActionContext diags _monly _)) = do
80
107
normalizedFilePath <- getNormalizedFilePathE uri
81
108
-- ghc session to get some dynflags even if module isn't parsed
@@ -89,7 +116,6 @@ mkCodeActionProvider mkSuggest state _plId
89
116
pure $ LSP. InL $ pragmaEditToAction uri nextPragmaInfo <$> pedits
90
117
91
118
92
-
93
119
-- | Add a Pragma to the given URI at the top of the file.
94
120
-- It is assumed that the pragma name is a valid pragma,
95
121
-- thus, not validated.
@@ -115,15 +141,12 @@ pragmaEditToAction uri Pragmas.NextPragmaInfo{ nextPragmaLine, lineSplitTextEdit
115
141
Nothing
116
142
Nothing
117
143
118
- suggest :: Maybe DynFlags -> Diagnostic -> [PragmaEdit ]
119
- suggest dflags diag =
120
- suggestAddPragma dflags diag
121
144
122
145
-- ---------------------------------------------------------------------
123
146
124
- suggestDisableWarning :: Diagnostic -> [PragmaEdit ]
147
+ suggestDisableWarning :: FileDiagnostic -> [PragmaEdit ]
125
148
suggestDisableWarning diagnostic
126
- | Just (Just (JSON. Array attachedReasons)) <- diagnostic ^? attachedReason
149
+ | Just (Just (JSON. Array attachedReasons)) <- diagnostic ^? fdLspDiagnosticL . attachedReason
127
150
=
128
151
[ (" Disable \" " <> w <> " \" warnings" , OptGHC w)
129
152
| JSON. String attachedReason <- Foldable. toList attachedReasons
@@ -142,10 +165,24 @@ warningBlacklist =
142
165
143
166
-- ---------------------------------------------------------------------
144
167
168
+ -- | Offer to add a missing Language Pragma to the top of a file.
169
+ suggestAddPragma :: Maybe DynFlags -> FileDiagnostic -> [PragmaEdit ]
170
+ suggestAddPragma mDynflags fd= [(" Add \" " <> r <> " \" " , LangExt r) | r <- map (T. pack . show ) $ suggestsExtension fd, r `notElem` disabled]
171
+ where
172
+ disabled
173
+ | Just dynFlags <- mDynflags =
174
+ -- GHC does not export 'OnOff', so we have to view it as string
175
+ mapMaybe (T. stripPrefix " Off " . printOutputable) (extensions dynFlags)
176
+ | otherwise =
177
+ -- When the module failed to parse, we don't have access to its
178
+ -- dynFlags. In that case, simply don't disable any pragmas.
179
+ []
180
+
145
181
-- | Offer to add a missing Language Pragma to the top of a file.
146
182
-- Pragmas are defined by a curated list of known pragmas, see 'possiblePragmas'.
147
- suggestAddPragma :: Maybe DynFlags -> Diagnostic -> [PragmaEdit ]
148
- suggestAddPragma mDynflags Diagnostic {_message, _source}
183
+ -- Kept for compatibility with ghc9.6 - it is missing some structured diagnostics
184
+ suggestAddPragma96 :: Maybe DynFlags -> Diagnostic -> [PragmaEdit ]
185
+ suggestAddPragma96 mDynflags Diagnostic {_message, _source}
149
186
| _source == Just sourceTypecheck || _source == Just sourceParser = genPragma _message
150
187
where
151
188
genPragma target =
@@ -158,8 +195,7 @@ suggestAddPragma mDynflags Diagnostic {_message, _source}
158
195
-- When the module failed to parse, we don't have access to its
159
196
-- dynFlags. In that case, simply don't disable any pragmas.
160
197
[]
161
- suggestAddPragma _ _ = []
162
-
198
+ suggestAddPragma96 _ _ = []
163
199
-- | Find all Pragmas are an infix of the search term.
164
200
findPragma :: T. Text -> [T. Text ]
165
201
findPragma str = concatMap check possiblePragmas
@@ -178,6 +214,22 @@ findPragma str = concatMap check possiblePragmas
178
214
, " Strict" /= name
179
215
]
180
216
217
+ suggestsExtension :: FileDiagnostic -> [Extension ]
218
+ suggestsExtension message = case message ^? fdStructuredMessageL . _SomeStructuredMessage . msgEnvelopeErrorL of
219
+ Just s -> concat $ mapMaybe (\ case
220
+ SuggestExtension s -> Just $ ghcHintSuggestsExtension s
221
+ _ -> Nothing ) (diagnosticHints s)
222
+ _ -> []
223
+
224
+ ghcHintSuggestsExtension :: LanguageExtensionHint -> [Extension ]
225
+ ghcHintSuggestsExtension (SuggestSingleExtension _ ext) = [ext]
226
+ ghcHintSuggestsExtension (SuggestAnyExtension _ (ext: _)) = [ext] -- ghc suggests any of those, we pick first
227
+ ghcHintSuggestsExtension (SuggestAnyExtension _ [] ) = []
228
+ ghcHintSuggestsExtension (SuggestExtensions _ ext) = ext
229
+ ghcHintSuggestsExtension (SuggestExtensionInOrderTo _ ext) = [ext]
230
+
231
+
232
+
181
233
-- | All language pragmas, including the No- variants
182
234
allPragmas :: [T. Text ]
183
235
allPragmas =
0 commit comments