diff options
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 31 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 3 |
2 files changed, 22 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index f4f9178d0..eec4a3bc9 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -64,6 +64,7 @@ module Text.Pandoc.Parsing ( anyLine, widthsFromIndices, gridTableWith, readWith, + readWithM, testStringWith, guardEnabled, guardDisabled, @@ -106,7 +107,9 @@ module Text.Pandoc.Parsing ( anyLine, askF, asksF, -- * Re-exports from Text.Pandoc.Parsec + Stream, runParser, + runParserT, parse, anyToken, getInput, @@ -825,15 +828,16 @@ gridTableFooter = blanklines --- --- | Parse a string with a given parser and state. -readWith :: (Stream [Char] Identity Char) - => ParserT [Char] st Identity a -- ^ parser - -> st -- ^ initial state - -> [Char] -- ^ input - -> a -readWith parser state input = - case runParser parser state "source" input of - Left err' -> +-- | Removes the ParsecT layer from the monad transformer stack +readWithM :: (Monad m, Functor m) + => ParserT [Char] st m a -- ^ parser + -> st -- ^ initial state + -> String -- ^ input + -> m a +readWithM parser state input = + handleError <$> (runParserT parser state "source" input) + where + handleError (Left err') = let errPos = errorPos err' errLine = sourceLine errPos errColumn = sourceColumn errPos @@ -841,7 +845,14 @@ readWith parser state input = in error $ "\nError at " ++ show err' ++ "\n" ++ theline ++ "\n" ++ replicate (errColumn - 1) ' ' ++ "^" - Right result -> result + handleError (Right result) = result + +-- | Parse a string with a given parser and state +readWith :: Parser [Char] st a + -> st + -> String + -> a +readWith p t inp = runIdentity $ readWithM p t inp -- | Parse a string with @parser@ (for testing). testStringWith :: (Show a, Stream [Char] Identity Char) diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 339f8e3c9..9f51e9a8f 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -41,7 +41,6 @@ import Text.Pandoc.Shared import Text.Pandoc.Options import Text.Pandoc.Parsing hiding ((<|>), many, optional, space, mathDisplay, mathInline) -import Text.Parsec.Prim (ParsecT, runParserT) import qualified Text.Pandoc.UTF8 as UTF8 import Data.Char ( chr, ord ) import Control.Monad.Trans (lift) @@ -808,7 +807,7 @@ rawEnv name = do ---- -type IncludeParser = ParsecT [Char] [String] IO String +type IncludeParser = ParserT [Char] [String] IO String -- | Replace "include" commands with file contents. handleIncludes :: String -> IO String |