{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Polysemy.Error
(
Error (..)
, throw
, catch
, fromEither
, fromEitherM
, fromException
, fromExceptionVia
, fromExceptionSem
, fromExceptionSemVia
, note
, try
, tryJust
, catchJust
, runError
, mapError
, errorToIOFinal
, lowerError
) where
import qualified Control.Exception as X
import Control.Monad
import qualified Control.Monad.Trans.Except as E
import Data.Bifunctor (first)
import Data.Typeable
import Polysemy
import Polysemy.Final
import Polysemy.Internal
import Polysemy.Internal.Union
data Error e m a where
Throw :: e -> Error e m a
Catch :: ∀ e m a. m a -> (e -> m a) -> Error e m a
makeSem ''Error
hush :: Either e a -> Maybe a
hush (Right a) = Just a
hush (Left _) = Nothing
fromEither
:: Member (Error e) r
=> Either e a
-> Sem r a
fromEither (Left e) = throw e
fromEither (Right a) = pure a
{-# INLINABLE fromEither #-}
fromEitherM
:: forall e m r a
. ( Member (Error e) r
, Member (Embed m) r
)
=> m (Either e a)
-> Sem r a
fromEitherM = fromEither <=< embed
{-# INLINABLE fromEitherM #-}
fromException
:: forall e r a
. ( X.Exception e
, Member (Error e) r
, Member (Embed IO) r
)
=> IO a
-> Sem r a
fromException = fromExceptionVia @e id
{-# INLINABLE fromException #-}
fromExceptionVia
:: ( X.Exception exc
, Member (Error err) r
, Member (Embed IO) r
)
=> (exc -> err)
-> IO a
-> Sem r a
fromExceptionVia f m = do
r <- embed $ X.try m
case r of
Left e -> throw $ f e
Right a -> pure a
{-# INLINABLE fromExceptionVia #-}
fromExceptionSem
:: forall e r a
. ( X.Exception e
, Member (Error e) r
, Member (Final IO) r
)
=> Sem r a
-> Sem r a
fromExceptionSem = fromExceptionSemVia @e id
{-# INLINABLE fromExceptionSem #-}
fromExceptionSemVia
:: ( X.Exception exc
, Member (Error err) r
, Member (Final IO) r
)
=> (exc -> err)
-> Sem r a
-> Sem r a
fromExceptionSemVia f m = do
r <- withStrategicToFinal $ do
m' <- runS m
s <- getInitialStateS
pure $ (fmap . fmap) Right m' `X.catch` \e -> (pure (Left e <$ s))
case r of
Left e -> throw $ f e
Right a -> pure a
{-# INLINABLE fromExceptionSemVia #-}
note :: Member (Error e) r => e -> Maybe a -> Sem r a
note e Nothing = throw e
note _ (Just a) = pure a
{-# INLINABLE note #-}
try :: Member (Error e) r => Sem r a -> Sem r (Either e a)
try m = catch (Right <$> m) (return . Left)
{-# INLINABLE try #-}
tryJust :: Member (Error e) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a)
tryJust f m = do
r <- try m
case r of
Right v -> return (Right v)
Left e -> case f e of
Nothing -> throw e
Just b -> return $ Left b
{-# INLINABLE tryJust #-}
catchJust :: Member (Error e) r
=> (e -> Maybe b)
-> Sem r a
-> (b -> Sem r a)
-> Sem r a
catchJust ef m bf = catch m handler
where
handler e = case ef e of
Nothing -> throw e
Just b -> bf b
{-# INLINABLE catchJust #-}
runError
:: Sem (Error e ': r) a
-> Sem r (Either e a)
runError (Sem m) = Sem $ \k -> E.runExceptT $ m $ \u ->
case decomp u of
Left x -> E.ExceptT $ k $
weave (Right ())
(either (pure . Left) runError)
hush
x
Right (Weaving (Throw e) _ _ _ _) -> E.throwE e
Right (Weaving (Catch main handle) s d y _) ->
E.ExceptT $ usingSem k $ do
ma <- runError $ d $ main <$ s
case ma of
Right a -> pure . Right $ y a
Left e -> do
ma' <- runError $ d $ (<$ s) $ handle e
case ma' of
Left e' -> pure $ Left e'
Right a -> pure . Right $ y a
{-# INLINE runError #-}
mapError
:: forall e1 e2 r a
. Member (Error e2) r
=> (e1 -> e2)
-> Sem (Error e1 ': r) a
-> Sem r a
mapError f = interpretH $ \case
Throw e -> throw $ f e
Catch action handler -> do
a <- runT action
h <- bindT handler
mx <- raise $ runError a
case mx of
Right x -> pure x
Left e -> do
istate <- getInitialStateT
mx' <- raise $ runError $ h $ e <$ istate
case mx' of
Right x -> pure x
Left e' -> throw $ f e'
{-# INLINE mapError #-}
newtype WrappedExc e = WrappedExc { unwrapExc :: e }
deriving (Typeable)
instance Typeable e => Show (WrappedExc e) where
show = mappend "WrappedExc: " . show . typeRep
instance (Typeable e) => X.Exception (WrappedExc e)
errorToIOFinal
:: ( Typeable e
, Member (Final IO) r
)
=> Sem (Error e ': r) a
-> Sem r (Either e a)
errorToIOFinal sem = withStrategicToFinal @IO $ do
m' <- runS (runErrorAsExcFinal sem)
s <- getInitialStateS
pure $
either
((<$ s) . Left . unwrapExc)
(fmap Right)
<$> X.try m'
{-# INLINE errorToIOFinal #-}
runErrorAsExcFinal
:: forall e r a
. ( Typeable e
, Member (Final IO) r
)
=> Sem (Error e ': r) a
-> Sem r a
runErrorAsExcFinal = interpretFinal $ \case
Throw e -> pure $ X.throwIO $ WrappedExc e
Catch m h -> do
m' <- runS m
h' <- bindS h
s <- getInitialStateS
pure $ X.catch m' $ \(se :: WrappedExc e) ->
h' (unwrapExc se <$ s)
{-# INLINE runErrorAsExcFinal #-}
lowerError
:: ( Typeable e
, Member (Embed IO) r
)
=> (∀ x. Sem r x -> IO x)
-> Sem (Error e ': r) a
-> Sem r (Either e a)
lowerError lower
= embed
. fmap (first unwrapExc)
. X.try
. (lower .@ runErrorAsExc)
{-# INLINE lowerError #-}
{-# DEPRECATED lowerError "Use 'errorToIOFinal' instead" #-}
runErrorAsExc
:: forall e r a. ( Typeable e
, Member (Embed IO) r
)
=> (∀ x. Sem r x -> IO x)
-> Sem (Error e ': r) a
-> Sem r a
runErrorAsExc lower = interpretH $ \case
Throw e -> embed $ X.throwIO $ WrappedExc e
Catch main handle -> do
is <- getInitialStateT
m <- runT main
h <- bindT handle
let runIt = lower . runErrorAsExc lower
embed $ X.catch (runIt m) $ \(se :: WrappedExc e) ->
runIt $ h $ unwrapExc se <$ is
{-# INLINE runErrorAsExc #-}