| 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
- newtype TabSize = TabSize Int
- data WithUnicode
- 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 => WithUnicode -> TabSize -> Diagnostic msg -> Doc (Annotation ann)
- prettyDiagnostic' :: WithUnicode -> TabSize -> Diagnostic (Doc ann) -> Doc (Annotation ann)
- printDiagnostic :: (MonadIO m, Pretty msg) => Handle -> WithUnicode -> TabSize -> Style ann -> Diagnostic msg -> m ()
- printDiagnostic' :: MonadIO m => Handle -> WithUnicode -> TabSize -> Style ann -> Diagnostic (Doc ann) -> m ()
- addFile :: Diagnostic msg -> FilePath -> String -> Diagnostic msg
- addReport :: Diagnostic msg -> Report msg -> Diagnostic msg
- diagnosticToJson :: ToJSON msg => Diagnostic msg -> ByteString
Re-exports
data WithUnicode Source #
Constructors
| WithoutUnicode | |
| WithUnicode | 
data Diagnostic msg Source #
The data type for diagnostic containing messages of an abstract type.
Users can use mempty to create a new empty diagnostic, and addFile and
   addReport to alter its internal state.
Instances
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 | |
| => WithUnicode | Should we use unicode when printing paths? | 
| -> TabSize | The number of spaces each TAB character will span. | 
| -> Diagnostic msg | The diagnostic to print. | 
| -> Doc (Annotation ann) | 
Pretty prints a Diagnostic into a Document 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
| :: WithUnicode | Should we use unicode when printing paths? | 
| -> TabSize | The number of spaces each TAB character will span. | 
| -> Diagnostic (Doc ann) | The diagnostic to print. | 
| -> Doc (Annotation ann) | 
Like prettyDiagnostic except that instead of requiring a pretty
 instance for messages, this allows passing in your own Doc. Custom
 annotations are retained in OtherStyle
Arguments
| :: (MonadIO m, Pretty msg) | |
| => Handle | The handle onto which to output the diagnostic. | 
| -> WithUnicode | Should we print with unicode characters? | 
| -> TabSize | The number of spaces each TAB character will span. | 
| -> Style ann | The style in which to output the diagnostic. | 
| -> Diagnostic msg | The diagnostic to output. | 
| -> m () | 
Prints a Diagnostic onto a specific Handle.
Arguments
| :: MonadIO m | |
| => Handle | The handle onto which to output the diagnostic. | 
| -> WithUnicode | Should we print with unicode characters? | 
| -> TabSize | The number of spaces each TAB character will span. | 
| -> Style ann | The style in which to output the diagnostic. | 
| -> Diagnostic (Doc ann) | The diagnostic to output. | 
| -> m () | 
Like printDiagnostic except that instead of requiring a pretty
 instance for messages, this allows passing in your own Doc.
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.