{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Control.Eff.ExceptionExtra
( try
, liftRethrow
, runErrorRethrowIO
, liftCatch
, liftCatchEff
, liftTry
, module X
)
where
import Control.Monad ( (>=>) )
import qualified Control.Exception as Exc
import Control.Eff
import Control.Eff.Lift
import Control.Eff.Exception as X
import GHC.Stack
try :: forall e r a . Member (Exc e) r => Eff r a -> Eff r (Either e a)
try e = catchError (Right <$> e) (return . Left)
liftRethrow
:: forall proxy e r a
. (Exc.Exception e, SetMember Lift (Lift IO) r, SetMember Exc (Exc e) r)
=> proxy e
-> IO a
-> Eff r a
liftRethrow _ m = lift (Exc.try m) >>= either (throwError @e) return
runErrorRethrowIO
:: forall e r a
. (Exc.Exception e, SetMember Lift (Lift IO) r)
=> Eff (Exc e ': r) a
-> Eff r a
runErrorRethrowIO = runError >=> either (Exc.throw . Exc.SomeException) return
liftCatch
:: forall e r a
. (HasCallStack, Exc.Exception e, SetMember Lift (Lift IO) r)
=> (e -> a)
-> IO a
-> Eff r a
liftCatch handleE m =
lift (Exc.try m) >>= either (return . handleE) return
liftCatchEff
:: forall e r a
. (SetMember Lift (Lift IO) r, HasCallStack, Exc.Exception e)
=> (e -> Eff r a)
-> IO a
-> Eff r a
liftCatchEff handleE m =
lift (Exc.try m) >>= either handleE return
liftTry
:: forall e r a
. (HasCallStack, Exc.Exception e, SetMember Lift (Lift IO) r)
=> Eff r a
-> Eff r (Either e a)
liftTry m =
(Right <$> m) `catchDynE` (return . Left)