diff options
author | Jesse Rosenthal <jrosenthal@jhu.edu> | 2014-07-12 08:56:59 +0100 |
---|---|---|
committer | Jesse Rosenthal <jrosenthal@jhu.edu> | 2014-07-12 18:04:06 +0100 |
commit | fe2eda9d54e64ffa0c6c5c5295c19941040a5f3d (patch) | |
tree | 637d6bb84df637b1287bf83e7a26e6a3b566ea45 /src | |
parent | d65fd581713f181032ac29afe9843f1de99c70e0 (diff) | |
download | pandoc-fe2eda9d54e64ffa0c6c5c5295c19941040a5f3d.tar.gz |
Docx Reader: Add a compatibility layer for Except.
mtl switched from ErrorT to ExceptT, but we're not sure which mtl we'll
be dealing with. This should make errors work with both.
The main difference (beside the name of the module and the monad
transformer) is that Except doesn't require an instance of an Error
Typeclass. So we define that for compatability. When we switch to a
later mtl, using Control.Monad.Exception, we can just erase the instance
declaration, and all should work fine.
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Compat/Except.hs | 27 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Parse.hs | 6 |
2 files changed, 30 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Compat/Except.hs b/src/Text/Pandoc/Compat/Except.hs new file mode 100644 index 000000000..7f5648e7a --- /dev/null +++ b/src/Text/Pandoc/Compat/Except.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE CPP #-} +module Text.Pandoc.Compat.Except ( ExceptT + , Error(..) + , runExceptT + , throwError + , catchError ) + where + +#if MIN_VERSION_mtl(2,2,1) +import Control.Monad.Except + +class Error a where + noMsg :: a + strMsg :: String -> a + + noMsg = strMsg "" + strMsg _ = noMsg + +#else +import Control.Monad.Error +type ExceptT = ErrorT + +runExceptT :: ExceptT e m a -> m (Either e a) +runExceptT = runErrorT +#endif + + diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index bb65236a3..4b5a11fa8 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -69,7 +69,7 @@ import qualified Data.ByteString.Lazy as B import qualified Text.Pandoc.UTF8 as UTF8 import Control.Monad.Reader import qualified Data.Map as M -import Control.Monad.Error +import Text.Pandoc.Compat.Except data ReaderEnv = ReaderEnv { envNotes :: Notes , envNumbering :: Numbering @@ -84,10 +84,10 @@ data DocxError = DocxError | WrongElem instance Error DocxError where noMsg = WrongElem -type D = ErrorT DocxError (Reader ReaderEnv) +type D = ExceptT DocxError (Reader ReaderEnv) runD :: D a -> ReaderEnv -> Either DocxError a -runD dx re = runReader (runErrorT dx ) re +runD dx re = runReader (runExceptT dx ) re maybeToD :: Maybe a -> D a maybeToD (Just a) = return a |