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

Error.Diagnose.Style

Description

 
Synopsis

Defining new style

data Annotation a Source #

Some annotations as placeholders for colors in a Doc.

Constructors

ThisColor Bool

The color of This markers, depending on whether the report is an error report or a warning report.

MaybeColor

The color of Maybe markers.

WhereColor

The color of Where markers.

HintColor

The color for hints.

Note that the beginning Hint: text will always be in bold.

FileColor

The color for file names.

RuleColor

The color of the rule separating the code/markers from the line numbers.

KindColor Bool

The color of the [error]/[warning] at the top, depending on whether this is an error or warning report.

NoLineColor

The color in which to output the line information when the file was not found.

MarkerStyle (Annotation a)

Additional style to apply to marker rules (e.g. bold) on top of some already processed color annotation.

CodeStyle

The color of the code when no marker is present.

OtherStyle a

Something else, could be provided by the user

Instances

Instances details
Foldable Annotation Source # 
Instance details

Defined in Error.Diagnose.Style

Methods

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

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

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

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

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

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

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

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

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

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

null :: Annotation a -> Bool Source #

length :: Annotation a -> Int Source #

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

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

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

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

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

Traversable Annotation Source # 
Instance details

Defined in Error.Diagnose.Style

Methods

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

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

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

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

Functor Annotation Source # 
Instance details

Defined in Error.Diagnose.Style

Methods

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

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

Generic (Annotation a) Source # 
Instance details

Defined in Error.Diagnose.Style

Associated Types

type Rep (Annotation a) :: Type -> Type Source #

Methods

from :: Annotation a -> Rep (Annotation a) x Source #

to :: Rep (Annotation a) x -> Annotation a Source #

Show a => Show (Annotation a) Source # 
Instance details

Defined in Error.Diagnose.Style

Eq a => Eq (Annotation a) Source # 
Instance details

Defined in Error.Diagnose.Style

Ord a => Ord (Annotation a) Source # 
Instance details

Defined in Error.Diagnose.Style

type Rep (Annotation a) Source # 
Instance details

Defined in Error.Diagnose.Style

type Rep (Annotation a) = D1 ('MetaData "Annotation" "Error.Diagnose.Style" "diagnose-2.5.1-inplace" 'False) (((C1 ('MetaCons "ThisColor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "MaybeColor" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WhereColor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HintColor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileColor" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RuleColor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KindColor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "NoLineColor" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MarkerStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Annotation a))) :+: (C1 ('MetaCons "CodeStyle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))))

type Style a = Annotation a -> AnsiStyle Source #

A style is a function which can be applied using reAnnotate.

It transforms a Document containing Annotations into a Document containing color information.

Defining new color styles (one may call them "themes") is actually rather easy.

A Style is a function from an annotated Document to another annotated Document. Note that only the annotation type changes, hence the need of only providing a unidirectional mapping between those.

Annotations are used when creating a Document and are simply placeholders to specify custom colors. AnsiStyle is the concrete annotation to specify custom colors when rendering a Document.

One may define additional styles as follows:

myNewCustomStyle :: Style
myNewCustomStyle = reAnnotate \case
  -- all cases for all annotations

For simplicity's sake, a default style is given as defaultStyle.

Styles

defaultStyle :: Style AnsiStyle Source #

The default style for diagnostics, where:

  • This markers are colored in red for errors and yellow for warnings
  • Where markers are colored in dull blue
  • Maybe markers are colored in magenta
  • Marker rules are of the same color of the marker, but also in bold
  • Hints are output in cyan
  • The left rules are colored in bold black
  • File names are output in dull green
  • The [error]/[warning] at the top is colored in red for errors and yellow for warnings
  • The code is output in normal white

unadornedStyle :: Style a Source #

A style which disregards all annotations