Copyright | (c) Mesabloo 2021-2022 |
---|---|
License | BSD3 |
Stability | experimental |
Portability | Portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Error.Diagnose.Diagnostic
Contents
Description
Synopsis
- stdout :: Handle
- stderr :: Handle
- def :: Default a => a
- data Diagnostic msg
- hasReports :: Diagnostic msg -> Bool
- reportsOf :: Diagnostic msg -> [Report msg]
- warningsToErrors :: Diagnostic msg -> Diagnostic msg
- errorsToWarnings :: Diagnostic msg -> Diagnostic msg
- prettyDiagnostic :: Pretty msg => Bool -> Int -> Diagnostic msg -> Doc Annotation
- printDiagnostic :: (MonadIO m, Pretty msg) => Handle -> Bool -> Bool -> Int -> Style -> Diagnostic msg -> m ()
- addFile :: Diagnostic msg -> FilePath -> String -> Diagnostic msg
- addReport :: Diagnostic msg -> Report msg -> Diagnostic msg
- diagnosticToJson :: ToJSON msg => Diagnostic msg -> ByteString
Re-exports
data Diagnostic msg Source #
The data type for diagnostic containing messages of an abstract type.
The constructors are private, but users can use def
from the Default
typeclass
to create a new empty diagnostic, and addFile
and addReport
to alter its internal state.
Instances
ToJSON msg => ToJSON (Diagnostic msg) Source # | |
Defined in Error.Diagnose.Diagnostic.Internal Methods toJSON :: Diagnostic msg -> Value # toEncoding :: Diagnostic msg -> Encoding # toJSONList :: [Diagnostic msg] -> Value # toEncodingList :: [Diagnostic msg] -> Encoding # | |
Semigroup (Diagnostic msg) Source # | |
Defined in Error.Diagnose.Diagnostic.Internal Methods (<>) :: Diagnostic msg -> Diagnostic msg -> Diagnostic msg # sconcat :: NonEmpty (Diagnostic msg) -> Diagnostic msg # stimes :: Integral b => b -> Diagnostic msg -> Diagnostic msg # | |
Default (Diagnostic msg) Source # | |
Defined in Error.Diagnose.Diagnostic.Internal Methods def :: Diagnostic msg # |
hasReports :: Diagnostic msg -> Bool Source #
Checks whether the given diagnostic has any report or not (if it is effectively empty).
reportsOf :: Diagnostic msg -> [Report msg] Source #
Retrieves the reports for this diagnostic.
warningsToErrors :: Diagnostic msg -> Diagnostic msg Source #
Transforms every warning report in this diagnostic into an error report.
errorsToWarnings :: Diagnostic msg -> Diagnostic msg Source #
Transforms every error report in this diagnostic into a warning report.
Arguments
:: Pretty msg | |
=> Bool | Should we use unicode when printing paths? |
-> Int | The number of spaces each TAB character will span. |
-> Diagnostic msg | The diagnostic to print. |
-> Doc Annotation |
Pretty prints a Diagnostic
into a Doc
ument that can be output using hPutDoc
.
Colors are put by default.
If you do not want these, just unAnnotate
the resulting document like so:
>>>
let doc = unAnnotate (prettyDiagnostic withUnicode tabSize diagnostic)
Changing the style is also rather easy:
>>>
let myCustomStyle :: Style = _
>>>
let doc = myCustomStyle (prettyDiagnostic withUnicode tabSize diagnostic)
Arguments
:: (MonadIO m, Pretty msg) | |
=> Handle | The handle onto which to output the diagnostic. |
-> Bool | Should we print with unicode characters? |
-> Bool |
|
-> Int | The number of spaces each TAB character will span. |
-> Style | The style in which to output the diagnostic. |
-> Diagnostic msg | The diagnostic to output. |
-> m () |
Prints a Diagnostic
onto a specific Handle
.
Arguments
:: Diagnostic msg | |
-> FilePath | The path to the file. |
-> String | The content of the file as a single string, where lines are ended by |
-> Diagnostic msg |
Inserts a new referenceable file within the diagnostic.
Arguments
:: Diagnostic msg | |
-> Report msg | The new report to add to the diagnostic. |
-> Diagnostic msg |
Inserts a new report into a diagnostic.
diagnosticToJson :: ToJSON msg => Diagnostic msg -> ByteString Source #
Creates a JSON object from a diagnostic, containing those fields (only types are indicated):
{ files: { name: string , content: string[] }[] , reports: { kind: 'error' | 'warning' , code: T? , message: T , markers: { kind: 'this' | 'where' | 'maybe' , position: { beginning: { line: int, column: int } , end: { line: int, column: int } , file: string } , message: T }[] , hints: ({ note: T } | { hint: T })[] }[] }
where T
is the type of the JSON representation for the msg
type variable.