| Portability | non-portable | 
|---|---|
| Stability | experimental | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
Text.Trifecta.Diagnostic
Description
- data Diagnostic m = Diagnostic !(Either String Rendering) !DiagnosticLevel m [Diagnostic m]
- class Renderable t where
- class Source t
- rendering :: Source s => Delta -> s -> Rendering
- renderingCaret :: Delta -> ByteString -> Rendering
- data Caret = Caret !Delta !ByteString
- data Careted a = a :^ Caret
- data Span = Span !Delta !Delta !ByteString
- data Spanned a = a :~ Span
- data  Fixit  = Fixit {- fixitSpan :: !Span
- fixitReplacement :: !ByteString
 
- data Rendered a = a :@ Rendering
- class Monad m => MonadDiagnostic e m | m -> e where- throwDiagnostic :: Diagnostic e -> m a
- logDiagnostic :: Diagnostic e -> m ()
 
- panic, err, fatal :: (MonadParser m, MonadDiagnostic e m) => [Diagnostic e] -> e -> m a
- panicAt, errAt, fatalAt :: MonadDiagnostic e m => [Diagnostic e] -> e -> Rendering -> m a
- warn, note :: (MonadParser m, MonadDiagnostic e m) => [Diagnostic e] -> e -> m ()
- warnAt, noteAt :: MonadDiagnostic e m => [Diagnostic e] -> e -> Rendering -> m ()
- verbose :: (MonadParser m, MonadDiagnostic e m) => Int -> [Diagnostic e] -> e -> m ()
- verboseAt :: MonadDiagnostic e m => Int -> [Diagnostic e] -> e -> Rendering -> m ()
- data DiagnosticLevel
Diagnostics
data Diagnostic m Source
Constructors
| Diagnostic !(Either String Rendering) !DiagnosticLevel m [Diagnostic m] | 
Instances
| Functor Diagnostic | |
| Typeable1 Diagnostic | |
| Foldable Diagnostic | |
| Traversable Diagnostic | |
| Comonad Diagnostic | |
| Extend Diagnostic | |
| Foldable1 Diagnostic | |
| Traversable1 Diagnostic | |
| Show m => Show (Diagnostic m) | |
| (Typeable m, Show m) => Exception (Diagnostic m) | |
| Pretty m => Pretty (Diagnostic m) | |
| PrettyTerm m => PrettyTerm (Diagnostic m) | |
| HasBytes (Diagnostic m) | |
| HasDelta (Diagnostic m) | |
| Highlightable (Diagnostic e) | |
| Renderable (Diagnostic m) | 
Rendering
class Renderable t whereSource
Instances
renderingCaret :: Delta -> ByteString -> RenderingSource
 In file included from baz.c:9
 In file included from bar.c:4
 foo.c:8:36: note
 int main(int argc, char ** argv) { int; }
                                    ^
Constructors
| Caret !Delta !ByteString | 
Instances
| Functor Careted | |
| Foldable Careted | |
| Traversable Careted | |
| Comonad Careted | |
| Extend Careted | |
| Foldable1 Careted | |
| Traversable1 Careted | |
| Eq a => Eq (Careted a) | |
| Ord a => Ord (Careted a) | |
| Show a => Show (Careted a) | |
| Hashable a => Hashable (Careted a) | |
| HasBytes (Careted a) | |
| HasDelta (Careted a) | |
| Renderable (Careted a) | |
| Reducer (Careted a) Rendering | 
Constructors
| Span !Delta !Delta !ByteString | 
Instances
| Functor Spanned | |
| Foldable Spanned | |
| Traversable Spanned | |
| Comonad Spanned | |
| Extend Spanned | |
| Apply Spanned | |
| Foldable1 Spanned | |
| Traversable1 Spanned | |
| Bind Spanned | |
| Eq a => Eq (Spanned a) | |
| Ord a => Ord (Spanned a) | |
| Show a => Show (Spanned a) | |
| Hashable a => Hashable (Spanned a) | |
| Renderable (Spanned a) | |
| Reducer (Spanned a) Rendering | 
Constructors
| Fixit | |
| Fields 
 | |
Emitting diagnostics
class Monad m => MonadDiagnostic e m | m -> e whereSource
Instances
| MonadDiagnostic e m => MonadDiagnostic e (IdentityT m) | |
| MonadDiagnostic e m => MonadDiagnostic e (Language m) | |
| MonadDiagnostic e m => MonadDiagnostic e (Literate m) | |
| MonadDiagnostic e m => MonadDiagnostic e (Layout m) | |
| (MonadDiagnostic e m, Monoid w) => MonadDiagnostic e (WriterT w m) | |
| (MonadDiagnostic e m, Monoid w) => MonadDiagnostic e (WriterT w m) | |
| MonadDiagnostic e m => MonadDiagnostic e (ReaderT r m) | |
| MonadDiagnostic e m => MonadDiagnostic e (StateT s m) | |
| MonadDiagnostic e m => MonadDiagnostic e (StateT s m) | |
| MonadDiagnostic e (Parser r e) | |
| (MonadDiagnostic e m, Monoid w) => MonadDiagnostic e (RWST r w s m) | |
| (MonadDiagnostic e m, Monoid w) => MonadDiagnostic e (RWST r w s m) | 
panic, err, fatal :: (MonadParser m, MonadDiagnostic e m) => [Diagnostic e] -> e -> m aSource
panicAt, errAt, fatalAt :: MonadDiagnostic e m => [Diagnostic e] -> e -> Rendering -> m aSource
warn, note :: (MonadParser m, MonadDiagnostic e m) => [Diagnostic e] -> e -> m ()Source
warnAt, noteAt :: MonadDiagnostic e m => [Diagnostic e] -> e -> Rendering -> m ()Source
verbose :: (MonadParser m, MonadDiagnostic e m) => Int -> [Diagnostic e] -> e -> m ()Source
verboseAt :: MonadDiagnostic e m => Int -> [Diagnostic e] -> e -> Rendering -> m ()Source
Diagnostic Levels
data DiagnosticLevel Source
The severity of an error (or message)
Constructors
| Verbose !Int | a comment we should only show to the excessively curious | 
| Note | a comment | 
| Warning | a warning, computation continues | 
| Error | a user specified error | 
| Fatal | a user specified fatal error | 
| Panic | a non-maskable death sentence thrown by the parser itself | 
Instances
| Eq DiagnosticLevel | |
| Ord DiagnosticLevel | |
| Read DiagnosticLevel | |
| Show DiagnosticLevel | |
| Semigroup DiagnosticLevel | Compute the maximum of two diagnostic levels | 
| Pretty DiagnosticLevel | |
| PrettyTerm DiagnosticLevel | pretty print as a color coded description |