{-# LANGUAGE ExistentialQuantification, StandaloneDeriving #-}
module OAlg.Control.Exception
(
oalgExceptionToException
, oalgExceptionFromException
, SomeOAlgException(..)
, AlgebraicException(..)
, implementation
, Exception(..), throw
)
where
import Control.Exception as E
import Data.Typeable (cast)
data SomeOAlgException = forall e . Exception e => SomeOAlgException e
instance Show SomeOAlgException where
show :: SomeOAlgException -> String
show (SomeOAlgException e
e) = forall a. Show a => a -> String
show e
e
instance Exception SomeOAlgException
oalgExceptionToException :: Exception e => e -> SomeException
oalgExceptionToException :: forall e. Exception e => e -> SomeException
oalgExceptionToException = forall e. Exception e => e -> SomeException
toException forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. Exception e => e -> SomeOAlgException
SomeOAlgException
oalgExceptionFromException :: Exception e => SomeException -> Maybe e
oalgExceptionFromException :: forall e. Exception e => SomeException -> Maybe e
oalgExceptionFromException SomeException
e = do
SomeOAlgException e
a <- forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
a
data AlgebraicException
= AlgebraicException String
| Undefined String
| ImplementationError String
| NoPredecor
| InvalidData String
deriving (Int -> AlgebraicException -> ShowS
[AlgebraicException] -> ShowS
AlgebraicException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlgebraicException] -> ShowS
$cshowList :: [AlgebraicException] -> ShowS
show :: AlgebraicException -> String
$cshow :: AlgebraicException -> String
showsPrec :: Int -> AlgebraicException -> ShowS
$cshowsPrec :: Int -> AlgebraicException -> ShowS
Show)
instance Exception AlgebraicException where
toException :: AlgebraicException -> SomeException
toException = forall e. Exception e => e -> SomeException
oalgExceptionToException
fromException :: SomeException -> Maybe AlgebraicException
fromException = forall e. Exception e => SomeException -> Maybe e
oalgExceptionFromException
implementation :: String
implementation :: String
implementation = String
"implementation"