module Effectful.Error.Static
(
Error
, runError
, runErrorWith
, runErrorNoCallStack
, runErrorNoCallStackWith
, throwError
, catchError
, handleError
, tryError
, HasCallStack
, CallStack
, getCallStack
, prettyCallStack
) where
import Control.Exception
import GHC.Stack
import Effectful
import Effectful.Dispatch.Static
import Effectful.Dispatch.Static.Primitive
import Effectful.Internal.Utils
data Error e :: Effect
type instance DispatchOf (Error e) = Static NoSideEffects
newtype instance StaticRep (Error e) = Error ErrorId
runError
:: forall e es a
. Eff (Error e : es) a
-> Eff es (Either (CallStack, e) a)
runError :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
runError Eff (Error e : es) a
m = forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Env es -> IO a) -> Eff es a
unsafeEff forall a b. (a -> b) -> a -> b
$ \Env es
es0 -> forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
unmask -> do
ErrorId
eid <- IO ErrorId
newErrorId
Env (Error e : es)
es <- forall (e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
EffectRep (DispatchOf e) e
-> Relinker (EffectRep (DispatchOf e)) e
-> Env es
-> IO (Env (e : es))
consEnv (forall e. ErrorId -> StaticRep (Error e)
Error @e ErrorId
eid) forall (rep :: ((Type -> Type) -> Type -> Type) -> Type)
(e :: (Type -> Type) -> Type -> Type).
Relinker rep e
dummyRelinker Env es
es0
Either (CallStack, e) a
r <- (IO a -> IO a)
-> ErrorId -> Env (Error e : es) -> IO (Either (CallStack, e) a)
tryErrorIO forall a. IO a -> IO a
unmask ErrorId
eid Env (Error e : es)
es forall a b. IO a -> IO b -> IO a
`onException` forall (e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
Env (e : es) -> IO ()
unconsEnv Env (Error e : es)
es
forall (e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
Env (e : es) -> IO ()
unconsEnv Env (Error e : es)
es
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Either (CallStack, e) a
r
where
tryErrorIO :: (IO a -> IO a)
-> ErrorId -> Env (Error e : es) -> IO (Either (CallStack, e) a)
tryErrorIO IO a -> IO a
unmask ErrorId
eid Env (Error e : es)
es = forall e a. Exception e => IO a -> IO (Either e a)
try (IO a -> IO a
unmask forall a b. (a -> b) -> a -> b
$ forall (es :: [(Type -> Type) -> Type -> Type]) a.
Eff es a -> Env es -> IO a
unEff Eff (Error e : es) a
m Env (Error e : es)
es) forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right a
a -> forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right a
a
Left SomeException
ex -> forall e r.
SomeException -> ErrorId -> (CallStack -> e -> r) -> IO r -> IO r
tryHandler SomeException
ex ErrorId
eid (\CallStack
cs e
e -> forall a b. a -> Either a b
Left (CallStack
cs, e
e))
forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO SomeException
ex
runErrorWith
:: (CallStack -> e -> Eff es a)
-> Eff (Error e : es) a
-> Eff es a
runErrorWith :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(CallStack -> e -> Eff es a) -> Eff (Error e : es) a -> Eff es a
runErrorWith CallStack -> e -> Eff es a
handler Eff (Error e : es) a
m = forall e (es :: [(Type -> Type) -> Type -> Type]) a.
Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
runError Eff (Error e : es) a
m forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left (CallStack
cs, e
e) -> CallStack -> e -> Eff es a
handler CallStack
cs e
e
Right a
a -> forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
a
runErrorNoCallStack
:: forall e es a
. Eff (Error e : es) a
-> Eff es (Either e a)
runErrorNoCallStack :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
Eff (Error e : es) a -> Eff es (Either e a)
runErrorNoCallStack = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) forall a b. b -> Either a b
Right) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (es :: [(Type -> Type) -> Type -> Type]) a.
Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
runError
runErrorNoCallStackWith
:: (e -> Eff es a)
-> Eff (Error e : es) a
-> Eff es a
runErrorNoCallStackWith :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(e -> Eff es a) -> Eff (Error e : es) a -> Eff es a
runErrorNoCallStackWith e -> Eff es a
handler Eff (Error e : es) a
m = forall e (es :: [(Type -> Type) -> Type -> Type]) a.
Eff (Error e : es) a -> Eff es (Either e a)
runErrorNoCallStack Eff (Error e : es) a
m forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left e
e -> e -> Eff es a
handler e
e
Right a
a -> forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
a
throwError
:: forall e es a. (HasCallStack, Error e :> es)
=> e
-> Eff es a
throwError :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, Error e :> es) =>
e -> Eff es a
throwError e
e = forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Env es -> IO a) -> Eff es a
unsafeEff forall a b. (a -> b) -> a -> b
$ \Env es
es -> do
Error ErrorId
eid <- forall (e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
(e :> es) =>
Env es -> IO (EffectRep (DispatchOf e) e)
getEnv @(Error e) Env es
es
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ ErrorId -> CallStack -> Any -> ErrorWrapper
ErrorWrapper ErrorId
eid HasCallStack => CallStack
callStack (forall a. a -> Any
toAny e
e)
catchError
:: forall e es a. Error e :> es
=> Eff es a
-> (CallStack -> e -> Eff es a)
-> Eff es a
catchError :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(Error e :> es) =>
Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
catchError Eff es a
m CallStack -> e -> Eff es a
handler = forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Env es -> IO a) -> Eff es a
unsafeEff forall a b. (a -> b) -> a -> b
$ \Env es
es -> do
Error ErrorId
eid <- forall (e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]).
(e :> es) =>
Env es -> IO (EffectRep (DispatchOf e) e)
getEnv @(Error e) Env es
es
forall a e. ErrorId -> IO a -> (CallStack -> e -> IO a) -> IO a
catchErrorIO ErrorId
eid (forall (es :: [(Type -> Type) -> Type -> Type]) a.
Eff es a -> Env es -> IO a
unEff Eff es a
m Env es
es) forall a b. (a -> b) -> a -> b
$ \CallStack
cs e
e -> do
forall (es :: [(Type -> Type) -> Type -> Type]) a.
Eff es a -> Env es -> IO a
unEff (CallStack -> e -> Eff es a
handler CallStack
cs e
e) Env es
es
handleError
:: forall e es a. Error e :> es
=> (CallStack -> e -> Eff es a)
-> Eff es a
-> Eff es a
handleError :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(Error e :> es) =>
(CallStack -> e -> Eff es a) -> Eff es a -> Eff es a
handleError = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(Error e :> es) =>
Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
catchError
tryError
:: forall e es a. Error e :> es
=> Eff es a
-> Eff es (Either (CallStack, e) a)
tryError :: forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(Error e :> es) =>
Eff es a -> Eff es (Either (CallStack, e) a)
tryError Eff es a
m = (forall a b. b -> Either a b
Right forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Eff es a
m) forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(Error e :> es) =>
Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
`catchError` \CallStack
es e
e -> forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (CallStack
es, e
e)
newtype ErrorId = ErrorId Unique
deriving ErrorId -> ErrorId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorId -> ErrorId -> Bool
$c/= :: ErrorId -> ErrorId -> Bool
== :: ErrorId -> ErrorId -> Bool
$c== :: ErrorId -> ErrorId -> Bool
Eq
newErrorId :: IO ErrorId
newErrorId :: IO ErrorId
newErrorId = Unique -> ErrorId
ErrorId forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Unique
newUnique
tryHandler
:: SomeException
-> ErrorId
-> (CallStack -> e -> r)
-> IO r
-> IO r
tryHandler :: forall e r.
SomeException -> ErrorId -> (CallStack -> e -> r) -> IO r -> IO r
tryHandler SomeException
ex ErrorId
eid0 CallStack -> e -> r
handler IO r
next = case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
ex of
Just (ErrorWrapper ErrorId
eid CallStack
cs Any
e)
| ErrorId
eid0 forall a. Eq a => a -> a -> Bool
== ErrorId
eid -> forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ CallStack -> e -> r
handler CallStack
cs (forall a. Any -> a
fromAny Any
e)
| Bool
otherwise -> IO r
next
Maybe ErrorWrapper
Nothing -> IO r
next
data ErrorWrapper = ErrorWrapper !ErrorId CallStack Any
instance Show ErrorWrapper where
showsPrec :: Int -> ErrorWrapper -> ShowS
showsPrec Int
p (ErrorWrapper ErrorId
_ CallStack
cs Any
_)
= (String
"Effectful.Error.Static.ErrorWrapper\n\n" forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"If you see this, most likely there is a stray 'Async' action that\n" forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"outlived the scope of the 'Error' effect, was interacted with and threw\n" forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"an error to the parent thread. If that scenario sounds unlikely, please\n" forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"file a ticket at https://github.com/haskell-effectful/effectful/issues.\n\n" forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (CallStack -> String
prettyCallStack CallStack
cs)
instance Exception ErrorWrapper
catchErrorIO :: ErrorId -> IO a -> (CallStack -> e -> IO a) -> IO a
catchErrorIO :: forall a e. ErrorId -> IO a -> (CallStack -> e -> IO a) -> IO a
catchErrorIO ErrorId
eid IO a
m CallStack -> e -> IO a
handler = do
IO a
m forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \err :: ErrorWrapper
err@(ErrorWrapper ErrorId
etag CallStack
cs Any
e) -> do
if ErrorId
eid forall a. Eq a => a -> a -> Bool
== ErrorId
etag
then CallStack -> e -> IO a
handler CallStack
cs (forall a. Any -> a
fromAny Any
e)
else forall e a. Exception e => e -> IO a
throwIO ErrorWrapper
err