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

Error.Diagnose.Report

Contents

Description

 
Synopsis

Re-exports

data Note msg Source #

A note is a piece of information that is found at the end of a report.

Constructors

Note msg

A note, which is meant to give valuable information related to the encountered error.

Hint msg

A hint, to propose potential fixes or help towards fixing the issue.

Instances

Instances details
Foldable Note Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

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

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

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

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

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

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

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

null :: Note a -> Bool Source #

length :: Note a -> Int Source #

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

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

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

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

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

Traversable Note Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

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

Functor Note Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

Defined in Error.Diagnose.Report.Internal

IsString msg => IsString (Note msg) Source #

Constructs a Note from the given message as a literal string.

Instance details

Defined in Error.Diagnose.Report.Internal

Methods

fromString :: String -> Note msg Source #

Show msg => Show (Note msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

showsPrec :: Int -> Note msg -> ShowS Source #

show :: Note msg -> String Source #

showList :: [Note msg] -> ShowS Source #

Eq msg => Eq (Note msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

(==) :: Note msg -> Note msg -> Bool Source #

(/=) :: Note msg -> Note msg -> Bool Source #

Ord msg => Ord (Note msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

compare :: Note msg -> Note msg -> Ordering Source #

(<) :: Note msg -> Note msg -> Bool Source #

(<=) :: Note msg -> Note msg -> Bool Source #

(>) :: Note msg -> Note msg -> Bool Source #

(>=) :: Note msg -> Note msg -> Bool Source #

max :: Note msg -> Note msg -> Note msg Source #

min :: Note msg -> Note msg -> Note msg Source #

data Marker msg Source #

The type of markers with abstract message type, shown under code lines.

Constructors

This msg

A red or yellow marker under source code, marking important parts of the code.

Where msg

A blue marker symbolizing additional information.

Maybe msg

A magenta marker to report potential fixes.

Blank

An empty marker, whose sole purpose is to include a line of code in the report without markers under.

Instances

Instances details
Foldable Marker Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

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

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

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

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

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

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

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

null :: Marker a -> Bool Source #

length :: Marker a -> Int Source #

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

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

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

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

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

Traversable Marker Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

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

Functor Marker Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

Eq msg => Eq (Marker msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

(==) :: Marker msg -> Marker msg -> Bool Source #

(/=) :: Marker msg -> Marker msg -> Bool Source #

Ord msg => Ord (Marker msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

compare :: Marker msg -> Marker msg -> Ordering Source #

(<) :: Marker msg -> Marker msg -> Bool Source #

(<=) :: Marker msg -> Marker msg -> Bool Source #

(>) :: Marker msg -> Marker msg -> Bool Source #

(>=) :: Marker msg -> Marker msg -> Bool Source #

max :: Marker msg -> Marker msg -> Marker msg Source #

min :: Marker msg -> Marker msg -> Marker msg Source #

data Report msg where Source #

The type of diagnostic reports with abstract message type.

Bundled Patterns

pattern Warn :: Maybe msg -> msg -> [(Position, Marker msg)] -> [Note msg] -> Report msg

Pattern synonym for a warning report.

pattern Err :: Maybe msg -> msg -> [(Position, Marker msg)] -> [Note msg] -> Report msg

Pattern synonym for an error report.

Instances

Instances details
Foldable Report Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

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

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

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

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

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

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

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

null :: Report a -> Bool Source #

length :: Report a -> Int Source #

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

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

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

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

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

Traversable Report Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

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

Functor Report Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

Defined in Error.Diagnose.Report.Internal

Monoid msg => Monoid (Report msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

mempty :: Report msg Source #

mappend :: Report msg -> Report msg -> Report msg Source #

mconcat :: [Report msg] -> Report msg Source #

Semigroup msg => Semigroup (Report msg) Source # 
Instance details

Defined in Error.Diagnose.Report.Internal

Methods

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

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

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

warn Source #

Arguments

:: Maybe msg

An optional error code to be shown right next to "error" or "warning".

-> msg

The report message, shown at the very top.

-> [(Position, Marker msg)]

A list associating positions with markers.

-> [Note msg]

A possibly mempty list of hints to add at the end of the report.

-> Report msg 

Deprecated: warn is deprecated. Use Warn instead.

Constructs a warning or an error report.

err Source #

Arguments

:: Maybe msg

An optional error code to be shown right next to "error" or "warning".

-> msg

The report message, shown at the very top.

-> [(Position, Marker msg)]

A list associating positions with markers.

-> [Note msg]

A possibly mempty list of hints to add at the end of the report.

-> Report msg 

Deprecated: err is deprecated. Use Err instead.

Constructs a warning or an error report.

warningToError :: Report msg -> Report msg Source #

Transforms a warning report into an error report.

errorToWarning :: Report msg -> Report msg Source #

Transforms an error report into a warning report.