module Control.Arrow.ArrowExc
( ArrowExc(..)
)
where
import Control.Arrow
import Control.Arrow.ArrowIO
import Control.Exception ( SomeException
)
class (Arrow a, ArrowChoice a, ArrowZero a, ArrowIO a) => ArrowExc a where
tryA :: a b c -> a b (Either SomeException c)
catchA :: a b c -> a SomeException c -> a b c
catchA a b c
f a SomeException c
h = a b c -> a b (Either SomeException c)
forall (a :: * -> * -> *) b c.
ArrowExc a =>
a b c -> a b (Either SomeException c)
tryA a b c
f
a b (Either SomeException c)
-> a (Either SomeException c) c -> a b c
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>>
( a SomeException c
h a SomeException c -> a c c -> a (Either SomeException c) c
forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| a c c
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA )