module Text.Trifecta.Diagnostic.Err
( Err(..)
, knownErr
, fatalErr
) where
import Control.Applicative
import Data.Foldable
import Data.Traversable
import Data.Semigroup
import Data.Functor.Plus
import Text.Trifecta.Diagnostic.Prim
import Text.Trifecta.Diagnostic.Level
import Text.Trifecta.Diagnostic.Rendering.Prim
data Err e
= EmptyErr
| FailErr Rendering String
| PanicErr Rendering String
| Err !(Diagnostic e)
deriving Show
knownErr :: Err e -> Bool
knownErr EmptyErr = False
knownErr _ = True
fatalErr :: Err e -> Bool
fatalErr (Err (Diagnostic _ Panic _ _)) = True
fatalErr (Err (Diagnostic _ Fatal _ _)) = True
fatalErr (PanicErr _ _) = True
fatalErr _ = False
instance Functor Err where
fmap _ EmptyErr = EmptyErr
fmap _ (FailErr r s) = FailErr r s
fmap _ (PanicErr r s) = PanicErr r s
fmap f (Err e) = Err (fmap f e)
instance Foldable Err where
foldMap _ EmptyErr = mempty
foldMap _ FailErr{} = mempty
foldMap _ PanicErr{} = mempty
foldMap f (Err e) = foldMap f e
instance Traversable Err where
traverse _ EmptyErr = pure EmptyErr
traverse _ (FailErr r s) = pure $ FailErr r s
traverse _ (PanicErr r s) = pure $ PanicErr r s
traverse f (Err e) = Err <$> traverse f e
instance Alt Err where
a <!> EmptyErr = a
_ <!> a@(Err (Diagnostic _ Panic _ _)) = a
a@(Err (Diagnostic _ Panic _ _)) <!> _ = a
_ <!> a@PanicErr{} = a
a@PanicErr{} <!> _ = a
_ <!> a@(Err (Diagnostic _ Fatal _ _)) = a
a@(Err (Diagnostic _ Fatal _ _)) <!> _ = a
_ <!> b = b
instance Plus Err where
zero = EmptyErr
instance Semigroup (Err t) where
(<>) = (<!>)
times1p _ = id
instance Monoid (Err t) where
mempty = EmptyErr
mappend = (<!>)