{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Polysemy.ConstraintAbsorber.MonadError
( absorbError
) where
import qualified Control.Monad.Error.Class as S
import Polysemy
import Polysemy.ConstraintAbsorber
import Polysemy.Error
absorbError
:: Member (Error e) r
=> (S.MonadError e (Sem r) => Sem r a)
-> Sem r a
absorbError = absorbWithSem @(S.MonadError _) @Action
(ErrorDict throw catch)
(Sub Dict)
{-# INLINEABLE absorbError #-}
data ErrorDict e m = ErrorDict
{ throwError_ :: forall a. e -> m a
, catchError_ :: forall a. m a -> (e -> m a) -> m a
}
newtype Action m s' a = Action { action :: m a }
deriving (Functor, Applicative, Monad)
instance ( Monad m
, Reifies s' (ErrorDict e m)
) => S.MonadError e (Action m s') where
throwError e = Action $ throwError_ (reflect $ Proxy @s') e
{-# INLINEABLE throwError #-}
catchError x f = Action $ catchError_ (reflect $ Proxy @s') (action x) (action . f)
{-# INLINEABLE catchError #-}