Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Development.IDE.GHC.Error
Synopsis
- diagFromGhcErrorMessages :: Text -> DynFlags -> Bag (MsgEnvelope GhcMessage) -> [FileDiagnostic]
- diagFromErrMsgs :: Text -> DynFlags -> Bag (MsgEnvelope GhcMessage) -> [FileDiagnostic]
- diagFromErrMsg :: Text -> DynFlags -> MsgEnvelope GhcMessage -> [FileDiagnostic]
- diagFromSDocErrMsgs :: Text -> DynFlags -> Bag (MsgEnvelope DecoratedSDoc) -> [FileDiagnostic]
- diagFromSDocErrMsg :: Text -> DynFlags -> MsgEnvelope DecoratedSDoc -> [FileDiagnostic]
- diagFromString :: Text -> DiagnosticSeverity -> SrcSpan -> String -> Maybe (MsgEnvelope GhcMessage) -> [FileDiagnostic]
- diagFromStrings :: Text -> DiagnosticSeverity -> [(SrcSpan, String, Maybe (MsgEnvelope GhcMessage))] -> [FileDiagnostic]
- diagFromGhcException :: Text -> DynFlags -> GhcException -> [FileDiagnostic]
- catchSrcErrors :: DynFlags -> Text -> IO a -> IO (Either [FileDiagnostic] a)
- srcSpanToLocation :: SrcSpan -> Maybe Location
- srcSpanToRange :: SrcSpan -> Maybe Range
- realSrcSpanToRange :: RealSrcSpan -> Range
- realSrcLocToPosition :: RealSrcLoc -> Position
- realSrcSpanToLocation :: RealSrcSpan -> Location
- realSrcSpanToCodePointRange :: RealSrcSpan -> CodePointRange
- realSrcLocToCodePointPosition :: RealSrcLoc -> CodePointPosition
- srcSpanToFilename :: SrcSpan -> Maybe FilePath
- rangeToSrcSpan :: NormalizedFilePath -> Range -> SrcSpan
- rangeToRealSrcSpan :: NormalizedFilePath -> Range -> RealSrcSpan
- positionToRealSrcLoc :: NormalizedFilePath -> Position -> RealSrcLoc
- zeroSpan :: FastString -> RealSrcSpan
- realSpan :: SrcSpan -> Maybe RealSrcSpan
- isInsideSrcSpan :: Position -> SrcSpan -> Bool
- spanContainsRange :: SrcSpan -> Range -> Maybe Bool
- noSpan :: String -> SrcSpan
- toDSeverity :: Severity -> Maybe DiagnosticSeverity
Producing Diagnostic values
diagFromGhcErrorMessages :: Text -> DynFlags -> Bag (MsgEnvelope GhcMessage) -> [FileDiagnostic] Source #
Compatibility function for creating '[FileDiagnostic]' from
a Bag
of GHC error messages.
The function signature changes based on the GHC version.
While this is not desirable, it avoids more CPP statements in code
that implements actual logic.
diagFromErrMsgs :: Text -> DynFlags -> Bag (MsgEnvelope GhcMessage) -> [FileDiagnostic] Source #
diagFromErrMsg :: Text -> DynFlags -> MsgEnvelope GhcMessage -> [FileDiagnostic] Source #
Produce a GHC-style error from a source span and a message.
diagFromSDocErrMsgs :: Text -> DynFlags -> Bag (MsgEnvelope DecoratedSDoc) -> [FileDiagnostic] Source #
diagFromSDocErrMsg :: Text -> DynFlags -> MsgEnvelope DecoratedSDoc -> [FileDiagnostic] Source #
diagFromString :: Text -> DiagnosticSeverity -> SrcSpan -> String -> Maybe (MsgEnvelope GhcMessage) -> [FileDiagnostic] Source #
Produce a GHC-style error from a source span and a message.
diagFromStrings :: Text -> DiagnosticSeverity -> [(SrcSpan, String, Maybe (MsgEnvelope GhcMessage))] -> [FileDiagnostic] Source #
Produce a bag of GHC-style errors (ErrorMessages
) from the given
(optional) locations and message strings.
diagFromGhcException :: Text -> DynFlags -> GhcException -> [FileDiagnostic] Source #
catchSrcErrors :: DynFlags -> Text -> IO a -> IO (Either [FileDiagnostic] a) Source #
Catch the errors thrown by GHC (SourceErrors and compiler-internal exceptions like Panic or InstallationError), and turn them into diagnostics
utilities working with spans
realSrcSpanToCodePointRange :: RealSrcSpan -> CodePointRange Source #
Convert a GHC SrcSpan to CodePointRange see Note [Unicode support]
realSrcLocToCodePointPosition :: RealSrcLoc -> CodePointPosition Source #
Convert a GHC RealSrcLoc to CodePointPosition see Note [Unicode support]
srcSpanToFilename :: SrcSpan -> Maybe FilePath Source #
Extract a file name from a GHC SrcSpan (use message for unhelpful ones) FIXME This may not be an _absolute_ file name, needs fixing.
rangeToSrcSpan :: NormalizedFilePath -> Range -> SrcSpan Source #
Arguments
:: FastString | file path of span |
-> RealSrcSpan |
creates a span with zero length in the filename of the argument passed
utilities working with severities
toDSeverity :: Severity -> Maybe DiagnosticSeverity Source #
Convert a GHC severity to a DAML compiler Severity. Severities below Warning level are dropped (returning Nothing).