Skip to content

Commit 465ee2b

Browse files
committed
Remove explicit uses of FileDiagnostic, add codes to LSP diagnostics
1 parent 4b39d0f commit 465ee2b

File tree

5 files changed

+45
-30
lines changed

5 files changed

+45
-30
lines changed

ghcide/src/Development/IDE/Core/Preprocessor.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ data CPPDiag
112112

113113
diagsFromCPPLogs :: FilePath -> [CPPLog] -> [FileDiagnostic]
114114
diagsFromCPPLogs filename logs =
115-
map (\d -> FileDiagnostic (toNormalizedFilePath' filename) ShowDiag (cppDiagToDiagnostic d) NoStructuredMessage) $
115+
map (\d -> ideErrorFromLspDiag (cppDiagToDiagnostic d) (toNormalizedFilePath' filename) Nothing) $
116116
go [] logs
117117
where
118118
-- On errors, CPP calls logAction with a real span for the initial log and

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1374,7 +1374,7 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
13741374
lastPublish <- atomicallyNamed "diagnostics - publish" $ STM.focus (Focus.lookupWithDefault [] <* Focus.insert newDiags) uri' publishedDiagnostics
13751375
let action = when (lastPublish /= newDiags) $ case lspEnv of
13761376
Nothing -> -- Print an LSP event.
1377-
logWith recorder Info $ LogDiagsDiffButNoLspEnv (map (\lspDiag -> FileDiagnostic fp ShowDiag lspDiag NoStructuredMessage) newDiags) -- TODO: Should try to get structured diagnostics plumbed here if possible
1377+
logWith recorder Info $ LogDiagsDiffButNoLspEnv (map (\lspDiag -> ideErrorFromLspDiag lspDiag fp Nothing) newDiags) -- TODO: Should try to get structured diagnostics plumbed here if possible
13781378
Just env -> LSP.runLspT env $ do
13791379
liftIO $ tag "count" (show $ Prelude.length newDiags)
13801380
liftIO $ tag "key" (show k)
@@ -1442,7 +1442,7 @@ getAllDiagnostics ::
14421442
STMDiagnosticStore ->
14431443
STM [FileDiagnostic]
14441444
getAllDiagnostics =
1445-
fmap (concatMap (\(k,v) -> map (\diag -> FileDiagnostic (fromUri k) ShowDiag diag NoStructuredMessage) $ getDiagnosticsFromStore v)) . ListT.toList . STM.listT -- TODO: Do we need the structured message here?
1445+
fmap (concatMap (\(k,v) -> map (\diag -> ideErrorFromLspDiag diag (fromUri k) Nothing) $ getDiagnosticsFromStore v)) . ListT.toList . STM.listT -- TODO: Do we need the structured message here?
14461446

14471447
updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> STM ()
14481448
updatePositionMapping IdeState{shakeExtras = ShakeExtras{positionMapping}} VersionedTextDocumentIdentifier{..} changes =

ghcide/src/Development/IDE/GHC/Error.hs

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE DisambiguateRecordFields #-}
23
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
34
-- SPDX-License-Identifier: Apache-2.0
45
module Development.IDE.GHC.Error
@@ -56,23 +57,11 @@ import Language.LSP.VFS (CodePointPosition (CodePoint
5657

5758
diagFromText :: T.Text -> D.DiagnosticSeverity -> SrcSpan -> T.Text -> Maybe (MsgEnvelope GhcMessage) -> FileDiagnostic
5859
diagFromText diagSource sev loc msg origMsg =
59-
FileDiagnostic
60-
{ fdFilePath = toNormalizedFilePath' $ fromMaybe noFilePath $ srcSpanToFilename loc
61-
, fdShouldShowDiagnostic = ShowDiag
62-
, fdLspDiagnostic =
63-
Diagnostic
64-
{ _range = fromMaybe noRange $ srcSpanToRange loc
65-
, _severity = Just sev
66-
, _source = Just diagSource -- not shown in the IDE, but useful for ghcide developers
67-
, _message = msg
68-
, _code = Nothing
69-
, _relatedInformation = Nothing
70-
, _tags = Nothing
71-
, _codeDescription = Nothing
72-
, _data_ = Nothing
73-
}
74-
, fdStructuredMessage = maybe NoStructuredMessage SomeStructuredMessage origMsg
75-
}
60+
modifyFdLspDiagnostic (\diag -> diag { D._range = fromMaybe noRange $ srcSpanToRange loc }) $
61+
D.ideErrorWithSource
62+
(Just diagSource) (Just sev)
63+
(toNormalizedFilePath' $ fromMaybe noFilePath $ srcSpanToFilename loc)
64+
msg origMsg
7665

7766
-- | Produce a GHC-style error from a source span and a message.
7867
diagFromErrMsg :: T.Text -> DynFlags -> MsgEnvelope GhcMessage -> [FileDiagnostic]

ghcide/src/Development/IDE/Plugin/TypeLenses.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -126,9 +126,10 @@ codeLensProvider ideState pId CodeLensParams{_textDocument = TextDocumentIdentif
126126
-- We don't actually pass any data to resolve, however we need this
127127
-- dummy type to make sure HLS resolves our lens
128128
[ CodeLens _range Nothing (Just $ toJSON TypeLensesResolve)
129-
| FileDiagnostic dFile _ diag@Diagnostic{_range} _ <- diags
130-
, dFile == nfp
131-
, isGlobalDiagnostic diag]
129+
| diag <- diags
130+
, let lspDiag@Diagnostic {_range} = fdLspDiagnostic diag
131+
, fdFilePath diag == nfp
132+
, isGlobalDiagnostic lspDiag]
132133
-- The second option is to generate lenses from the GlobalBindingTypeSig
133134
-- rule. This is the only type that needs to have the range adjusted
134135
-- with PositionMapping.

ghcide/src/Development/IDE/Types/Diagnostics.hs

Lines changed: 32 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2,18 +2,24 @@
22
-- SPDX-License-Identifier: Apache-2.0
33

44
{-# LANGUAGE DeriveGeneric #-}
5+
{-# LANGUAGE CPP #-}
56

67
module Development.IDE.Types.Diagnostics (
78
LSP.Diagnostic(..),
89
ShowDiagnostic(..),
910
FileDiagnostic(..),
11+
fdFilePath,
12+
fdShouldShowDiagnostic,
13+
fdLspDiagnostic,
14+
fdStructuredMessage,
1015
modifyFdLspDiagnostic,
1116
StructuredMessage(..),
1217
IdeResult,
1318
LSP.DiagnosticSeverity(..),
1419
DiagnosticStore,
1520
ideErrorText,
1621
ideErrorWithSource,
22+
ideErrorFromLspDiag,
1723
showDiagnostics,
1824
showDiagnosticsColored,
1925
IdeResultNoDiagnosticsEarlyCutoff) where
@@ -25,13 +31,14 @@ import qualified Data.Text as T
2531
import Development.IDE.GHC.Compat (GhcMessage, MsgEnvelope)
2632
import Development.IDE.Types.Location
2733
import GHC.Generics
34+
import GHC.Types.Error (diagnosticCode, DiagnosticCode (..), errMsgDiagnostic)
2835
import Language.LSP.Diagnostics
29-
import Language.LSP.Protocol.Types as LSP (Diagnostic (..),
30-
DiagnosticSeverity (..))
36+
import Language.LSP.Protocol.Types as LSP
3137
import Prettyprinter
3238
import Prettyprinter.Render.Terminal (Color (..), color)
3339
import qualified Prettyprinter.Render.Terminal as Terminal
3440
import Prettyprinter.Render.Text
41+
import Text.Printf (printf)
3542

3643

3744
-- | The result of an IDE operation. Warnings and errors are in the Diagnostic,
@@ -53,6 +60,27 @@ ideErrorText :: Maybe (MsgEnvelope GhcMessage) -> NormalizedFilePath -> T.Text -
5360
ideErrorText origMsg fdFilePath msg =
5461
ideErrorWithSource (Just "compiler") (Just DiagnosticSeverity_Error) fdFilePath msg origMsg
5562

63+
ideErrorFromLspDiag
64+
:: LSP.Diagnostic
65+
-> NormalizedFilePath
66+
-> Maybe (MsgEnvelope GhcMessage)
67+
-> FileDiagnostic
68+
ideErrorFromLspDiag lspDiag fdFilePath origMsg =
69+
let fdShouldShowDiagnostic = ShowDiag
70+
fdStructuredMessage =
71+
maybe NoStructuredMessage SomeStructuredMessage origMsg
72+
fdLspDiagnostic = lspDiag
73+
{ _code = fmap ghcCodeToLspCode . diagnosticCode . errMsgDiagnostic =<< origMsg
74+
}
75+
ghcCodeToLspCode :: DiagnosticCode -> Int32 LSP.|? T.Text
76+
#if MIN_VERSION_ghc(9,10,1)
77+
ghcCodeToLspCode = InR . T.pack . show
78+
#else
79+
ghcCodeToLspCode (DiagnosticCode prefix c) = InR $ T.pack $ prefix ++ "-" ++ printf "%05d" c
80+
#endif
81+
in
82+
FileDiagnostic {..}
83+
5684
ideErrorWithSource
5785
:: Maybe T.Text
5886
-> Maybe DiagnosticSeverity
@@ -61,8 +89,7 @@ ideErrorWithSource
6189
-> Maybe (MsgEnvelope GhcMessage)
6290
-> FileDiagnostic
6391
ideErrorWithSource source sev fdFilePath msg origMsg =
64-
let fdShouldShowDiagnostic = ShowDiag
65-
fdLspDiagnostic =
92+
let lspDiagnostic =
6693
LSP.Diagnostic {
6794
_range = noRange,
6895
_severity = sev,
@@ -74,10 +101,8 @@ ideErrorWithSource source sev fdFilePath msg origMsg =
74101
_codeDescription = Nothing,
75102
_data_ = Nothing
76103
}
77-
fdStructuredMessage =
78-
maybe NoStructuredMessage SomeStructuredMessage origMsg
79104
in
80-
FileDiagnostic {..}
105+
ideErrorFromLspDiag lspDiagnostic fdFilePath origMsg
81106

82107
-- | Defines whether a particular diagnostic should be reported
83108
-- back to the user.

0 commit comments

Comments
 (0)