{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module Polysemy.ConstraintAbsorber.MonadCatch
(
absorbMonadThrow
, absorbMonadCatch
, runMonadCatch
, runMonadCatchAsText
, Exception(..)
, SomeException
)
where
import qualified Control.Monad.Catch as C
import Control.Monad.Catch ( Exception(..)
, SomeException
, toException
)
import qualified Data.Text as T
import Polysemy
import Polysemy.ConstraintAbsorber
import qualified Polysemy.Error as E
runMonadCatch
:: Exception e
=> (Maybe e -> e')
-> Sem (E.Error C.SomeException : E.Error e' : r) a
-> Sem r (Either e' a)
runMonadCatch f = E.runError . E.mapError (f . C.fromException)
runMonadCatchAsText
:: Sem (E.Error C.SomeException : E.Error T.Text : r) a
-> Sem r (Either T.Text a)
runMonadCatchAsText = E.runError . E.mapError (T.pack . C.displayException)
absorbMonadCatch
:: Member (E.Error C.SomeException) r
=> (C.MonadCatch (Sem r) => Sem r a)
-> Sem r a
absorbMonadCatch =
absorbWithSem @C.MonadCatch @Action (CatchDict E.throw E.catch) (Sub Dict)
{-# INLINABLE absorbMonadCatch #-}
absorbMonadThrow
:: Member (E.Error C.SomeException) r
=> (C.MonadThrow (Sem r) => Sem r a)
-> Sem r a
absorbMonadThrow = absorbMonadCatch
{-# INLINABLE absorbMonadThrow #-}
data CatchDict m = CatchDict
{ throwM_ :: forall a. C.SomeException -> m a
, catch_ :: forall a. m a -> (C.SomeException -> m a) -> m a
}
newtype Action m s' a = Action { action :: m a }
deriving (Functor, Applicative, Monad)
instance ( Monad m
, Reifies s' (CatchDict m)
) => C.MonadThrow (Action m s') where
throwM e = Action $ throwM_ (reflect $ Proxy @s') (C.toException e)
{-# INLINEABLE throwM #-}
instance ( Monad m
, Reifies s' (CatchDict m)
) => C.MonadCatch (Action m s') where
catch x f =
let catchF = catch_ (reflect $ Proxy @s')
in Action $ (action x) `catchF` \e -> case C.fromException e of
Just e' -> action $ f e'
_ -> throwM_ (reflect $ Proxy @s') (C.toException e)
{-# INLINEABLE catch #-}