aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Compat/Except.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Compat/Except.hs')
-rw-r--r--src/Text/Pandoc/Compat/Except.hs12
1 files changed, 11 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Compat/Except.hs b/src/Text/Pandoc/Compat/Except.hs
index 7f5648e7a..9ce7c0d36 100644
--- a/src/Text/Pandoc/Compat/Except.hs
+++ b/src/Text/Pandoc/Compat/Except.hs
@@ -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