aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-11-02 18:23:46 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-11-02 18:23:46 -0700
commitc721d28c332929e0a06a32577886beb48ea1484a (patch)
treed706ffcd2848a117458678f9817757221a42b8c4 /src/Text/Pandoc
parent9e369e90164fe832d4e09ba51fbdf4ba4d2f9ba1 (diff)
downloadpandoc-c721d28c332929e0a06a32577886beb48ea1484a.tar.gz
T.P.Parsing: Generalize readWithM to any Char Stream.
[API change]
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Parsing.hs17
1 files changed, 12 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index a9f323863..d53ea129b 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -198,6 +198,7 @@ where
import Prelude
import Control.Monad.Identity
+import Control.Monad.Loops (unfoldM)
import Control.Monad.Reader
import Data.Char (chr, isAlphaNum, isAscii, isAsciiUpper,
isPunctuation, isSpace, ord, toLower, toUpper)
@@ -221,6 +222,7 @@ import Text.Pandoc.Shared
import qualified Text.Pandoc.UTF8 as UTF8 (putStrLn)
import Text.Pandoc.XML (fromEntities)
import Text.Parsec hiding (token)
+import qualified Text.Parsec (uncons)
import Text.Parsec.Pos (initialPos, newPos, updatePosString)
import Control.Monad.Except
@@ -1044,13 +1046,18 @@ gridTableFooter = blanklines
---
-- | Removes the ParsecT layer from the monad transformer stack
-readWithM :: Monad m
- => ParserT [Char] st m a -- ^ parser
+readWithM :: (Monad m, Stream s m Char)
+ => ParserT s st m a -- ^ parser
-> st -- ^ initial state
- -> String -- ^ input
+ -> s -- ^ input
-> m (Either PandocError a)
-readWithM parser state input =
- mapLeft (PandocParsecError input) `liftM` runParserT parser state "source" input
+readWithM parser state input = do
+ res <- runParserT parser state "source" input
+ case res of
+ Right x -> return $ Right x
+ Left e -> do
+ inp <- map fst <$> unfoldM (Text.Parsec.uncons input)
+ return $ Left $ PandocParsecError inp e
-- | Parse a string with a given parser and state