module Control.Monad.Error.Class (
Error(..),
MonadError(..),
) where
import Control.Monad.Trans.Error (Error(..), ErrorT)
import qualified Control.Monad.Trans.Error as ErrorT (throwError, catchError)
import Control.Monad.Trans.Identity as Identity
import Control.Monad.Trans.List as List
import Control.Monad.Trans.Maybe as Maybe
import Control.Monad.Trans.Reader as Reader
import Control.Monad.Trans.RWS.Lazy as LazyRWS
import Control.Monad.Trans.RWS.Strict as StrictRWS
import Control.Monad.Trans.State.Lazy as LazyState
import Control.Monad.Trans.State.Strict as StrictState
import Control.Monad.Trans.Writer.Lazy as LazyWriter
import Control.Monad.Trans.Writer.Strict as StrictWriter
import Control.Monad.Trans.Class (lift)
import Control.Exception (IOException)
import Control.Monad
import Control.Monad.Instances ()
import Data.Monoid
class (Monad m) => MonadError e m | m -> e where
throwError :: e -> m a
catchError :: m a -> (e -> m a) -> m a
instance MonadError IOException IO where
throwError = ioError
catchError = catch
instance (Error e) => MonadError e (Either e) where
throwError = Left
Left l `catchError` h = h l
Right r `catchError` _ = Right r
instance (Monad m, Error e) => MonadError e (ErrorT e m) where
throwError = ErrorT.throwError
catchError = ErrorT.catchError
instance (MonadError e m) => MonadError e (IdentityT m) where
throwError = lift . throwError
catchError = Identity.liftCatch catchError
instance (MonadError e m) => MonadError e (ListT m) where
throwError = lift . throwError
catchError = List.liftCatch catchError
instance (MonadError e m) => MonadError e (MaybeT m) where
throwError = lift . throwError
catchError = Maybe.liftCatch catchError
instance (MonadError e m) => MonadError e (ReaderT r m) where
throwError = lift . throwError
catchError = Reader.liftCatch catchError
instance (Monoid w, MonadError e m) => MonadError e (LazyRWS.RWST r w s m) where
throwError = lift . throwError
catchError = LazyRWS.liftCatch catchError
instance (Monoid w, MonadError e m) => MonadError e (StrictRWS.RWST r w s m) where
throwError = lift . throwError
catchError = StrictRWS.liftCatch catchError
instance (MonadError e m) => MonadError e (LazyState.StateT s m) where
throwError = lift . throwError
catchError = LazyState.liftCatch catchError
instance (MonadError e m) => MonadError e (StrictState.StateT s m) where
throwError = lift . throwError
catchError = StrictState.liftCatch catchError
instance (Monoid w, MonadError e m) => MonadError e (LazyWriter.WriterT w m) where
throwError = lift . throwError
catchError = LazyWriter.liftCatch catchError
instance (Monoid w, MonadError e m) => MonadError e (StrictWriter.WriterT w m) where
throwError = lift . throwError
catchError = StrictWriter.liftCatch catchError