module Algebra.Monad.Error (
  -- * The MonadError class
  MonadError(..),try,tryMay,throwIO,

  -- * The Either transformer
  EitherT,
  _eitherT
  ) where

import Algebra.Monad.Base
import qualified Control.Exception as Ex

try :: MonadError Void m => m a -> m a -> m a
try = catch . const
tryMay :: MonadError e m => m a -> m (Maybe a)
tryMay m = catch (\_ -> return Nothing) (Just<$>m)

instance MonadError e (Either e) where
  throw = Left
  catch f = f<|>Right
instance MonadError Void [] where
  throw = const zero
  catch f [] = f zero
  catch _ l = l
newtype EitherT e m a = EitherT (Compose' (Either e) m a)
                      deriving (Unit,Functor,Applicative,Monad,MonadFix
                               ,Foldable,Traversable,MonadTrans)
_eitherT :: (Functor m) => Iso (EitherT e m a) (EitherT f m b) (m (e:+:a)) (m (f:+:b))                              
_eitherT = _Compose'.iso EitherT (\(EitherT e) -> e)

instance MonadError Void Maybe where
  throw = const Nothing
  catch f Nothing = f zero
  catch _ a = a
instance MonadError Ex.SomeException IO where
  throw = Ex.throw
  catch = flip Ex.catch
throwIO :: Ex.Exception e => e -> IO ()
throwIO = throw . Ex.toException