6
6
{-# LANGUAGE FlexibleInstances #-}
7
7
{-# LANGUAGE OverloadedLabels #-}
8
8
{-# LANGUAGE OverloadedStrings #-}
9
- {-# LANGUAGE PackageImports #-}
10
9
{-# LANGUAGE PatternSynonyms #-}
11
10
{-# LANGUAGE ScopedTypeVariables #-}
12
- {-# LANGUAGE TupleSections #-}
13
11
{-# LANGUAGE TypeFamilies #-}
14
- {-# LANGUAGE ViewPatterns #-}
15
12
{-# OPTIONS_GHC -Wno-orphans #-}
13
+ {-# LANGUAGE MultiWayIf #-}
14
+ {-# LANGUAGE NamedFieldPuns #-}
15
+ {-# LANGUAGE RecordWildCards #-}
16
16
17
17
#ifdef HLINT_ON_GHC_LIB
18
18
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib(x,y,z)
23
23
module Ide.Plugin.Hlint
24
24
(
25
25
descriptor
26
- -- , provider
27
26
) where
28
27
import Control.Arrow ((&&&) )
29
28
import Control.Concurrent.STM
@@ -105,6 +104,13 @@ import qualified Language.LSP.Types.Lens as LSP
105
104
import GHC.Generics (Generic )
106
105
import Text.Regex.TDFA.Text ()
107
106
107
+ import Development.IDE.Spans.Pragmas (LineSplitTextEdits (LineSplitTextEdits ),
108
+ NextPragmaInfo (NextPragmaInfo ),
109
+ getNextPragmaInfo ,
110
+ lineSplitDeleteTextEdit ,
111
+ lineSplitInsertTextEdit ,
112
+ lineSplitTextEdits ,
113
+ nextPragmaLine )
108
114
import System.Environment (setEnv ,
109
115
unsetEnv )
110
116
-- ---------------------------------------------------------------------
@@ -303,39 +309,57 @@ getHlintConfig pId =
303
309
Config
304
310
<$> usePropertyAction # flags pId properties
305
311
312
+ runHlintAction
313
+ :: (Eq k , Hashable k , Show k , Show (RuleResult k ), Typeable k , Typeable (RuleResult k ), NFData k , NFData (RuleResult k ))
314
+ => IdeState
315
+ -> NormalizedFilePath -> String -> k -> IO (Maybe (RuleResult k ))
316
+ runHlintAction ideState normalizedFilePath desc rule = runAction desc ideState $ use rule normalizedFilePath
317
+
318
+ runGetFileContentsAction :: IdeState -> NormalizedFilePath -> IO (Maybe (FileVersion , Maybe T. Text ))
319
+ runGetFileContentsAction ideState normalizedFilePath = runHlintAction ideState normalizedFilePath " Hlint.GetFileContents" GetFileContents
320
+
321
+ runGetModSummaryAction :: IdeState -> NormalizedFilePath -> IO (Maybe ModSummaryResult )
322
+ runGetModSummaryAction ideState normalizedFilePath = runHlintAction ideState normalizedFilePath " Hlint.GetModSummary" GetModSummary
323
+
306
324
-- ---------------------------------------------------------------------
307
325
codeActionProvider :: PluginMethodHandler IdeState TextDocumentCodeAction
308
- codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right . LSP. List . map InR <$> liftIO getCodeActions
309
- where
310
-
311
- getCodeActions = do
312
- allDiags <- atomically $ getDiagnostics ideState
313
- let docNfp = toNormalizedFilePath' <$> uriToFilePath' (docId ^. LSP. uri)
314
- numHintsInDoc = length
315
- [d | (nfp, _, d) <- allDiags
316
- , validCommand d
317
- , Just nfp == docNfp
318
- ]
319
- numHintsInContext = length
320
- [d | d <- diags
321
- , validCommand d
322
- ]
323
- -- We only want to show the applyAll code action if there is more than 1
324
- -- hint in the current document and if code action range contains at
325
- -- least one hint
326
- if numHintsInDoc > 1 && numHintsInContext > 0 then do
327
- pure $ applyAllAction: applyOneActions
328
- else
329
- pure applyOneActions
326
+ codeActionProvider ideState pluginId (CodeActionParams _ _ documentId _ context)
327
+ | let TextDocumentIdentifier uri = documentId
328
+ , Just docNormalizedFilePath <- uriToNormalizedFilePath (toNormalizedUri uri)
329
+ = liftIO $ fmap (Right . LSP. List . map LSP. InR ) $ do
330
+ allDiagnostics <- atomically $ getDiagnostics ideState
331
+ let numHintsInDoc = length
332
+ [diagnostic | (diagnosticNormalizedFilePath, _, diagnostic) <- allDiagnostics
333
+ , validCommand diagnostic
334
+ , diagnosticNormalizedFilePath == docNormalizedFilePath
335
+ ]
336
+ let numHintsInContext = length
337
+ [diagnostic | diagnostic <- diags
338
+ , validCommand diagnostic
339
+ ]
340
+ file <- runGetFileContentsAction ideState docNormalizedFilePath
341
+ singleHintCodeActions <-
342
+ if | Just (_, source) <- file -> do
343
+ modSummaryResult <- runGetModSummaryAction ideState docNormalizedFilePath
344
+ pure if | Just modSummaryResult <- modSummaryResult
345
+ , Just source <- source
346
+ , let dynFlags = ms_hspp_opts $ msrModSummary modSummaryResult ->
347
+ diags >>= diagnosticToCodeActions dynFlags source pluginId documentId
348
+ | otherwise -> []
349
+ | otherwise -> pure []
350
+ if numHintsInDoc > 1 && numHintsInContext > 0 then do
351
+ pure $ singleHintCodeActions ++ [applyAllAction]
352
+ else
353
+ pure singleHintCodeActions
354
+ | otherwise
355
+ = pure $ Right $ LSP. List []
330
356
357
+ where
331
358
applyAllAction =
332
- let args = Just [toJSON (docId ^. LSP. uri)]
333
- cmd = mkLspCommand plId " applyAll" " Apply all hints" args
359
+ let args = Just [toJSON (documentId ^. LSP. uri)]
360
+ cmd = mkLspCommand pluginId " applyAll" " Apply all hints" args
334
361
in LSP. CodeAction " Apply all hints" (Just LSP. CodeActionQuickFix ) Nothing Nothing Nothing Nothing (Just cmd) Nothing
335
362
336
- applyOneActions :: [LSP. CodeAction ]
337
- applyOneActions = mapMaybe mkHlintAction (filter validCommand diags)
338
-
339
363
-- | Some hints do not have an associated refactoring
340
364
validCommand (LSP. Diagnostic _ _ (Just (InR code)) (Just " hlint" ) _ _ _) =
341
365
" refact:" `T.isPrefixOf` code
@@ -344,18 +368,64 @@ codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right
344
368
345
369
LSP. List diags = context ^. LSP. diagnostics
346
370
347
- mkHlintAction :: LSP. Diagnostic -> Maybe LSP. CodeAction
348
- mkHlintAction diag@ (LSP. Diagnostic (LSP. Range start _) _s (Just (InR code)) (Just " hlint" ) _ _ _) =
349
- Just . codeAction $ mkLspCommand plId " applyOne" title (Just args)
350
- where
351
- codeAction cmd = LSP. CodeAction title (Just LSP. CodeActionQuickFix ) (Just (LSP. List [diag])) Nothing Nothing Nothing (Just cmd) Nothing
352
- -- we have to recover the original ideaHint removing the prefix
353
- ideaHint = T. replace " refact:" " " code
354
- title = " Apply hint: " <> ideaHint
355
- -- need 'file', 'start_pos' and hint title (to distinguish between alternative suggestions at the same location)
356
- args = [toJSON (AOP (docId ^. LSP. uri) start ideaHint)]
357
- mkHlintAction (LSP. Diagnostic _r _s _c _source _m _ _) = Nothing
358
-
371
+ -- | Convert a hlint diagonistic into an apply and an ignore code action
372
+ -- if applicable
373
+ diagnosticToCodeActions :: DynFlags -> T. Text -> PluginId -> TextDocumentIdentifier -> LSP. Diagnostic -> [LSP. CodeAction ]
374
+ diagnosticToCodeActions dynFlags fileContents pluginId documentId diagnostic
375
+ | LSP. Diagnostic { _source = Just " hlint" , _code = Just (InR code), _range = LSP. Range start _ } <- diagnostic
376
+ , let TextDocumentIdentifier uri = documentId
377
+ , let isHintApplicable = " refact:" `T.isPrefixOf` code
378
+ , let hint = T. replace " refact:" " " code
379
+ , let suppressHintTitle = " Ignore hint \" " <> hint <> " \" in this module"
380
+ , let suppressHintTextEdits = mkSuppressHintTextEdits dynFlags fileContents hint
381
+ , let suppressHintWorkspaceEdit =
382
+ LSP. WorkspaceEdit
383
+ (Just (Map. singleton uri (List suppressHintTextEdits)))
384
+ Nothing
385
+ Nothing
386
+ = catMaybes
387
+ [ if | isHintApplicable
388
+ , let applyHintTitle = " Apply hint \" " <> hint <> " \" "
389
+ applyHintArguments = [toJSON (AOP (documentId ^. LSP. uri) start hint)]
390
+ applyHintCommand = mkLspCommand pluginId " applyOne" applyHintTitle (Just applyHintArguments) ->
391
+ Just (mkCodeAction applyHintTitle diagnostic Nothing (Just applyHintCommand))
392
+ | otherwise -> Nothing
393
+ , Just (mkCodeAction suppressHintTitle diagnostic (Just suppressHintWorkspaceEdit) Nothing )
394
+ ]
395
+ | otherwise = []
396
+
397
+ mkCodeAction :: T. Text -> LSP. Diagnostic -> Maybe LSP. WorkspaceEdit -> Maybe LSP. Command -> LSP. CodeAction
398
+ mkCodeAction title diagnostic workspaceEdit command =
399
+ LSP. CodeAction
400
+ { _title = title
401
+ , _kind = Just LSP. CodeActionQuickFix
402
+ , _diagnostics = Just (LSP. List [diagnostic])
403
+ , _isPreferred = Nothing
404
+ , _disabled = Nothing
405
+ , _edit = workspaceEdit
406
+ , _command = command
407
+ , _xdata = Nothing
408
+ }
409
+
410
+ mkSuppressHintTextEdits :: DynFlags -> T. Text -> T. Text -> [LSP. TextEdit ]
411
+ mkSuppressHintTextEdits dynFlags fileContents hint =
412
+ let
413
+ NextPragmaInfo { nextPragmaLine, lineSplitTextEdits } = getNextPragmaInfo dynFlags (Just fileContents)
414
+ nextPragmaLinePosition = Position nextPragmaLine 0
415
+ nextPragmaRange = Range nextPragmaLinePosition nextPragmaLinePosition
416
+ wnoUnrecognisedPragmasText =
417
+ if wopt Opt_WarnUnrecognisedPragmas dynFlags
418
+ then Just " {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}\n "
419
+ else Nothing
420
+ hlintIgnoreText = Just (" {-# HLINT ignore \" " <> hint <> " \" #-}\n " )
421
+ -- we combine the texts into a single text because lsp-test currently
422
+ -- applies text edits backwards and I want the options pragma to
423
+ -- appear above the hlint pragma in the tests
424
+ combinedText = mconcat $ catMaybes [wnoUnrecognisedPragmasText, hlintIgnoreText]
425
+ combinedTextEdit = LSP. TextEdit nextPragmaRange combinedText
426
+ lineSplitTextEditList = maybe [] (\ LineSplitTextEdits {.. } -> [lineSplitInsertTextEdit, lineSplitDeleteTextEdit]) lineSplitTextEdits
427
+ in
428
+ combinedTextEdit : lineSplitTextEditList
359
429
-- ---------------------------------------------------------------------
360
430
361
431
applyAllCmd :: CommandFunction IdeState Uri
0 commit comments