diagnose-2.5.1: Beautiful error reporting done easily
Copyright(c) Mesabloo 2021-2022
LicenseBSD3
Stabilityexperimental
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Error.Diagnose.Diagnostic

Contents

Description

 
Synopsis

Re-exports

newtype TabSize Source #

Constructors

TabSize Int 

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

Instances details
Foldable Diagnostic Source # 
Instance details

Defined in Error.Diagnose.Diagnostic.Internal

Methods

fold :: Monoid m => Diagnostic m -> m Source #

foldMap :: Monoid m => (a -> m) -> Diagnostic a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Diagnostic a -> m Source #

foldr :: (a -> b -> b) -> b -> Diagnostic a -> b Source #

foldr' :: (a -> b -> b) -> b -> Diagnostic a -> b Source #

foldl :: (b -> a -> b) -> b -> Diagnostic a -> b Source #

foldl' :: (b -> a -> b) -> b -> Diagnostic a -> b Source #

foldr1 :: (a -> a -> a) -> Diagnostic a -> a Source #

foldl1 :: (a -> a -> a) -> Diagnostic a -> a Source #

toList :: Diagnostic a -> [a] Source #

null :: Diagnostic a -> Bool Source #

length :: Diagnostic a -> Int Source #

elem :: Eq a => a -> Diagnostic a -> Bool Source #

maximum :: Ord a => Diagnostic a -> a Source #

minimum :: Ord a => Diagnostic a -> a Source #

sum :: Num a => Diagnostic a -> a Source #

product :: Num a => Diagnostic a -> a Source #

Traversable Diagnostic Source # 
Instance details

Defined in Error.Diagnose.Diagnostic.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Diagnostic a -> f (Diagnostic b) Source #

sequenceA :: Applicative f => Diagnostic (f a) -> f (Diagnostic a) Source #

mapM :: Monad m => (a -> m b) -> Diagnostic a -> m (Diagnostic b) Source #

sequence :: Monad m => Diagnostic (m a) -> m (Diagnostic a) Source #

Functor Diagnostic Source # 
Instance details

Defined in Error.Diagnose.Diagnostic.Internal

Methods

fmap :: (a -> b) -> Diagnostic a -> Diagnostic b Source #

(<$) :: a -> Diagnostic b -> Diagnostic a Source #

ToJSON msg => ToJSON (Diagnostic msg) Source # 
Instance details

Defined in Error.Diagnose.Diagnostic.Internal

Monoid (Diagnostic msg) Source # 
Instance details

Defined in Error.Diagnose.Diagnostic.Internal

Semigroup (Diagnostic msg) Source # 
Instance details

Defined in Error.Diagnose.Diagnostic.Internal

Methods

(<>) :: Diagnostic msg -> Diagnostic msg -> Diagnostic msg Source #

sconcat :: NonEmpty (Diagnostic msg) -> Diagnostic msg Source #

stimes :: Integral b => b -> Diagnostic msg -> Diagnostic msg Source #

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.

prettyDiagnostic Source #

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)

prettyDiagnostic' Source #

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

printDiagnostic Source #

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.

printDiagnostic' Source #

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.

addFile Source #

Arguments

:: Diagnostic msg 
-> FilePath

The path to the file.

-> String

The content of the file as a single string, where lines are ended by \n.

-> Diagnostic msg 

Inserts a new referenceable file within the diagnostic.

addReport Source #

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.