Readers: pass errors straight up to PandocMonad.

Since we've unified error types, we can just throw the same error at
the toplevel.
This commit is contained in:
Jesse Rosenthal 2016-12-02 08:15:10 -05:00 committed by John MacFarlane
parent 9d69c51527
commit 650fa20788
8 changed files with 8 additions and 13 deletions

View file

@ -68,7 +68,7 @@ readLaTeX opts ltx = do
parsed <- readWithM parseLaTeX def{ stateOptions = opts } ltx
case parsed of
Right result -> return result
Left _ -> throwError $ PandocParseError "parsing error"
Left e -> throwError e
parseLaTeX :: PandocMonad m => LP m Pandoc
parseLaTeX = do

View file

@ -68,7 +68,6 @@ import Debug.Trace (trace)
import Data.Monoid ((<>))
import Control.Monad.Trans (lift)
import Control.Monad.Except (throwError, catchError)
import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
@ -83,7 +82,7 @@ readMarkdown opts s = do
parsed <- (readWithM parseMarkdown) def{ stateOptions = opts } (s ++ "\n\n")
case parsed of
Right result -> return result
Left _ -> throwError $ PandocParseError "markdown parse error"
Left e -> throwError e
-- | Read markdown from an input string and return a pair of a Pandoc document
-- and a list of warnings.

View file

@ -58,7 +58,6 @@ import Data.Maybe (fromMaybe)
import Text.Printf (printf)
import Debug.Trace (trace)
import Control.Monad.Except (throwError)
import Text.Pandoc.Error(PandocError(..))
import Text.Pandoc.Class (PandocMonad)
-- | Read mediawiki from an input string and return a Pandoc document.
@ -77,7 +76,7 @@ readMediaWiki opts s = do
(s ++ "\n")
case parsed of
Right result -> return result
Left _ -> throwError $ PandocParseError "problem parsing mediawiki"
Left e -> throwError e
data MWState = MWState { mwOptions :: ReaderOptions
, mwMaxNestingLevel :: Int

View file

@ -64,7 +64,7 @@ readOdt opts bytes = case readOdt' opts bytes of
Right (doc, mb) -> do
P.setMediaBag mb
return doc
Left _ -> throwError $ PandocParseError "couldn't parse odt"
Left e -> throwError e
--
readOdt' :: ReaderOptions

View file

@ -51,7 +51,6 @@ import Data.Char (toLower, isHexDigit, isSpace)
import Data.Monoid ((<>))
import Control.Monad.Except (throwError)
import Control.Monad.Trans (lift)
import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
@ -64,7 +63,7 @@ readRST opts s = do
parsed <- (readWithM parseRST) def{ stateOptions = opts } (s ++ "\n\n")
case parsed of
Right result -> return result
Left _ -> throwError $ PandocParseError "error parsing rst"
Left e -> throwError e
readRSTWithWarnings :: PandocMonad m
=> ReaderOptions -- ^ Reader options

View file

@ -60,7 +60,7 @@ readTWiki opts s = case readTWikiWithWarnings' opts s of
Right (doc, warns) -> do
mapM_ P.warn warns
return doc
Left _ -> throwError $ PandocParseError "couldn't parse TWiki"
Left e -> throwError e
readTWikiWithWarnings' :: ReaderOptions -- ^ Reader options
-> String -- ^ String to parse (assuming @'\n'@ line endings)

View file

@ -68,7 +68,6 @@ import Control.Monad ( guard, liftM, when )
import Data.Monoid ((<>))
import Text.Printf
import Debug.Trace (trace)
import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad)
import Control.Monad.Except (throwError)
@ -81,7 +80,7 @@ readTextile opts s = do
parsed <- readWithM parseTextile def{ stateOptions = opts } (s ++ "\n\n")
case parsed of
Right result -> return result
Left _ -> throwError $ PandocParseError "textile parse error"
Left e -> throwError e
-- | Generate a Pandoc ADT from a textile document

View file

@ -50,7 +50,6 @@ import Control.Monad.Reader (Reader, runReader, asks)
import Data.Time.Format (formatTime)
import Text.Pandoc.Compat.Time (defaultTimeLocale)
import Control.Monad.Except (throwError, catchError)
import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
@ -99,7 +98,7 @@ readTxt2Tags opts s = do
let parsed = flip runReader meta $ readWithM parseT2T (def {stateOptions = opts}) (s ++ "\n\n")
case parsed of
Right result -> return $ result
Left _ -> throwError $ PandocParseError "error parsing t2t"
Left e -> throwError e
-- | Read Txt2Tags (ignoring all macros) from an input string returning
-- a Pandoc document