Safe Haskell | None |
---|---|
Language | GHC2021 |
Development.IDE.Types.Diagnostics
Synopsis
- data Diagnostic = Diagnostic {}
- data ShowDiagnostic
- data FileDiagnostic = FileDiagnostic {}
- fdFilePathL :: Lens' FileDiagnostic NormalizedFilePath
- fdLspDiagnosticL :: Lens' FileDiagnostic Diagnostic
- fdShouldShowDiagnosticL :: Lens' FileDiagnostic ShowDiagnostic
- fdStructuredMessageL :: Lens' FileDiagnostic StructuredMessage
- data StructuredMessage
- _NoStructuredMessage :: Prism' StructuredMessage ()
- _SomeStructuredMessage :: Prism' StructuredMessage (MsgEnvelope GhcMessage)
- type IdeResult v = ([FileDiagnostic], Maybe v)
- data DiagnosticSeverity
- type DiagnosticStore = HashMap NormalizedUri StoreItem
- ideErrorText :: NormalizedFilePath -> Text -> FileDiagnostic
- ideErrorWithSource :: Maybe Text -> Maybe DiagnosticSeverity -> NormalizedFilePath -> Text -> Maybe (MsgEnvelope GhcMessage) -> FileDiagnostic
- ideErrorFromLspDiag :: Diagnostic -> NormalizedFilePath -> Maybe (MsgEnvelope GhcMessage) -> FileDiagnostic
- showDiagnostics :: [FileDiagnostic] -> Text
- showDiagnosticsColored :: [FileDiagnostic] -> Text
- showGhcCode :: DiagnosticCode -> Text
- type IdeResultNoDiagnosticsEarlyCutoff v = (Maybe ByteString, Maybe v)
- attachReason :: Maybe DiagnosticReason -> Diagnostic -> Diagnostic
- attachedReason :: Traversal' Diagnostic (Maybe Value)
Documentation
data Diagnostic #
Constructors
Diagnostic | |
Instances
data ShowDiagnostic Source #
Defines whether a particular diagnostic should be reported back to the user.
One important use case is "missing signature" code lenses, for which we need to enable the corresponding warning during type checking. However, we do not want to show the warning unless the programmer asks for it (#261).
Instances
Show ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods showsPrec :: Int -> ShowDiagnostic -> ShowS # show :: ShowDiagnostic -> String # showList :: [ShowDiagnostic] -> ShowS # | |
NFData ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods rnf :: ShowDiagnostic -> () # | |
Eq ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods (==) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (/=) :: ShowDiagnostic -> ShowDiagnostic -> Bool # | |
Ord ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods compare :: ShowDiagnostic -> ShowDiagnostic -> Ordering # (<) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (<=) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (>) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (>=) :: ShowDiagnostic -> ShowDiagnostic -> Bool # max :: ShowDiagnostic -> ShowDiagnostic -> ShowDiagnostic # min :: ShowDiagnostic -> ShowDiagnostic -> ShowDiagnostic # |
data FileDiagnostic Source #
Human readable diagnostics for a specific file.
This type packages a pretty printed, human readable error message along with the related source location so that we can display the error on either the console or in the IDE at the right source location.
It also optionally keeps a structured diagnostic message GhcMessage in StructuredMessage.
Constructors
FileDiagnostic | |
Fields
|
Instances
Generic FileDiagnostic Source # | |||||
Defined in Development.IDE.Types.Diagnostics Associated Types
Methods from :: FileDiagnostic -> Rep FileDiagnostic x # to :: Rep FileDiagnostic x -> FileDiagnostic # | |||||
Show FileDiagnostic Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods showsPrec :: Int -> FileDiagnostic -> ShowS # show :: FileDiagnostic -> String # showList :: [FileDiagnostic] -> ShowS # | |||||
NFData FileDiagnostic Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods rnf :: FileDiagnostic -> () # | |||||
Eq FileDiagnostic Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods (==) :: FileDiagnostic -> FileDiagnostic -> Bool # (/=) :: FileDiagnostic -> FileDiagnostic -> Bool # | |||||
Ord FileDiagnostic Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods compare :: FileDiagnostic -> FileDiagnostic -> Ordering # (<) :: FileDiagnostic -> FileDiagnostic -> Bool # (<=) :: FileDiagnostic -> FileDiagnostic -> Bool # (>) :: FileDiagnostic -> FileDiagnostic -> Bool # (>=) :: FileDiagnostic -> FileDiagnostic -> Bool # max :: FileDiagnostic -> FileDiagnostic -> FileDiagnostic # min :: FileDiagnostic -> FileDiagnostic -> FileDiagnostic # | |||||
type Rep FileDiagnostic Source # | |||||
Defined in Development.IDE.Types.Diagnostics type Rep FileDiagnostic = D1 ('MetaData "FileDiagnostic" "Development.IDE.Types.Diagnostics" "ghcide-2.11.0.0-IzuGh9ZsoLJF9Sbc2JF8Yt" 'False) (C1 ('MetaCons "FileDiagnostic" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fdFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NormalizedFilePath) :*: S1 ('MetaSel ('Just "fdShouldShowDiagnostic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShowDiagnostic)) :*: (S1 ('MetaSel ('Just "fdLspDiagnostic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Diagnostic) :*: S1 ('MetaSel ('Just "fdStructuredMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StructuredMessage)))) |
data StructuredMessage Source #
A Maybe-like wrapper for a GhcMessage that doesn't try to compare, show, or force the GhcMessage inside, so that we can derive Show, Eq, Ord, NFData on FileDiagnostic. FileDiagnostic only uses this as metadata so we can safely ignore it in fields.
Instead of pattern matching on these constructors directly, consider Prism
from
the lens
package. This allows to conveniently pattern match deeply into the 'MsgEnvelope GhcMessage'
constructor.
The module Error
implements additional Lens
s and Prism
s,
allowing you to avoid importing GHC modules directly.
For example, to pattern match on a TcRnMessage
you can use the lens:
message ^? _SomeStructuredMessage . msgEnvelopeErrorL . _TcRnMessage
This produces a value of type `Maybe TcRnMessage`.
Further, consider utility functions such as stripTcRnMessageContext
, which strip
context from error messages which may be more convenient in certain situations.
Constructors
NoStructuredMessage | |
SomeStructuredMessage (MsgEnvelope GhcMessage) |
Instances
Generic StructuredMessage Source # | |||||
Defined in Development.IDE.Types.Diagnostics Associated Types
Methods from :: StructuredMessage -> Rep StructuredMessage x # to :: Rep StructuredMessage x -> StructuredMessage # | |||||
Show StructuredMessage Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods showsPrec :: Int -> StructuredMessage -> ShowS # show :: StructuredMessage -> String # showList :: [StructuredMessage] -> ShowS # | |||||
NFData StructuredMessage Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods rnf :: StructuredMessage -> () # | |||||
Eq StructuredMessage Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods (==) :: StructuredMessage -> StructuredMessage -> Bool # (/=) :: StructuredMessage -> StructuredMessage -> Bool # | |||||
Ord StructuredMessage Source # | |||||
Defined in Development.IDE.Types.Diagnostics Methods compare :: StructuredMessage -> StructuredMessage -> Ordering # (<) :: StructuredMessage -> StructuredMessage -> Bool # (<=) :: StructuredMessage -> StructuredMessage -> Bool # (>) :: StructuredMessage -> StructuredMessage -> Bool # (>=) :: StructuredMessage -> StructuredMessage -> Bool # max :: StructuredMessage -> StructuredMessage -> StructuredMessage # min :: StructuredMessage -> StructuredMessage -> StructuredMessage # | |||||
type Rep StructuredMessage Source # | |||||
Defined in Development.IDE.Types.Diagnostics type Rep StructuredMessage = D1 ('MetaData "StructuredMessage" "Development.IDE.Types.Diagnostics" "ghcide-2.11.0.0-IzuGh9ZsoLJF9Sbc2JF8Yt" 'False) (C1 ('MetaCons "NoStructuredMessage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SomeStructuredMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MsgEnvelope GhcMessage)))) |
type IdeResult v = ([FileDiagnostic], Maybe v) Source #
The result of an IDE operation. Warnings and errors are in the Diagnostic, and a value is in the Maybe. For operations that throw an error you expect a non-empty list of diagnostics, at least one of which is an error, and a Nothing. For operations that succeed you expect perhaps some warnings and a Just. For operations that depend on other failing operations you may get empty diagnostics and a Nothing, to indicate this phase throws no fresh errors but still failed.
A rule on a file should only return diagnostics for that given file. It should not propagate diagnostic errors through multiple phases.
data DiagnosticSeverity #
Constructors
DiagnosticSeverity_Error | |
DiagnosticSeverity_Warning | |
DiagnosticSeverity_Information | |
DiagnosticSeverity_Hint |
Instances
FromJSON DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Methods parseJSON :: Value -> Parser DiagnosticSeverity # parseJSONList :: Value -> Parser [DiagnosticSeverity] # | |||||
ToJSON DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Methods toJSON :: DiagnosticSeverity -> Value # toEncoding :: DiagnosticSeverity -> Encoding # toJSONList :: [DiagnosticSeverity] -> Value # toEncodingList :: [DiagnosticSeverity] -> Encoding # omitField :: DiagnosticSeverity -> Bool # | |||||
Generic DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Associated Types
Methods from :: DiagnosticSeverity -> Rep DiagnosticSeverity x # to :: Rep DiagnosticSeverity x -> DiagnosticSeverity # | |||||
Show DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Methods showsPrec :: Int -> DiagnosticSeverity -> ShowS # show :: DiagnosticSeverity -> String # showList :: [DiagnosticSeverity] -> ShowS # | |||||
NFData DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Methods rnf :: DiagnosticSeverity -> () # | |||||
Eq DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Methods (==) :: DiagnosticSeverity -> DiagnosticSeverity -> Bool # (/=) :: DiagnosticSeverity -> DiagnosticSeverity -> Bool # | |||||
Ord DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Methods compare :: DiagnosticSeverity -> DiagnosticSeverity -> Ordering # (<) :: DiagnosticSeverity -> DiagnosticSeverity -> Bool # (<=) :: DiagnosticSeverity -> DiagnosticSeverity -> Bool # (>) :: DiagnosticSeverity -> DiagnosticSeverity -> Bool # (>=) :: DiagnosticSeverity -> DiagnosticSeverity -> Bool # max :: DiagnosticSeverity -> DiagnosticSeverity -> DiagnosticSeverity # min :: DiagnosticSeverity -> DiagnosticSeverity -> DiagnosticSeverity # | |||||
Hashable DiagnosticSeverity | |||||
LspEnum DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity Associated Types
Methods knownValues :: Set DiagnosticSeverity toEnumBaseType :: DiagnosticSeverity -> EnumBaseType DiagnosticSeverity fromEnumBaseType :: EnumBaseType DiagnosticSeverity -> Maybe DiagnosticSeverity | |||||
Pretty DiagnosticSeverity | |||||
HasSeverity Diagnostic (Maybe DiagnosticSeverity) | |||||
Defined in Language.LSP.Protocol.Types.Lens Methods | |||||
type Rep DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity type Rep DiagnosticSeverity = D1 ('MetaData "DiagnosticSeverity" "Language.LSP.Protocol.Internal.Types.DiagnosticSeverity" "lsp-types-2.3.0.1-FBxKf7HSq8k8Km3kag4dAL" 'False) ((C1 ('MetaCons "DiagnosticSeverity_Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DiagnosticSeverity_Warning" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DiagnosticSeverity_Information" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DiagnosticSeverity_Hint" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
type EnumBaseType DiagnosticSeverity | |||||
Defined in Language.LSP.Protocol.Internal.Types.DiagnosticSeverity type EnumBaseType DiagnosticSeverity = UInt |
ideErrorText :: NormalizedFilePath -> Text -> FileDiagnostic Source #
Produce a FileDiagnostic
for the given NormalizedFilePath
with an error message.
ideErrorWithSource :: Maybe Text -> Maybe DiagnosticSeverity -> NormalizedFilePath -> Text -> Maybe (MsgEnvelope GhcMessage) -> FileDiagnostic Source #
ideErrorFromLspDiag :: Diagnostic -> NormalizedFilePath -> Maybe (MsgEnvelope GhcMessage) -> FileDiagnostic Source #
Create a FileDiagnostic
from an existing Diagnostic
for a
specific NormalizedFilePath
.
The optional 'MsgEnvelope GhcMessage' is the original error message
that was used for creating the Diagnostic
.
It is included here, to allow downstream consumers, such as HLS plugins,
to provide LSP features based on the structured error messages.
Additionally, if available, we insert the ghc error code into the
Diagnostic
. These error codes are used in https://errors.haskell.org/
to provide documentation and explanations for error messages.
showDiagnostics :: [FileDiagnostic] -> Text Source #
showDiagnosticsColored :: [FileDiagnostic] -> Text Source #
showGhcCode :: DiagnosticCode -> Text Source #
type IdeResultNoDiagnosticsEarlyCutoff v = (Maybe ByteString, Maybe v) Source #
an IdeResult with a fingerprint
attachReason :: Maybe DiagnosticReason -> Diagnostic -> Diagnostic Source #