{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE StrictData #-}
module Data.VCS.Ignore.Types
( VCSIgnoreError(..)
, fromVCSIgnoreError
, toVCSIgnoreError
)
where
import Control.Exception ( Exception(..)
, SomeException
)
import Data.Typeable ( cast )
data VCSIgnoreError = forall e . Exception e => VCSIgnoreError e
instance Show VCSIgnoreError where
show :: VCSIgnoreError -> String
show (VCSIgnoreError e
e) = e -> String
forall a. Show a => a -> String
show e
e
instance Exception VCSIgnoreError where
displayException :: VCSIgnoreError -> String
displayException (VCSIgnoreError e
e) = e -> String
forall e. Exception e => e -> String
displayException e
e
fromVCSIgnoreError :: Exception e
=> SomeException
-> Maybe e
fromVCSIgnoreError :: SomeException -> Maybe e
fromVCSIgnoreError SomeException
e = do
VCSIgnoreError e
e' <- SomeException -> Maybe VCSIgnoreError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e
e -> Maybe e
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
e'
toVCSIgnoreError :: Exception e
=> e
-> SomeException
toVCSIgnoreError :: e -> SomeException
toVCSIgnoreError = VCSIgnoreError -> SomeException
forall e. Exception e => e -> SomeException
toException (VCSIgnoreError -> SomeException)
-> (e -> VCSIgnoreError) -> e -> SomeException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> VCSIgnoreError
forall e. Exception e => e -> VCSIgnoreError
VCSIgnoreError