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
import qualified Control.Exception
#if !(MIN_VERSION_base(4,6,0))
import Control.Monad.Instances ()  
#endif
import Data.Monoid
import System.IO
class (Monad m) => MonadError m where
    type ErrorType m
    
    throwError :: ErrorType m -> m a
    
    catchError :: m a -> (ErrorType m -> m a) -> m a
instance MonadError IO where
    type ErrorType IO = IOError
    throwError = ioError
    catchError = Control.Exception.catch
instance (Error e) => MonadError (Either e) where
    type ErrorType (Either e) = e
    throwError             = Left
    Left  l `catchError` h = h l
    Right r `catchError` _ = Right r
instance (Monad m, Error e) => MonadError (ErrorT e m) where
    type ErrorType (ErrorT e m) = e
    throwError = ErrorT.throwError
    catchError = ErrorT.catchError
instance (MonadError m) => MonadError (IdentityT m) where
    type ErrorType (IdentityT m) = ErrorType m
    throwError = lift . throwError
    catchError = Identity.liftCatch catchError
instance (MonadError m) => MonadError (ListT m) where
    type ErrorType (ListT m) = ErrorType m
    throwError = lift . throwError
    catchError = List.liftCatch catchError
instance (MonadError m) => MonadError (MaybeT m) where
    type ErrorType (MaybeT m) = ErrorType m
    throwError = lift . throwError
    catchError = Maybe.liftCatch catchError
instance (MonadError m) => MonadError (ReaderT r m) where
    type ErrorType (ReaderT r m) = ErrorType m
    throwError = lift . throwError
    catchError = Reader.liftCatch catchError
instance (Monoid w, MonadError m) => MonadError (LazyRWS.RWST r w s m) where
    type ErrorType (LazyRWS.RWST r w s m) = ErrorType m
    throwError = lift . throwError
    catchError = LazyRWS.liftCatch catchError
instance (Monoid w, MonadError m) => MonadError (StrictRWS.RWST r w s m) where
    type ErrorType (StrictRWS.RWST r w s m) = ErrorType m
    throwError = lift . throwError
    catchError = StrictRWS.liftCatch catchError
instance (MonadError m) => MonadError (LazyState.StateT s m) where
    type ErrorType (LazyState.StateT s m) = ErrorType m
    throwError = lift . throwError
    catchError = LazyState.liftCatch catchError
instance (MonadError m) => MonadError (StrictState.StateT s m) where
    type ErrorType (StrictState.StateT s m) = ErrorType m
    throwError = lift . throwError
    catchError = StrictState.liftCatch catchError
instance (Monoid w, MonadError m) => MonadError (LazyWriter.WriterT w m) where
    type ErrorType (LazyWriter.WriterT w m) = ErrorType m
    throwError = lift . throwError
    catchError = LazyWriter.liftCatch catchError
instance (Monoid w, MonadError m) => MonadError (StrictWriter.WriterT w m) where
    type ErrorType (StrictWriter.WriterT w m) = ErrorType m
    throwError = lift . throwError
    catchError = StrictWriter.liftCatch catchError