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.
This commit is contained in:
Jesse Rosenthal 2014-07-12 08:56:59 +01:00
parent d65fd58171
commit fe2eda9d54
3 changed files with 31 additions and 3 deletions

View file

@ -340,6 +340,7 @@ Library
Text.Pandoc.Slides, Text.Pandoc.Slides,
Text.Pandoc.Highlighting, Text.Pandoc.Highlighting,
Text.Pandoc.Compat.Monoid, Text.Pandoc.Compat.Monoid,
Text.Pandoc.Compat.Except,
Text.Pandoc.Compat.TagSoupEntity, Text.Pandoc.Compat.TagSoupEntity,
Paths_pandoc Paths_pandoc

View file

@ -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

View file

@ -69,7 +69,7 @@ import qualified Data.ByteString.Lazy as B
import qualified Text.Pandoc.UTF8 as UTF8 import qualified Text.Pandoc.UTF8 as UTF8
import Control.Monad.Reader import Control.Monad.Reader
import qualified Data.Map as M import qualified Data.Map as M
import Control.Monad.Error import Text.Pandoc.Compat.Except
data ReaderEnv = ReaderEnv { envNotes :: Notes data ReaderEnv = ReaderEnv { envNotes :: Notes
, envNumbering :: Numbering , envNumbering :: Numbering
@ -84,10 +84,10 @@ data DocxError = DocxError | WrongElem
instance Error DocxError where instance Error DocxError where
noMsg = WrongElem noMsg = WrongElem
type D = ErrorT DocxError (Reader ReaderEnv) type D = ExceptT DocxError (Reader ReaderEnv)
runD :: D a -> ReaderEnv -> Either DocxError a 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 :: Maybe a -> D a
maybeToD (Just a) = return a maybeToD (Just a) = return a