chapelure-0.0.1.0: A diagnostics library for Haskell
Safe HaskellNone
LanguageHaskell2010

Chapelure.Types

Synopsis

Documentation

data Diagnostic Source #

Constructors

Diagnostic 

Fields

  • code :: Maybe Text

    Unique diagnostic code that be used to look up more information. Should be globally unique, and documented for easy searching.

  • severity :: Severity

    Diagnostic severity, this may be used by the Report Handler to adapt the formatting of the diagnostic.

  • message :: Maybe DocText

    A short description of the diagnostic. Rendered at the top.

  • help :: Maybe DocText

    Additional free-form text for the poor bastard at the end of it all. Rendered at the bottom

  • link :: Maybe Text

    Link to visit for a more detailed explanation. Can make use of the $sel:code:Diagnostic component.

  • snippets :: Maybe (NonEmptyVector Snippet)

    Contextual snippet to provide relevant source data.

data Severity Source #

Enum used to indicate the severity of a diagnostic. The Report Handlers will use this to adapt the formatting of the diagnostic.

Constructors

Info 
Warning 
Error 

Instances

Instances details
Bounded Severity Source # 
Instance details

Defined in Chapelure.Types

Enum Severity Source # 
Instance details

Defined in Chapelure.Types

Eq Severity Source # 
Instance details

Defined in Chapelure.Types

Show Severity Source # 
Instance details

Defined in Chapelure.Types

Display Severity Source # 
Instance details

Defined in Chapelure.Types

newtype Offset Source #

Wrapper to mark an offset from the beginning of a Highlight.

Constructors

Offset Word 

Instances

Instances details
Enum Offset Source # 
Instance details

Defined in Chapelure.Types

Eq Offset Source # 
Instance details

Defined in Chapelure.Types

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Ord Offset Source # 
Instance details

Defined in Chapelure.Types

Show Offset Source # 
Instance details

Defined in Chapelure.Types

Generic Offset Source # 
Instance details

Defined in Chapelure.Types

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Pretty Offset Source # 
Instance details

Defined in Chapelure.Types

Methods

pretty :: Offset -> Doc ann #

prettyList :: [Offset] -> Doc ann #

type Rep Offset Source # 
Instance details

Defined in Chapelure.Types

type Rep Offset = D1 ('MetaData "Offset" "Chapelure.Types" "chapelure-0.0.1.0-inplace" 'True) (C1 ('MetaCons "Offset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

newtype Line Source #

Wrapper that represents a line in a Diagnostic report

Constructors

Line Word 

Instances

Instances details
Enum Line Source # 
Instance details

Defined in Chapelure.Types

Methods

succ :: Line -> Line #

pred :: Line -> Line #

toEnum :: Int -> Line #

fromEnum :: Line -> Int #

enumFrom :: Line -> [Line] #

enumFromThen :: Line -> Line -> [Line] #

enumFromTo :: Line -> Line -> [Line] #

enumFromThenTo :: Line -> Line -> Line -> [Line] #

Eq Line Source # 
Instance details

Defined in Chapelure.Types

Methods

(==) :: Line -> Line -> Bool #

(/=) :: Line -> Line -> Bool #

Ord Line Source # 
Instance details

Defined in Chapelure.Types

Methods

compare :: Line -> Line -> Ordering #

(<) :: Line -> Line -> Bool #

(<=) :: Line -> Line -> Bool #

(>) :: Line -> Line -> Bool #

(>=) :: Line -> Line -> Bool #

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Show Line Source # 
Instance details

Defined in Chapelure.Types

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Generic Line Source # 
Instance details

Defined in Chapelure.Types

Associated Types

type Rep Line :: Type -> Type #

Methods

from :: Line -> Rep Line x #

to :: Rep Line x -> Line #

Pretty Line Source # 
Instance details

Defined in Chapelure.Types

Methods

pretty :: Line -> Doc ann #

prettyList :: [Line] -> Doc ann #

Display Line Source # 
Instance details

Defined in Chapelure.Types

type Rep Line Source # 
Instance details

Defined in Chapelure.Types

type Rep Line = D1 ('MetaData "Line" "Chapelure.Types" "chapelure-0.0.1.0-inplace" 'True) (C1 ('MetaCons "Line" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

newtype Column Source #

Wrapper that represents a column in a Diagnostic report

Constructors

Column Word 

Instances

Instances details
Enum Column Source # 
Instance details

Defined in Chapelure.Types

Eq Column Source # 
Instance details

Defined in Chapelure.Types

Methods

(==) :: Column -> Column -> Bool #

(/=) :: Column -> Column -> Bool #

Ord Column Source # 
Instance details

Defined in Chapelure.Types

Show Column Source # 
Instance details

Defined in Chapelure.Types

Generic Column Source # 
Instance details

Defined in Chapelure.Types

Associated Types

type Rep Column :: Type -> Type #

Methods

from :: Column -> Rep Column x #

to :: Rep Column x -> Column #

Pretty Column Source # 
Instance details

Defined in Chapelure.Types

Methods

pretty :: Column -> Doc ann #

prettyList :: [Column] -> Doc ann #

Display Column Source # 
Instance details

Defined in Chapelure.Types

type Rep Column Source # 
Instance details

Defined in Chapelure.Types

type Rep Column = D1 ('MetaData "Column" "Chapelure.Types" "chapelure-0.0.1.0-inplace" 'True) (C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data Snippet Source #

A datatype holding a message, some source data and a span to highlight.

Constructors

Snippet 

Fields

Instances

Instances details
Show Snippet Source # 
Instance details

Defined in Chapelure.Types

Generic Snippet Source # 
Instance details

Defined in Chapelure.Types

Associated Types

type Rep Snippet :: Type -> Type #

Methods

from :: Snippet -> Rep Snippet x #

to :: Rep Snippet x -> Snippet #

type Rep Snippet Source # 
Instance details

Defined in Chapelure.Types

data Highlight Source #

A piece of source data that is shown when reporting an error. Pointers on a source are always on a single line.

Constructors

Highlight 

Fields

Instances

Instances details
Show Highlight Source # 
Instance details

Defined in Chapelure.Types

Generic Highlight Source # 
Instance details

Defined in Chapelure.Types

Associated Types

type Rep Highlight :: Type -> Type #

type Rep Highlight Source # 
Instance details

Defined in Chapelure.Types

type Rep Highlight = D1 ('MetaData "Highlight" "Chapelure.Types" "chapelure-0.0.1.0-inplace" 'False) (C1 ('MetaCons "Highlight" 'PrefixI 'True) (S1 ('MetaSel ('Just "label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DocText)) :*: S1 ('MetaSel ('Just "spans") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmptyVector (Line, Column, Column)))))