Except Compat: Updated to export more module functions

This commit is contained in:
Matthew Pickering 2014-07-30 00:48:40 +01:00
parent 089745af61
commit b57e554b59

View file

@ -1,7 +1,10 @@
{-# LANGUAGE CPP #-}
module Text.Pandoc.Compat.Except ( ExceptT
, Except
, Error(..)
, runExceptT
, runExcept
, MonadError
, throwError
, catchError )
where
@ -18,10 +21,17 @@ class Error a where
#else
import Control.Monad.Error
import Control.Monad.Identity (Identity, runIdentity)
type ExceptT = ErrorT
runExceptT :: ExceptT e m a -> m (Either e a)
type Except s a = ErrorT s Identity a
runExceptT :: ExceptT e m a -> m (Either e a)
runExceptT = runErrorT
runExcept :: ExceptT e Identity a -> Either e a
runExcept = runIdentity . runExceptT
#endif