diff options
| author | John MacFarlane <[email protected]> | 2022-10-16 19:16:12 -0700 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2022-10-16 20:01:01 -0700 |
| commit | c64ac35ae23dfbc3e6d6ab5a034e03c7e9c2d7db (patch) | |
| tree | 7c4fd1a2c640facf239d5a8ff4ce65f0eae38236 /src | |
| parent | 276335bcea515061250b894bbc78da222fb3fdf6 (diff) | |
T.P.Parsing: Remove gratuitious renaming of Parsec types.
We were exporting Parser, ParserT as synonyms of Parsec, ParsecT.
There is no good reason for this and it can cause confusion.
Also, when possible, we replace imports of Text.Parsec with
T.P.Parsing. The idea is to make it easier, at some point,
to switch to megaparsec or another parsing engine if we want to.
T.P.Parsing new exports: Stream(..), updatePosString, SourceName,
Parsec, ParsecT [API change].
Removed exports: Parser, ParserT [API change].
Diffstat (limited to 'src')
42 files changed, 281 insertions, 280 deletions
diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs index 03065cc9b..9a8f0bd05 100644 --- a/src/Text/Pandoc/CSS.hs +++ b/src/Text/Pandoc/CSS.hs @@ -22,8 +22,9 @@ import Data.Either (fromRight) import Data.Maybe (mapMaybe, listToMaybe) import Data.Text (Text, pack) import Text.Pandoc.Shared (trim) -import Text.Parsec -import Text.Parsec.Text +import Text.Pandoc.Parsing + +type Parser = Parsec Text () ruleParser :: Parser (Text, Text) ruleParser = do diff --git a/src/Text/Pandoc/CSV.hs b/src/Text/Pandoc/CSV.hs index 963fead0d..03fb24ffa 100644 --- a/src/Text/Pandoc/CSV.hs +++ b/src/Text/Pandoc/CSV.hs @@ -19,8 +19,9 @@ module Text.Pandoc.CSV ( import Control.Monad (unless, void, mzero) import Data.Text (Text) import qualified Data.Text as T -import Text.Parsec -import Text.Parsec.Text (Parser) +import Text.Pandoc.Parsing hiding (escaped) + +type Parser = Parsec Text () data CSVOptions = CSVOptions{ csvDelim :: Char diff --git a/src/Text/Pandoc/Citeproc/BibTeX.hs b/src/Text/Pandoc/Citeproc/BibTeX.hs index 679644b7f..e1ad44cc7 100644 --- a/src/Text/Pandoc/Citeproc/BibTeX.hs +++ b/src/Text/Pandoc/Citeproc/BibTeX.hs @@ -348,7 +348,7 @@ defaultLang = Lang "en" Nothing (Just "US") [] [] [] -- a map of bibtex "string" macros type StringMap = Map.Map Text Text -type BibParser = Parser Sources (Lang, StringMap) +type BibParser = Parsec Sources (Lang, StringMap) data Item = Item{ identifier :: Text , sourcePos :: SourcePos @@ -832,7 +832,7 @@ bibString = do updateState (\(l,m) -> (l, Map.insert k v m)) return () -take1WhileP :: Monad m => (Char -> Bool) -> ParserT Sources u m Text +take1WhileP :: Monad m => (Char -> Bool) -> ParsecT Sources u m Text take1WhileP f = T.pack <$> many1 (satisfy f) inBraces :: BibParser Text diff --git a/src/Text/Pandoc/Format.hs b/src/Text/Pandoc/Format.hs index be1c32f02..2689a2834 100644 --- a/src/Text/Pandoc/Format.hs +++ b/src/Text/Pandoc/Format.hs @@ -32,9 +32,11 @@ import Text.Pandoc.Extensions , getDefaultExtensions , readExtension ) -import Text.Parsec +import Text.Pandoc.Parsing import qualified Data.Text as T +type Parser = Parsec T.Text () + -- | Format specifier with the format's name and the lists of extensions -- to be enabled or disabled. data FlavoredFormat = FlavoredFormat @@ -107,7 +109,7 @@ parseFlavoredFormat spec = Left err -> throwError $ PandocFormatError spec (T.pack $ show err) where fixSourcePos = do - pos <- statePos <$> getParserState + pos <- getPosition setPosition (incSourceColumn pos (T.length prefix)) formatSpec = do name <- parseFormatName @@ -118,7 +120,7 @@ parseFlavoredFormat spec = (_, "") -> ("", T.toLower spec) -- no extension (p,s) -> (T.pack p, T.pack s) -pExtensionsDiff :: Stream s m Char => ParsecT s u m ExtensionsDiff +pExtensionsDiff :: Parser ExtensionsDiff pExtensionsDiff = foldl' (flip ($)) (ExtensionsDiff [] []) <$> many extMod where extMod = do diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index ca2e86713..68efe471c 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -106,8 +106,8 @@ module Text.Pandoc.Parsing ( module Text.Pandoc.Sources, dash, nested, citeKey, - Parser, - ParserT, + Parsec, + ParsecT, Future(..), runF, askF, @@ -119,7 +119,7 @@ module Text.Pandoc.Parsing ( module Text.Pandoc.Sources, extractIdClass, insertIncludedFile, -- * Re-exports from Text.Parsec - Stream, + Stream(..), runParser, runParserT, parse, @@ -154,6 +154,8 @@ module Text.Pandoc.Parsing ( module Text.Pandoc.Sources, setState, updateState, SourcePos, + SourceName, + updatePosString, getPosition, setPosition, sourceName, @@ -174,7 +176,11 @@ where import Text.Pandoc.Sources import Text.Parsec - ( setSourceName, + ( Parsec, + ParsecT, + SourcePos, + SourceName, + setSourceName, Column, Line, incSourceLine, @@ -221,9 +227,8 @@ import Text.Parsec runParserT, runParser, ParseError, - SourcePos, Stream(..) ) -import Text.Parsec.Pos (initialPos, newPos) +import Text.Parsec.Pos (initialPos, newPos, updatePosString) import Text.Pandoc.Parsing.Capabilities ( guardDisabled, guardEnabled, @@ -329,5 +334,5 @@ import Text.Pandoc.Parsing.State ParserContext(..), ParserState(..), SubstTable ) -import Text.Pandoc.Parsing.Types - ( ParserT, askF, asksF, returnF, runF, Future(..), Parser ) +import Text.Pandoc.Parsing.Future + ( askF, asksF, returnF, runF, Future(..) ) diff --git a/src/Text/Pandoc/Parsing/Capabilities.hs b/src/Text/Pandoc/Parsing/Capabilities.hs index 0b50576de..4a2b9d2ca 100644 --- a/src/Text/Pandoc/Parsing/Capabilities.hs +++ b/src/Text/Pandoc/Parsing/Capabilities.hs @@ -43,7 +43,8 @@ where import Control.Monad (guard, when) import Data.Text (Text) -import Text.Parsec (ParsecT, SourcePos, Stream, getPosition, getState, updateState) +import Text.Parsec (SourcePos, Stream, ParsecT, + getPosition, getState, updateState) import Text.Pandoc.Class.PandocMonad (PandocMonad, report) import Text.Pandoc.Logging (LogMessage) import Text.Pandoc.Options @@ -51,7 +52,6 @@ import Text.Pandoc.Options , ReaderOptions(readerExtensions) , extensionEnabled ) -import Text.Pandoc.Parsing.Types import Text.Pandoc.TeX (Macro) import qualified Data.Map as M @@ -59,7 +59,7 @@ import qualified Data.Set as Set class HasReaderOptions st where extractReaderOptions :: st -> ReaderOptions - getOption :: (Stream s m t) => (ReaderOptions -> b) -> ParserT s st m b + getOption :: (Stream s m t) => (ReaderOptions -> b) -> ParsecT s st m b -- default getOption f = f . extractReaderOptions <$> getState @@ -69,7 +69,7 @@ class HasQuoteContext st m where failIfInQuoteContext :: (HasQuoteContext st m, Stream s m t) => QuoteContext - -> ParserT s st m () + -> ParsecT s st m () failIfInQuoteContext context = do context' <- getQuoteContext when (context' == context) $ Prelude.fail "already inside quotes" @@ -97,34 +97,34 @@ class HasIncludeFiles st where -- | Add a log message. logMessage :: (Stream s m a, HasLogMessages st) - => LogMessage -> ParserT s st m () + => LogMessage -> ParsecT s st m () logMessage msg = updateState (addLogMessage msg) -- | Report all the accumulated log messages, according to verbosity level. -reportLogMessages :: (PandocMonad m, HasLogMessages st) => ParserT s st m () +reportLogMessages :: (PandocMonad m, HasLogMessages st) => ParsecT s st m () reportLogMessages = do msgs <- getLogMessages <$> getState mapM_ report msgs -- | Succeed only if the extension is enabled. guardEnabled :: (Stream s m a, HasReaderOptions st) - => Extension -> ParserT s st m () + => Extension -> ParsecT s st m () guardEnabled ext = getOption readerExtensions >>= guard . extensionEnabled ext -- | Succeed only if the extension is disabled. guardDisabled :: (Stream s m a, HasReaderOptions st) - => Extension -> ParserT s st m () + => Extension -> ParsecT s st m () guardDisabled ext = getOption readerExtensions >>= guard . not . extensionEnabled ext -- | Update the position on which the last string ended. updateLastStrPos :: (Stream s m a, HasLastStrPosition st) - => ParserT s st m () + => ParsecT s st m () updateLastStrPos = getPosition >>= updateState . setLastStrPos . Just -- | Whether we are right after the end of a string. -notAfterString :: (Stream s m a, HasLastStrPosition st) => ParserT s st m Bool +notAfterString :: (Stream s m a, HasLastStrPosition st) => ParsecT s st m Bool notAfterString = do pos <- getPosition st <- getState diff --git a/src/Text/Pandoc/Parsing/Citations.hs b/src/Text/Pandoc/Parsing/Citations.hs index 923cd7dd0..a086951aa 100644 --- a/src/Text/Pandoc/Parsing/Citations.hs +++ b/src/Text/Pandoc/Parsing/Citations.hs @@ -21,6 +21,7 @@ import Text.Pandoc.Sources import Text.Parsec ( (<|>) , Stream(..) + , ParsecT , lookAhead , many , option @@ -28,13 +29,12 @@ import Text.Parsec ) import Text.Pandoc.Parsing.Capabilities (HasLastStrPosition, notAfterString) import Text.Pandoc.Parsing.General -import Text.Pandoc.Parsing.Types (ParserT) import qualified Data.Text as T citeKey :: (Stream s m Char, UpdateSourcePos s Char, HasLastStrPosition st) => Bool -- ^ If True, allow expanded @{..} syntax. - -> ParserT s st m (Bool, Text) + -> ParsecT s st m (Bool, Text) citeKey allowBraced = try $ do guard =<< notAfterString suppress_author <- option False (True <$ char '-') @@ -46,7 +46,7 @@ citeKey allowBraced = try $ do return (suppress_author, key) simpleCiteIdentifier :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Text + => ParsecT s st m Text simpleCiteIdentifier = do firstChar <- alphaNum <|> char '_' <|> char '*' -- @* for wildcard in nocite let regchar = satisfy (\c -> isAlphaNum c || c == '_') diff --git a/src/Text/Pandoc/Parsing/Types.hs b/src/Text/Pandoc/Parsing/Future.hs index f3745270b..041ee0a78 100644 --- a/src/Text/Pandoc/Parsing/Types.hs +++ b/src/Text/Pandoc/Parsing/Future.hs @@ -1,17 +1,15 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- | - Module : Text.Pandoc.Parsing + Module : Text.Pandoc.Parsing.Future Copyright : Copyright (C) 2006-2022 John MacFarlane License : GPL-2.0-or-later Maintainer : John MacFarlane <[email protected]> -Types and type-related functions for parsers. +Future type for parsing. -} -module Text.Pandoc.Parsing.Types - ( Parser - , ParserT - , Future (..) +module Text.Pandoc.Parsing.Future + ( Future (..) , runF , askF , asksF @@ -23,13 +21,6 @@ import Prelude hiding (Applicative(..)) import Control.Applicative (Applicative(..)) import Control.Monad.Reader ( asks, runReader, MonadReader(ask), Reader, ReaderT(ReaderT) ) -import Text.Parsec ( Parsec , ParsecT ) - --- | Generic parser type used by many pandoc readers. -type Parser t s = Parsec t s - --- | Generic parser transformer used by many pandoc readers. -type ParserT = ParsecT -- | Reader monad wrapping the parser state. This is used to possibly -- delay evaluation until all relevant information has been parsed and diff --git a/src/Text/Pandoc/Parsing/General.hs b/src/Text/Pandoc/Parsing/General.hs index f5f8136d2..d7c724694 100644 --- a/src/Text/Pandoc/Parsing/General.hs +++ b/src/Text/Pandoc/Parsing/General.hs @@ -128,12 +128,12 @@ import Text.Parsec , updateState ) import Text.Parsec.Pos (initialPos, newPos) +import Text.Parsec (Parsec) import Text.Pandoc.Error ( PandocError(PandocParseError, PandocParsecError) ) import Text.Pandoc.Parsing.Capabilities import Text.Pandoc.Parsing.State -import Text.Pandoc.Parsing.Types ( Parser, ParserT, Future (..)) - +import Text.Pandoc.Parsing.Future (Future (..)) import qualified Data.Set as Set import qualified Data.Text as T import qualified Text.Pandoc.Builder as B @@ -159,7 +159,7 @@ textStr t = string (T.unpack t) $> t -- | Parse any line of text, returning the contents without the -- final newline. -anyLine :: Monad m => ParserT Sources st m Text +anyLine :: Monad m => ParsecT Sources st m Text anyLine = do -- This is much faster than: -- manyTill anyChar newline @@ -182,13 +182,13 @@ anyLine = do return this -- | Parse any line, include the final newline in the output -anyLineNewline :: Monad m => ParserT Sources st m Text +anyLineNewline :: Monad m => ParsecT Sources st m Text anyLineNewline = (<> "\n") <$> anyLine -- | Parse indent by specified number of spaces (or equiv. tabs) indentWith :: (Stream s m Char, UpdateSourcePos s Char) => HasReaderOptions st - => Int -> ParserT s st m Text + => Int -> ParsecT s st m Text indentWith num = do tabStop <- getOption readerTabStop if num < tabStop @@ -198,28 +198,28 @@ indentWith num = do -- | Like @many@, but packs its result. manyChar :: Stream s m t - => ParserT s st m Char - -> ParserT s st m Text + => ParsecT s st m Char + -> ParsecT s st m Text manyChar = fmap T.pack . many -- | Like @many1@, but packs its result. many1Char :: Stream s m t - => ParserT s st m Char - -> ParserT s st m Text + => ParsecT s st m Char + -> ParsecT s st m Text many1Char = fmap T.pack . many1 -- | Like @manyTill@, but packs its result. manyTillChar :: Stream s m t - => ParserT s st m Char - -> ParserT s st m a - -> ParserT s st m Text + => ParsecT s st m Char + -> ParsecT s st m a + -> ParsecT s st m Text manyTillChar p = fmap T.pack . manyTill p -- | Like @manyTill@, but reads at least one item. many1Till :: (Show end, Stream s m t) - => ParserT s st m a - -> ParserT s st m end - -> ParserT s st m [a] + => ParsecT s st m a + -> ParsecT s st m end + -> ParsecT s st m [a] many1Till p end = do notFollowedBy' end first <- p @@ -228,15 +228,15 @@ many1Till p end = do -- | Like @many1Till@, but packs its result many1TillChar :: (Show end, Stream s m t) - => ParserT s st m Char - -> ParserT s st m end - -> ParserT s st m Text + => ParsecT s st m Char + -> ParsecT s st m end + -> ParsecT s st m Text many1TillChar p = fmap T.pack . many1Till p -- | Like @manyTill@, but also returns the result of end parser. -manyUntil :: ParserT s u m a - -> ParserT s u m b - -> ParserT s u m ([a], b) +manyUntil :: ParsecT s u m a + -> ParsecT s u m b + -> ParsecT s u m ([a], b) manyUntil p end = scan where scan = (do e <- end @@ -247,9 +247,9 @@ manyUntil p end = scan return (x:xs, e)) -- | Like @manyUntil@, but also packs its result. -manyUntilChar :: ParserT s u m Char - -> ParserT s u m b - -> ParserT s u m (Text, b) +manyUntilChar :: ParsecT s u m Char + -> ParsecT s u m b + -> ParsecT s u m (Text, b) manyUntilChar p = fmap go . manyUntil p where go (x, y) = (T.pack x, y) @@ -264,7 +264,7 @@ sepBy1' p sep = (:) <$> p <*> many (try $ sep >> p) -- | A more general form of @notFollowedBy@. This one allows any -- type of parser to be specified, and succeeds only if that parser fails. -- It does not consume any input. -notFollowedBy' :: (Show b, Stream s m a) => ParserT s st m b -> ParserT s st m () +notFollowedBy' :: (Show b, Stream s m a) => ParsecT s st m b -> ParsecT s st m () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> @@ -272,12 +272,12 @@ notFollowedBy' p = try $ join $ do a <- try p -- (This version due to Andrew Pimlott on the Haskell mailing list.) oneOfStrings' :: (Stream s m Char, UpdateSourcePos s Char) - => (Char -> Char -> Bool) -> [Text] -> ParserT s st m Text + => (Char -> Char -> Bool) -> [Text] -> ParsecT s st m Text oneOfStrings' f = fmap T.pack . oneOfStrings'' f . fmap T.unpack -- TODO: This should be re-implemented in a Text-aware way oneOfStrings'' :: (Stream s m Char, UpdateSourcePos s Char) - => (Char -> Char -> Bool) -> [String] -> ParserT s st m String + => (Char -> Char -> Bool) -> [String] -> ParsecT s st m String oneOfStrings'' _ [] = Prelude.fail "no strings" oneOfStrings'' matches strs = try $ do c <- anyChar @@ -293,7 +293,7 @@ oneOfStrings'' matches strs = try $ do -- two strings one of which is a prefix of the other, the longer -- string will be matched if possible. oneOfStrings :: (Stream s m Char, UpdateSourcePos s Char) - => [Text] -> ParserT s st m Text + => [Text] -> ParsecT s st m Text oneOfStrings = oneOfStrings' (==) -- | Parses one of a list of strings (tried in order), case insensitive. @@ -301,7 +301,7 @@ oneOfStrings = oneOfStrings' (==) -- TODO: This will not be accurate with general Unicode (neither -- Text.toLower nor Text.toCaseFold can be implemented with a map) oneOfStringsCI :: (Stream s m Char, UpdateSourcePos s Char) - => [Text] -> ParserT s st m Text + => [Text] -> ParsecT s st m Text oneOfStringsCI = oneOfStrings' ciMatch where ciMatch x y = toLower' x == toLower' y -- this optimizes toLower by checking common ASCII case @@ -313,12 +313,12 @@ oneOfStringsCI = oneOfStrings' ciMatch -- | Parses a space or tab. spaceChar :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Char + => ParsecT s st m Char spaceChar = satisfy $ \c -> c == ' ' || c == '\t' -- | Parses a nonspace, nonnewline character. nonspaceChar :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Char + => ParsecT s st m Char nonspaceChar = satisfy (not . isSpaceChar) isSpaceChar :: Char -> Bool @@ -330,23 +330,23 @@ isSpaceChar _ = False -- | Skips zero or more spaces or tabs. skipSpaces :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m () + => ParsecT s st m () skipSpaces = skipMany spaceChar -- | Skips zero or more spaces or tabs, then reads a newline. blankline :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Char + => ParsecT s st m Char blankline = try $ skipSpaces >> newline -- | Parses one or more blank lines and returns a string of newlines. blanklines :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Text + => ParsecT s st m Text blanklines = T.pack <$> many1 blankline -- | Gobble n spaces; if tabs are encountered, expand them -- and gobble some or all of their spaces, leaving the rest. gobbleSpaces :: (HasReaderOptions st, Monad m) - => Int -> ParserT Sources st m () + => Int -> ParsecT Sources st m () gobbleSpaces 0 = return () gobbleSpaces n | n < 0 = error "gobbleSpaces called with negative number" @@ -354,7 +354,7 @@ gobbleSpaces n char ' ' <|> eatOneSpaceOfTab gobbleSpaces (n - 1) -eatOneSpaceOfTab :: (HasReaderOptions st, Monad m) => ParserT Sources st m Char +eatOneSpaceOfTab :: (HasReaderOptions st, Monad m) => ParsecT Sources st m Char eatOneSpaceOfTab = do lookAhead (char '\t') pos <- getPosition @@ -373,7 +373,7 @@ eatOneSpaceOfTab = do -- | Gobble up to n spaces; if tabs are encountered, expand them -- and gobble some or all of their spaces, leaving the rest. gobbleAtMostSpaces :: (HasReaderOptions st, Monad m) - => Int -> ParserT Sources st m Int + => Int -> ParsecT Sources st m Int gobbleAtMostSpaces 0 = return 0 gobbleAtMostSpaces n | n < 0 = error "gobbleAtMostSpaces called with negative number" @@ -383,20 +383,20 @@ gobbleAtMostSpaces n -- | Parses material enclosed between start and end parsers. enclosed :: (Show end, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m t -- ^ start parser - -> ParserT s st m end -- ^ end parser - -> ParserT s st m a -- ^ content parser (to be used repeatedly) - -> ParserT s st m [a] + => ParsecT s st m t -- ^ start parser + -> ParsecT s st m end -- ^ end parser + -> ParsecT s st m a -- ^ content parser (to be used repeatedly) + -> ParsecT s st m [a] enclosed start end parser = try $ start >> notFollowedBy space >> many1Till parser end -- | Parse string, case insensitive. stringAnyCase :: (Stream s m Char, UpdateSourcePos s Char) - => Text -> ParserT s st m Text + => Text -> ParsecT s st m Text stringAnyCase = fmap T.pack . stringAnyCase' . T.unpack stringAnyCase' :: (Stream s m Char, UpdateSourcePos s Char) - => String -> ParserT s st m String + => String -> ParsecT s st m String stringAnyCase' [] = string "" stringAnyCase' (x:xs) = do firstChar <- char (toUpper x) <|> char (toLower x) @@ -406,9 +406,9 @@ stringAnyCase' (x:xs) = do -- TODO rewrite by just adding to Sources stream? -- | Parse contents of 'str' using 'parser' and return result. parseFromString :: Monad m - => ParserT Sources st m r + => ParsecT Sources st m r -> Text - -> ParserT Sources st m r + -> ParsecT Sources st m r parseFromString parser str = do oldPos <- getPosition oldInput <- getInput @@ -423,9 +423,9 @@ parseFromString parser str = do -- | Like 'parseFromString' but specialized for 'ParserState'. -- This resets 'stateLastStrPos', which is almost always what we want. parseFromString' :: (Monad m, HasLastStrPosition u) - => ParserT Sources u m a + => ParsecT Sources u m a -> Text - -> ParserT Sources u m a + -> ParsecT Sources u m a parseFromString' parser str = do oldLastStrPos <- getLastStrPos <$> getState updateState $ setLastStrPos Nothing @@ -434,7 +434,7 @@ parseFromString' parser str = do return res -- | Parse raw line block up to and including blank lines. -lineClump :: Monad m => ParserT Sources st m Text +lineClump :: Monad m => ParsecT Sources st m Text lineClump = blanklines <|> (T.unlines <$> many1 (notFollowedBy blankline >> anyLine)) @@ -443,8 +443,8 @@ lineClump = blanklines -- pairs of open and close, which must be different. For example, -- @charsInBalanced '(' ')' anyChar@ will parse "(hello (there))" -- and return "hello (there)". -charsInBalanced :: (Stream s m Char, UpdateSourcePos s Char) => Char -> Char -> ParserT s st m Char - -> ParserT s st m Text +charsInBalanced :: (Stream s m Char, UpdateSourcePos s Char) => Char -> Char -> ParsecT s st m Char + -> ParsecT s st m Text charsInBalanced open close parser = try $ do char open let isDelim c = c == open || c == close @@ -463,7 +463,7 @@ charsInBalanced open close parser = try $ do -- | Parses an email address; returns original and corresponding -- escaped mailto: URI. -emailAddress :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (Text, Text) +emailAddress :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (Text, Text) emailAddress = try $ toResult <$> mailbox <*> (char '@' *> domain) where toResult mbox dom = let full = fromEntities $ T.pack $ mbox ++ '@':dom in (full, escapeURI $ "mailto:" <> full) @@ -486,11 +486,11 @@ emailAddress = try $ toResult <$> mailbox <*> (char '@' *> domain) isEmailPunct c = T.any (== c) "!\"#$%&'*+-/=?^_{|}~;" -uriScheme :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m Text +uriScheme :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m Text uriScheme = oneOfStringsCI (Set.toList schemes) -- | Parses a URI. Returns pair of original and URI-escaped version. -uri :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (Text, Text) +uri :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (Text, Text) uri = try $ do scheme <- uriScheme char ':' @@ -538,8 +538,8 @@ uri = try $ do -- and the source column at the beginning). Vertical displacement -- (source row) is ignored. withHorizDisplacement :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m a -- ^ Parser to apply - -> ParserT s st m (a, Int) -- ^ (result, displacement) + => ParsecT s st m a -- ^ Parsec to apply + -> ParsecT s st m (a, Int) -- ^ (result, displacement) withHorizDisplacement parser = do pos1 <- getPosition result <- parser @@ -574,12 +574,12 @@ sourcesDifference (Sources is1) (Sources is2) = go is1 is2 -- | Parses backslash, then applies character parser. escaped :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Char -- ^ Parser for character to escape - -> ParserT s st m Char + => ParsecT s st m Char -- ^ Parsec for character to escape + -> ParsecT s st m Char escaped parser = try $ char '\\' >> parser -- | Parse character entity. -characterReference :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m Char +characterReference :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m Char characterReference = try $ do char '&' ent <- many1Till nonspaceChar (char ';') @@ -592,10 +592,10 @@ characterReference = try $ do _ -> Prelude.fail "entity not found" -- | Parses a character reference and returns a Str element. -charRef :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m Inline +charRef :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m Inline charRef = Str . T.singleton <$> characterReference -lineBlockLine :: Monad m => ParserT Sources st m Text +lineBlockLine :: Monad m => ParsecT Sources st m Text lineBlockLine = try $ do char '|' char ' ' @@ -605,11 +605,11 @@ lineBlockLine = try $ do continuations <- many (try $ char ' ' >> anyLine) return $ white <> T.unwords (line : continuations) -blankLineBlockLine :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m Char +blankLineBlockLine :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m Char blankLineBlockLine = try (char '|' >> blankline) -- | Parses an RST-style line block and returns a list of strings. -lineBlockLines :: Monad m => ParserT Sources st m [Text] +lineBlockLines :: Monad m => ParsecT Sources st m [Text] lineBlockLines = try $ do lines' <- many1 (lineBlockLine <|> (T.singleton <$> blankLineBlockLine)) skipMany blankline @@ -618,7 +618,7 @@ lineBlockLines = try $ do -- | Removes the ParsecT layer from the monad transformer stack readWithM :: (Monad m, ToSources t) - => ParserT Sources st m a -- ^ parser + => ParsecT Sources st m a -- ^ parser -> st -- ^ initial state -> t -- ^ input -> m (Either PandocError a) @@ -630,7 +630,7 @@ readWithM parser state input = -- | Parse a string with a given parser and state readWith :: ToSources t - => Parser Sources st a + => Parsec Sources st a -> st -> t -> Either PandocError a @@ -638,7 +638,7 @@ readWith p t inp = runIdentity $ readWithM p t inp -- | Parse a string with @parser@ (for testing). testStringWith :: Show a - => ParserT Sources ParserState Identity a + => ParsecT Sources ParserState Identity a -> Text -> IO () testStringWith parser str = UTF8.putStrLn $ tshow $ @@ -653,7 +653,7 @@ testStringWith parser str = UTF8.putStrLn $ tshow $ -- (explicit or automatically generated). registerHeader :: (Stream s m a, HasReaderOptions st, HasLogMessages st, HasIdentifierList st) - => Attr -> Inlines -> ParserT s st m Attr + => Attr -> Inlines -> ParsecT s st m Attr registerHeader (ident,classes,kvs) header' = do ids <- extractIdentifierList <$> getState exts <- getOption readerExtensions @@ -677,8 +677,8 @@ registerHeader (ident,classes,kvs) header' = do -- This is used to prevent exponential blowups for things like: -- a**a*a**a*a**a*a**a*a**a*a**a*a** nested :: Stream s m a - => ParserT s ParserState m a - -> ParserT s ParserState m a + => ParsecT s ParserState m a + -> ParsecT s ParserState m a nested p = do nestlevel <- stateMaxNestingLevel <$> getState guard $ nestlevel > 0 @@ -695,7 +695,7 @@ token :: (Stream s m t) token pp pos match = tokenPrim (T.unpack . pp) (\_ t _ -> pos t) match infixr 5 <+?> -(<+?>) :: (Monoid a) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a +(<+?>) :: (Monoid a) => ParsecT s st m a -> ParsecT s st m a -> ParsecT s st m a a <+?> b = a >>= flip fmap (try b <|> return mempty) . mappend extractIdClass :: Attr -> Attr @@ -706,13 +706,13 @@ extractIdClass (ident, cls, kvs) = (ident', cls', kvs') kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) - => ParserT a st m b -- ^ parser to apply + => ParsecT a st m b -- ^ parser to apply -> (Text -> a) -- ^ convert Text to stream type -> [FilePath] -- ^ search path (directories) -> FilePath -- ^ path of file to include -> Maybe Int -- ^ start line (negative counts from end) -> Maybe Int -- ^ end line (negative counts from end) - -> ParserT a st m b + -> ParsecT a st m b insertIncludedFile parser toStream dirs f mbstartline mbendline = do oldPos <- getPosition oldInput <- getInput diff --git a/src/Text/Pandoc/Parsing/GridTable.hs b/src/Text/Pandoc/Parsing/GridTable.hs index 88c592477..cec8653f7 100644 --- a/src/Text/Pandoc/Parsing/GridTable.hs +++ b/src/Text/Pandoc/Parsing/GridTable.hs @@ -31,9 +31,8 @@ import Text.Pandoc.Builder (Blocks) import Text.Pandoc.Definition import Text.Pandoc.Parsing.Capabilities import Text.Pandoc.Parsing.General -import Text.Pandoc.Parsing.Types import Text.Pandoc.Sources -import Text.Parsec (Stream (..), optional, sepEndBy1, try) +import Text.Parsec (Stream (..), ParsecT, optional, sepEndBy1, try) import qualified Data.Text as T import qualified Text.GridTable as GT @@ -103,8 +102,8 @@ data TableNormalization -- blank lines, and ending with a footer (dashed line followed by blank -- line). gridTableWith :: (Monad m, Monad mf, HasLastStrPosition st, HasReaderOptions st) - => ParserT Sources st m (mf Blocks) -- ^ Block list parser - -> ParserT Sources st m (mf Blocks) + => ParsecT Sources st m (mf Blocks) -- ^ Block list parser + -> ParsecT Sources st m (mf Blocks) gridTableWith blocks = fmap tableFromComponents <$> gridTableWith' NoNormalization blocks @@ -113,8 +112,8 @@ gridTableWith blocks = fmap tableFromComponents <$> gridTableWith' :: (Monad m, Monad mf, HasReaderOptions st, HasLastStrPosition st) => TableNormalization - -> ParserT Sources st m (mf Blocks) -- ^ Block list parser - -> ParserT Sources st m (mf TableComponents) + -> ParsecT Sources st m (mf Blocks) -- ^ Block list parser + -> ParsecT Sources st m (mf TableComponents) gridTableWith' normalization blocks = do tbl <- GT.gridTable <* optional blanklines let blkTbl = GT.mapCells @@ -192,22 +191,22 @@ fractionalColumnWidths gt charColumns = -- 'lineParser', and 'footerParser'. tableWith :: (Stream s m Char, UpdateSourcePos s Char, HasReaderOptions st, Monad mf) - => ParserT s st m (mf [Blocks], [Alignment], [Int]) -- ^ header parser - -> ([Int] -> ParserT s st m (mf [Blocks])) -- ^ row parser - -> ParserT s st m sep -- ^ line parser - -> ParserT s st m end -- ^ footer parser - -> ParserT s st m (mf Blocks) + => ParsecT s st m (mf [Blocks], [Alignment], [Int]) -- ^ header parser + -> ([Int] -> ParsecT s st m (mf [Blocks])) -- ^ row parser + -> ParsecT s st m sep -- ^ line parser + -> ParsecT s st m end -- ^ footer parser + -> ParsecT s st m (mf Blocks) tableWith hp rp lp fp = fmap tableFromComponents <$> tableWith' NoNormalization hp rp lp fp tableWith' :: (Stream s m Char, UpdateSourcePos s Char, HasReaderOptions st, Monad mf) => TableNormalization - -> ParserT s st m (mf [Blocks], [Alignment], [Int]) -- ^ header parser - -> ([Int] -> ParserT s st m (mf [Blocks])) -- ^ row parser - -> ParserT s st m sep -- ^ line parser - -> ParserT s st m end -- ^ footer parser - -> ParserT s st m (mf TableComponents) + -> ParsecT s st m (mf [Blocks], [Alignment], [Int]) -- ^ header parser + -> ([Int] -> ParsecT s st m (mf [Blocks])) -- ^ row parser + -> ParsecT s st m sep -- ^ line parser + -> ParsecT s st m end -- ^ footer parser + -> ParsecT s st m (mf TableComponents) tableWith' n11n headerParser rowParser lineParser footerParser = try $ do (heads, aligns, indices) <- headerParser lines' <- sequence <$> rowParser indices `sepEndBy1` lineParser diff --git a/src/Text/Pandoc/Parsing/Lists.hs b/src/Text/Pandoc/Parsing/Lists.hs index 6f0c47ce2..bd12c6ac2 100644 --- a/src/Text/Pandoc/Parsing/Lists.hs +++ b/src/Text/Pandoc/Parsing/Lists.hs @@ -37,6 +37,7 @@ import Text.Pandoc.Shared (safeRead) import Text.Pandoc.Sources import Text.Parsec ( (<|>) + , ParsecT , Stream(..) , choice , getState @@ -48,7 +49,6 @@ import Text.Parsec , updateState ) import Text.Pandoc.Parsing.State -import Text.Pandoc.Parsing.Types (ParserT) import qualified Data.Map as M import qualified Data.Text as T @@ -56,7 +56,7 @@ import qualified Data.Text as T -- | Parses a roman numeral (uppercase or lowercase), returns number. romanNumeral :: (Stream s m Char, UpdateSourcePos s Char) => Bool -- ^ Uppercase if true - -> ParserT s st m Int + -> ParsecT s st m Int romanNumeral upperCase = do let rchar uc = char $ if upperCase then uc else toLower uc let one = rchar 'I' @@ -88,19 +88,19 @@ romanNumeral upperCase = do else return total -- | Parses an uppercase roman numeral and returns (UpperRoman, number). -upperRoman :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +upperRoman :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) upperRoman = do num <- romanNumeral True return (UpperRoman, num) -- | Parses a lowercase roman numeral and returns (LowerRoman, number). -lowerRoman :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +lowerRoman :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) lowerRoman = do num <- romanNumeral False return (LowerRoman, num) -- | Parses a decimal numeral and returns (Decimal, number). -decimal :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +decimal :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) decimal = do num <- many1 digit return (Decimal, fromMaybe 1 $ safeRead $ T.pack num) @@ -110,7 +110,7 @@ decimal = do -- example number is incremented in parser state, and the label -- (if present) is added to the label table. exampleNum :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s ParserState m (ListNumberStyle, Int) + => ParsecT s ParserState m (ListNumberStyle, Int) exampleNum = do char '@' lab <- mconcat . map T.pack <$> @@ -128,30 +128,30 @@ exampleNum = do return (Example, num) -- | Parses a '#' returns (DefaultStyle, 1). -defaultNum :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +defaultNum :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) defaultNum = do char '#' return (DefaultStyle, 1) -- | Parses a lowercase letter and returns (LowerAlpha, number). -lowerAlpha :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +lowerAlpha :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) lowerAlpha = do ch <- satisfy isAsciiLower return (LowerAlpha, ord ch - ord 'a' + 1) -- | Parses an uppercase letter and returns (UpperAlpha, number). -upperAlpha :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +upperAlpha :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) upperAlpha = do ch <- satisfy isAsciiUpper return (UpperAlpha, ord ch - ord 'A' + 1) -- | Parses a roman numeral i or I -romanOne :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m (ListNumberStyle, Int) +romanOne :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m (ListNumberStyle, Int) romanOne = (char 'i' >> return (LowerRoman, 1)) <|> (char 'I' >> return (UpperRoman, 1)) -- | Parses an ordered list marker and returns list attributes. -anyOrderedListMarker :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s ParserState m ListAttributes +anyOrderedListMarker :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s ParserState m ListAttributes anyOrderedListMarker = choice [delimParser numParser | delimParser <- [inPeriod, inOneParen, inTwoParens], numParser <- [decimal, exampleNum, defaultNum, romanOne, @@ -159,8 +159,8 @@ anyOrderedListMarker = choice -- | Parses a list number (num) followed by a period, returns list attributes. inPeriod :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m (ListNumberStyle, Int) - -> ParserT s st m ListAttributes + => ParsecT s st m (ListNumberStyle, Int) + -> ParsecT s st m ListAttributes inPeriod num = try $ do (style, start) <- num char '.' @@ -171,8 +171,8 @@ inPeriod num = try $ do -- | Parses a list number (num) followed by a paren, returns list attributes. inOneParen :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m (ListNumberStyle, Int) - -> ParserT s st m ListAttributes + => ParsecT s st m (ListNumberStyle, Int) + -> ParsecT s st m ListAttributes inOneParen num = try $ do (style, start) <- num char ')' @@ -180,8 +180,8 @@ inOneParen num = try $ do -- | Parses a list number (num) enclosed in parens, returns list attributes. inTwoParens :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m (ListNumberStyle, Int) - -> ParserT s st m ListAttributes + => ParsecT s st m (ListNumberStyle, Int) + -> ParsecT s st m ListAttributes inTwoParens num = try $ do char '(' (style, start) <- num @@ -193,7 +193,7 @@ inTwoParens num = try $ do orderedListMarker :: (Stream s m Char, UpdateSourcePos s Char) => ListNumberStyle -> ListNumberDelim - -> ParserT s ParserState m Int + -> ParsecT s ParserState m Int orderedListMarker style delim = do let num = defaultNum <|> -- # can continue any kind of list case style of diff --git a/src/Text/Pandoc/Parsing/Math.hs b/src/Text/Pandoc/Parsing/Math.hs index a2cfa1a07..d001dc82a 100644 --- a/src/Text/Pandoc/Parsing/Math.hs +++ b/src/Text/Pandoc/Parsing/Math.hs @@ -17,20 +17,19 @@ where import Control.Monad (mzero, when) import Data.Text (Text) -import Text.Parsec ((<|>), Stream(..), notFollowedBy, skipMany, try) +import Text.Parsec ((<|>), ParsecT, Stream(..), notFollowedBy, skipMany, try) import Text.Pandoc.Options ( Extension(Ext_tex_math_dollars, Ext_tex_math_single_backslash, Ext_tex_math_double_backslash) ) import Text.Pandoc.Parsing.Capabilities (HasReaderOptions, guardEnabled) import Text.Pandoc.Parsing.General -import Text.Pandoc.Parsing.Types (ParserT) import Text.Pandoc.Shared (trimMath) import Text.Pandoc.Sources (UpdateSourcePos, anyChar, char, digit, newline, satisfy, space, string) import qualified Data.Text as T -mathInlineWith :: (Stream s m Char, UpdateSourcePos s Char) => Text -> Text -> ParserT s st m Text +mathInlineWith :: (Stream s m Char, UpdateSourcePos s Char) => Text -> Text -> ParsecT s st m Text mathInlineWith op cl = try $ do textStr op when (op == "$") $ notFollowedBy space @@ -51,10 +50,10 @@ mathInlineWith op cl = try $ do notFollowedBy digit -- to prevent capture of $5 return $ trimMath $ T.concat words' where - inBalancedBraces :: (Stream s m Char, UpdateSourcePos s Char) => Int -> Text -> ParserT s st m Text + inBalancedBraces :: (Stream s m Char, UpdateSourcePos s Char) => Int -> Text -> ParsecT s st m Text inBalancedBraces n = fmap T.pack . inBalancedBraces' n . T.unpack - inBalancedBraces' :: (Stream s m Char, UpdateSourcePos s Char) => Int -> String -> ParserT s st m String + inBalancedBraces' :: (Stream s m Char, UpdateSourcePos s Char) => Int -> String -> ParsecT s st m String inBalancedBraces' 0 "" = do c <- anyChar if c == '{' @@ -71,14 +70,14 @@ mathInlineWith op cl = try $ do '{' -> inBalancedBraces' (numOpen + 1) (c:xs) _ -> inBalancedBraces' numOpen (c:xs) -mathDisplayWith :: (Stream s m Char, UpdateSourcePos s Char) => Text -> Text -> ParserT s st m Text +mathDisplayWith :: (Stream s m Char, UpdateSourcePos s Char) => Text -> Text -> ParsecT s st m Text mathDisplayWith op cl = try $ fmap T.pack $ do textStr op many1Till (satisfy (/= '\n') <|> (newline <* notFollowedBy' blankline)) (try $ textStr cl) mathDisplay :: (HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Text + => ParsecT s st m Text mathDisplay = (guardEnabled Ext_tex_math_dollars >> mathDisplayWith "$$" "$$") <|> (guardEnabled Ext_tex_math_single_backslash >> @@ -87,7 +86,7 @@ mathDisplay = mathDisplayWith "\\\\[" "\\\\]") mathInline :: (HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Text + => ParsecT s st m Text mathInline = (guardEnabled Ext_tex_math_dollars >> mathInlineWith "$" "$") <|> (guardEnabled Ext_tex_math_single_backslash >> diff --git a/src/Text/Pandoc/Parsing/Smart.hs b/src/Text/Pandoc/Parsing/Smart.hs index 52ad27119..fdc824e2c 100644 --- a/src/Text/Pandoc/Parsing/Smart.hs +++ b/src/Text/Pandoc/Parsing/Smart.hs @@ -33,10 +33,10 @@ import Text.Pandoc.Options import Text.Pandoc.Sources import Text.Pandoc.Parsing.Capabilities import Text.Pandoc.Parsing.General -import Text.Pandoc.Parsing.Types (ParserT) import Text.Parsec ( (<|>) , Stream(..) + , ParsecT , choice , lookAhead , manyTill @@ -53,8 +53,8 @@ import qualified Text.Pandoc.Builder as B smartPunctuation :: (HasReaderOptions st, HasLastStrPosition st, HasQuoteContext st m, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines - -> ParserT s st m Inlines + => ParsecT s st m Inlines + -> ParsecT s st m Inlines smartPunctuation inlineParser = do guardEnabled Ext_smart choice [ quoted inlineParser, apostrophe, doubleCloseQuote, dash, ellipses ] @@ -63,16 +63,16 @@ smartPunctuation inlineParser = do -- quoting conventions. quoted :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines - -> ParserT s st m Inlines + => ParsecT s st m Inlines + -> ParsecT s st m Inlines quoted inlineParser = doubleQuoted inlineParser <|> singleQuoted inlineParser -- | Parses inline text in single quotes, assumes English quoting -- conventions. singleQuoted :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines - -> ParserT s st m Inlines + => ParsecT s st m Inlines + -> ParsecT s st m Inlines singleQuoted inlineParser = do singleQuoteStart (B.singleQuoted . mconcat <$> @@ -84,8 +84,8 @@ singleQuoted inlineParser = do -- conventions. doubleQuoted :: (HasQuoteContext st m, HasLastStrPosition st, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines - -> ParserT s st m Inlines + => ParsecT s st m Inlines + -> ParsecT s st m Inlines doubleQuoted inlineParser = do doubleQuoteStart (B.doubleQuoted . mconcat <$> @@ -93,7 +93,7 @@ doubleQuoted inlineParser = do (withQuoteContext InDoubleQuote (manyTill inlineParser doubleQuoteEnd))) <|> pure (B.str "\8220") -charOrRef :: (Stream s m Char, UpdateSourcePos s Char) => [Char] -> ParserT s st m Char +charOrRef :: (Stream s m Char, UpdateSourcePos s Char) => [Char] -> ParsecT s st m Char charOrRef cs = oneOf cs <|> try (do c <- characterReference guard (c `elem` cs) @@ -109,7 +109,7 @@ charOrRef cs = -- Gobbles the quote character on success. singleQuoteStart :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m () + => ParsecT s st m () singleQuoteStart = do failIfInQuoteContext InSingleQuote -- single quote start can't be right after str @@ -119,7 +119,7 @@ singleQuoteStart = do void $ lookAhead (satisfy (not . isSpaceChar)) singleQuoteEnd :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m () + => ParsecT s st m () singleQuoteEnd = try $ do charOrRef "'\8217\146" notFollowedBy alphaNum @@ -137,7 +137,7 @@ singleQuoteEnd = try $ do doubleQuoteStart :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m () + => ParsecT s st m () doubleQuoteStart = do failIfInQuoteContext InDoubleQuote guard =<< notAfterString @@ -146,24 +146,24 @@ doubleQuoteStart = do -- | Parses a closing quote character. doubleQuoteEnd :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m () + => ParsecT s st m () doubleQuoteEnd = void (charOrRef "\"\8221\148") -- | Parses an ASCII apostrophe (@'@) or right single quotation mark and -- returns a RIGHT SINGLE QUOtatiON MARK character. apostrophe :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines + => ParsecT s st m Inlines apostrophe = (char '\'' <|> char '\8217') >> return (B.str "\8217") -- | Parses an ASCII quotation mark character and returns a RIGHT DOUBLE -- QUOTATION MARK. doubleCloseQuote :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines + => ParsecT s st m Inlines doubleCloseQuote = B.str "\8221" <$ char '"' -- | Parses three dots as HORIZONTAL ELLIPSIS. ellipses :: (Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines + => ParsecT s st m Inlines ellipses = try (string "..." >> return (B.str "\8230")) -- | Parses two hyphens as EN DASH and three as EM DASH. @@ -172,7 +172,7 @@ ellipses = try (string "..." >> return (B.str "\8230")) -- parsed as EM DASH, and one hyphen is parsed as EN DASH if it is -- followed by a digit. dash :: (HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) - => ParserT s st m Inlines + => ParsecT s st m Inlines dash = try $ do oldDashes <- extensionEnabled Ext_old_dashes <$> getOption readerExtensions if oldDashes diff --git a/src/Text/Pandoc/Parsing/State.hs b/src/Text/Pandoc/Parsing/State.hs index 9e59b4c7e..1efb90b73 100644 --- a/src/Text/Pandoc/Parsing/State.hs +++ b/src/Text/Pandoc/Parsing/State.hs @@ -32,7 +32,7 @@ import Text.Pandoc.Definition (Attr, Meta, Target, nullMeta) import Text.Pandoc.Logging (LogMessage) import Text.Pandoc.Options (ReaderOptions) import Text.Pandoc.Parsing.Capabilities -import Text.Pandoc.Parsing.Types +import Text.Pandoc.Parsing.Future import Text.Pandoc.TeX (Macro) import qualified Data.Map as M diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index a055c1310..c2f21729e 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -32,7 +32,7 @@ import Data.Functor.Identity (runIdentity) import Data.Typeable import Text.Pandoc.Parsing (runParserT, getInput, getPosition, runF, defaultParserState, option, many1, anyChar, - Sources(..), ToSources(..), ParserT, Future, + Sources(..), ToSources(..), ParsecT, Future, sourceName, sourceLine, incSourceLine) import Text.Pandoc.Walk (walk) import qualified Data.Text as T @@ -80,7 +80,7 @@ sourceToToks (pos, s) = map adjust $ tokenize (sourceName pos) s metaValueParser :: Monad m - => ReaderOptions -> ParserT Sources st m (Future st MetaValue) + => ReaderOptions -> ParsecT Sources st m (Future st MetaValue) metaValueParser opts = do inp <- option "" $ T.pack <$> many1 anyChar let toks = concatMap sourceToToks (unSources (toSources inp)) diff --git a/src/Text/Pandoc/Readers/Creole.hs b/src/Text/Pandoc/Readers/Creole.hs index ad848ada7..316e416d3 100644 --- a/src/Text/Pandoc/Readers/Creole.hs +++ b/src/Text/Pandoc/Readers/Creole.hs @@ -36,7 +36,7 @@ readCreole opts s = do Left e -> throwError e Right d -> return d -type CRLParser = ParserT Sources ParserState +type CRLParser = ParsecT Sources ParserState -- -- Utility functions diff --git a/src/Text/Pandoc/Readers/Docx/Fields.hs b/src/Text/Pandoc/Readers/Docx/Fields.hs index 637e4fc88..79c4cca3f 100644 --- a/src/Text/Pandoc/Readers/Docx/Fields.hs +++ b/src/Text/Pandoc/Readers/Docx/Fields.hs @@ -17,8 +17,7 @@ module Text.Pandoc.Readers.Docx.Fields ( FieldInfo(..) import Data.Functor (($>), void) import qualified Data.Text as T -import Text.Parsec -import Text.Parsec.Text (Parser) +import Text.Pandoc.Parsing type URL = T.Text type Anchor = T.Text @@ -33,6 +32,8 @@ data FieldInfo = HyperlinkField URL | UnknownField deriving (Show) +type Parser = Parsec T.Text () + parseFieldInfo :: T.Text -> Either ParseError FieldInfo parseFieldInfo = parse fieldInfo "" diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs index d1b673611..1ed24bb34 100644 --- a/src/Text/Pandoc/Readers/DokuWiki.hs +++ b/src/Text/Pandoc/Readers/DokuWiki.hs @@ -46,12 +46,12 @@ readDokuWiki opts s = do Left e -> throwError $ PandocParsecError sources e Right d -> return d -type DWParser = ParserT Sources ParserState +type DWParser = ParsecT Sources ParserState -- * Utility functions -- | Parse end-of-line, which can be either a newline or end-of-file. -eol :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m () +eol :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m () eol = void newline <|> eof nested :: PandocMonad m => DWParser m a -> DWParser m a diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index b3a2b8c42..7893cc478 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -1028,7 +1028,7 @@ isCommentTag = tagComment (const True) -- | Matches a stretch of HTML in balanced tags. htmlInBalanced :: Monad m => (Tag Text -> Bool) - -> ParserT Sources st m Text + -> ParsecT Sources st m Text htmlInBalanced f = try $ do lookAhead (char '<') sources <- getInput @@ -1077,7 +1077,7 @@ hasTagWarning _ = False -- | Matches a tag meeting a certain condition. htmlTag :: (HasReaderOptions st, Monad m) => (Tag Text -> Bool) - -> ParserT Sources st m (Tag Text, Text) + -> ParsecT Sources st m (Tag Text, Text) htmlTag f = try $ do lookAhead (char '<') startpos <- getPosition diff --git a/src/Text/Pandoc/Readers/HTML/Types.hs b/src/Text/Pandoc/Readers/HTML/Types.hs index f9b5d2b37..cc26319a1 100644 --- a/src/Text/Pandoc/Readers/HTML/Types.hs +++ b/src/Text/Pandoc/Readers/HTML/Types.hs @@ -33,12 +33,12 @@ import Text.Pandoc.Options (ReaderOptions) import Text.Pandoc.Parsing ( HasIdentifierList (..), HasLastStrPosition (..), HasLogMessages (..) , HasMacros (..), HasQuoteContext (..), HasReaderOptions (..) - , ParserT, ParserState, QuoteContext (NoQuote) + , ParsecT, ParserState, QuoteContext (NoQuote) ) import Text.Pandoc.TeX (Macro) -- | HTML parser type -type HTMLParser m s = ParserT s HTMLState (ReaderT HTMLLocal m) +type HTMLParser m s = ParsecT s HTMLState (ReaderT HTMLLocal m) -- | HTML parser, expecting @Tag Text@ as tokens. type TagParser m = HTMLParser m [Tag Text] diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 083a87206..b077c92f4 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -134,7 +134,7 @@ resolveRefs _ x = x rawLaTeXBlock :: (PandocMonad m, HasMacros s, HasReaderOptions s) - => ParserT Sources s m Text + => ParsecT Sources s m Text rawLaTeXBlock = do lookAhead (try (char '\\' >> letter)) toks <- getInputTokens @@ -165,7 +165,7 @@ beginOrEndCommand = try $ do (txt <> untokenize rawargs) rawLaTeXInline :: (PandocMonad m, HasMacros s, HasReaderOptions s) - => ParserT Sources s m Text + => ParsecT Sources s m Text rawLaTeXInline = do lookAhead (try (char '\\' >> letter)) toks <- getInputTokens @@ -179,7 +179,7 @@ rawLaTeXInline = do finalbraces <- mconcat <$> many (try (string "{}")) -- see #5439 return $ raw <> T.pack finalbraces -inlineCommand :: PandocMonad m => ParserT Sources ParserState m Inlines +inlineCommand :: PandocMonad m => ParsecT Sources ParserState m Inlines inlineCommand = do lookAhead (try (char '\\' >> letter)) toks <- getInputTokens diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs index 3906dfaac..90dcabd75 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs @@ -120,8 +120,6 @@ import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline, import Text.Pandoc.TeX (ExpansionPoint (..), Macro (..), ArgSpec (..), Tok (..), TokType (..)) import Text.Pandoc.Shared -import Text.Parsec.Pos -import Text.Parsec (Stream(uncons)) import Text.Pandoc.Walk newtype DottedNum = DottedNum [Int] @@ -263,7 +261,7 @@ instance Monad m => Stream TokStream m Tok where uncons (TokStream _ []) = return Nothing uncons (TokStream _ (t:ts)) = return $ Just (t, TokStream False ts) -type LP m = ParserT TokStream LaTeXState m +type LP m = ParsecT TokStream LaTeXState m withVerbatimMode :: PandocMonad m => LP m a -> LP m a withVerbatimMode parser = do @@ -278,7 +276,7 @@ withVerbatimMode parser = do rawLaTeXParser :: (PandocMonad m, HasMacros s, HasReaderOptions s, Show a) => [Tok] -> LP m a -> LP m a - -> ParserT Sources s m (a, Text) + -> ParsecT Sources s m (a, Text) rawLaTeXParser toks parser valParser = do pstate <- getState let lstate = def{ sOptions = extractReaderOptions pstate } @@ -318,7 +316,7 @@ rawLaTeXParser toks parser valParser = do return (val, result') applyMacros :: (PandocMonad m, HasMacros s, HasReaderOptions s) - => Text -> ParserT Sources s m Text + => Text -> ParsecT Sources s m Text applyMacros s = (guardDisabled Ext_latex_macros >> return s) <|> do let retokenize = untokenize <$> many anyTok pstate <- getState @@ -346,7 +344,7 @@ tokenizeSources = concatMap tokenizeSource . unSources -- Return tokens from input sources. Ensure that starting position is -- correct. -getInputTokens :: PandocMonad m => ParserT Sources s m [Tok] +getInputTokens :: PandocMonad m => ParsecT Sources s m [Tok] getInputTokens = do pos <- getPosition ss <- getInput @@ -883,7 +881,7 @@ dimenarg = try $ do guard $ rest `elem` ["", "pt","pc","in","bp","cm","mm","dd","cc","sp"] return $ T.pack ['=' | ch] <> minus <> s -ignore :: (Monoid a, PandocMonad m) => Text -> ParserT s u m a +ignore :: (Monoid a, PandocMonad m) => Text -> ParsecT s u m a ignore raw = do pos <- getPosition report $ SkippedContent raw pos diff --git a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs index b7413a635..ac13f6f0c 100644 --- a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs +++ b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs @@ -43,7 +43,7 @@ import Text.Pandoc.Parsing try, skipMany1, runParser, - Parser ) + Parsec ) import Control.Applicative ((<|>)) import Control.Monad (void) import qualified Data.Map as M @@ -122,7 +122,7 @@ doSIlist tok = do mconcat (intersperse (str "," <> space) (init xs)) <> text ", & " <> last xs -parseNum :: Parser Text () Inlines +parseNum :: Parsec Text () Inlines parseNum = (mconcat <$> many parseNumPart) <* eof minus :: Text @@ -132,7 +132,7 @@ hyphenToMinus :: Inline -> Inline hyphenToMinus (Str t) = Str (T.replace "-" minus t) hyphenToMinus x = x -parseNumPart :: Parser Text () Inlines +parseNumPart :: Parsec Text () Inlines parseNumPart = parseDecimalNum <|> parseComma <|> @@ -145,7 +145,7 @@ parseNumPart = where parseDecimalNum, parsePlusMinus, parsePM, parseComma, parseI, parseX, - parseExp, parseSpace :: Parser Text () Inlines + parseExp, parseSpace :: Parsec Text () Inlines parseDecimalNum = try $ do pref <- option mempty $ (mempty <$ char '+') <|> (minus <$ char '-') basenum' <- many1 (satisfy (\c -> isDigit c || c == '.')) diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs index 1141af66f..715efff54 100644 --- a/src/Text/Pandoc/Readers/Man.hs +++ b/src/Text/Pandoc/Readers/Man.hs @@ -31,8 +31,7 @@ import Text.Pandoc.Parsing import Text.Pandoc.Walk (query) import Text.Pandoc.Shared (mapLeft) import Text.Pandoc.Readers.Roff -- TODO explicit imports -import qualified Text.Parsec as Parsec -import Text.Parsec.Pos (updatePosString) +import qualified Text.Pandoc.Parsing as P import qualified Data.Foldable as Foldable data ManState = ManState { readerOptions :: ReaderOptions @@ -45,7 +44,7 @@ instance Default ManState where , metadata = nullMeta , tableCellsPlain = True } -type ManParser m = ParserT [RoffToken] ManState m +type ManParser m = P.ParsecT [RoffToken] ManState m -- | Read man (troff) from an input string and return a Pandoc document. @@ -65,7 +64,7 @@ readMan opts s = do readWithMTokens :: PandocMonad m - => ParserT [RoffToken] ManState m a -- ^ parser + => ParsecT [RoffToken] ManState m a -- ^ parser -> ManState -- ^ initial state -> [RoffToken] -- ^ input -> m (Either PandocError a) @@ -180,14 +179,16 @@ parseNewParagraph = do -- Parser: [RoffToken] -> Pandoc -- -msatisfy :: Monad m => (RoffToken -> Bool) -> ParserT [RoffToken] st m RoffToken -msatisfy predic = tokenPrim show nextPos testTok +msatisfy :: Monad m + => (RoffToken -> Bool) -> P.ParsecT [RoffToken] st m RoffToken +msatisfy predic = P.tokenPrim show nextPos testTok where testTok t = if predic t then Just t else Nothing nextPos _pos _x (ControlLine _ _ pos':_) = pos' - nextPos pos _x _xs = updatePosString - (setSourceColumn - (setSourceLine pos $ sourceLine pos + 1) 1) "" + nextPos pos _x _xs = P.updatePosString + (P.setSourceColumn + (P.setSourceLine pos $ + P.sourceLine pos + 1) 1) "" mtoken :: PandocMonad m => ManParser m RoffToken mtoken = msatisfy (const True) @@ -431,7 +432,7 @@ listItem mbListType = try $ do (arg1 : _) -> do let cs = linePartsToText arg1 let cs' = if not (T.any (== '.') cs || T.any (== ')') cs) then cs <> "." else cs - let lt = case Parsec.runParser anyOrderedListMarker defaultParserState + let lt = case P.runParser anyOrderedListMarker defaultParserState "list marker" cs' of Right (start, listtype, listdelim) | cs == cs' -> Ordered (start, listtype, listdelim) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 3a63beb04..773119fa3 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -55,7 +55,7 @@ import Text.Pandoc.XML (fromEntities) import Text.Pandoc.Readers.Metadata (yamlBsToMeta, yamlBsToRefs, yamlMetaBlock) -- import Debug.Trace (traceShowId) -type MarkdownParser m = ParserT Sources ParserState m +type MarkdownParser m = ParsecT Sources ParserState m type F = Future ParserState @@ -157,14 +157,14 @@ inList = do ctx <- stateParserContext <$> getState guard (ctx == ListItemState) -spnl :: PandocMonad m => ParserT Sources st m () +spnl :: PandocMonad m => ParsecT Sources st m () spnl = try $ do skipSpaces optional newline skipSpaces notFollowedBy (char '\n') -spnl' :: PandocMonad m => ParserT Sources st m Text +spnl' :: PandocMonad m => ParsecT Sources st m Text spnl' = try $ do xs <- many spaceChar ys <- option "" $ try $ (:) <$> newline @@ -591,7 +591,7 @@ registerImplicitHeader raw attr@(ident, _, _) -- hrule block -- -hrule :: PandocMonad m => ParserT Sources st m (F Blocks) +hrule :: PandocMonad m => ParsecT Sources st m (F Blocks) hrule = try $ do skipSpaces start <- satisfy isHruleChar @@ -611,7 +611,7 @@ indentedLine = indentSpaces >> anyLineNewline blockDelimiter :: PandocMonad m => (Char -> Bool) -> Maybe Int - -> ParserT Sources ParserState m Int + -> ParsecT Sources ParserState m Int blockDelimiter f len = try $ do skipNonindentSpaces c <- lookAhead (satisfy f) @@ -759,7 +759,7 @@ lhsCodeBlockBirdWith c = try $ do blanklines return $ T.intercalate "\n" lns' -birdTrackLine :: PandocMonad m => Char -> ParserT Sources st m Text +birdTrackLine :: PandocMonad m => Char -> ParsecT Sources st m Text birdTrackLine c = try $ do char c -- allow html tags on left margin: @@ -1204,7 +1204,7 @@ lineBlock = do -- and the length including trailing space. dashedLine :: PandocMonad m => Char - -> ParserT Sources st m (Int, Int) + -> ParsecT Sources st m (Int, Int) dashedLine ch = do dashes <- many1 (char ch) sp <- many spaceChar @@ -1434,7 +1434,7 @@ pipeTableCell = return $ B.plain <$> result) <|> return mempty -pipeTableHeaderPart :: PandocMonad m => ParserT Sources st m (Alignment, Int) +pipeTableHeaderPart :: PandocMonad m => ParsecT Sources st m (Alignment, Int) pipeTableHeaderPart = try $ do skipMany spaceChar left <- optionMaybe (char ':') @@ -1450,7 +1450,7 @@ pipeTableHeaderPart = try $ do (Just _,Just _) -> AlignCenter, len) -- Succeed only if current line contains a pipe. -scanForPipe :: PandocMonad m => ParserT Sources st m () +scanForPipe :: PandocMonad m => ParsecT Sources st m () scanForPipe = do Sources inps <- getInput let ln = case inps of @@ -1727,7 +1727,7 @@ whitespace = spaceChar >> return <$> (lb <|> regsp) <?> "whitespace" where lb = spaceChar >> skipMany spaceChar >> option B.space (endline >> return B.linebreak) regsp = skipMany spaceChar >> return B.space -nonEndline :: PandocMonad m => ParserT Sources st m Char +nonEndline :: PandocMonad m => ParsecT Sources st m Char nonEndline = satisfy (/='\n') str :: PandocMonad m => MarkdownParser m (F Inlines) @@ -2011,7 +2011,7 @@ rawLaTeXInline' = do s <- rawLaTeXInline return $ return $ B.rawInline "tex" s -- "tex" because it might be context -rawConTeXtEnvironment :: PandocMonad m => ParserT Sources st m Text +rawConTeXtEnvironment :: PandocMonad m => ParsecT Sources st m Text rawConTeXtEnvironment = try $ do string "\\start" completion <- inBrackets (letter <|> digit <|> spaceChar) @@ -2020,7 +2020,7 @@ rawConTeXtEnvironment = try $ do (try $ string "\\stop" >> textStr completion) return $ "\\start" <> completion <> T.concat contents <> "\\stop" <> completion -inBrackets :: PandocMonad m => ParserT Sources st m Char -> ParserT Sources st m Text +inBrackets :: PandocMonad m => ParsecT Sources st m Char -> ParsecT Sources st m Text inBrackets parser = do char '[' contents <- manyChar parser diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 056f54812..33fcace2a 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -69,7 +69,7 @@ data MWState = MWState { mwOptions :: ReaderOptions , mwInTT :: Bool } -type MWParser m = ParserT Sources MWState m +type MWParser m = ParsecT Sources MWState m instance HasReaderOptions MWState where extractReaderOptions = mwOptions diff --git a/src/Text/Pandoc/Readers/Metadata.hs b/src/Text/Pandoc/Readers/Metadata.hs index 15f981c25..05c1abc75 100644 --- a/src/Text/Pandoc/Readers/Metadata.hs +++ b/src/Text/Pandoc/Readers/Metadata.hs @@ -35,9 +35,9 @@ import Text.Pandoc.Parsing hiding (tableWith, parse) import qualified Text.Pandoc.UTF8 as UTF8 yamlBsToMeta :: (PandocMonad m, HasLastStrPosition st) - => ParserT Sources st m (Future st MetaValue) + => ParsecT Sources st m (Future st MetaValue) -> B.ByteString - -> ParserT Sources st m (Future st Meta) + -> ParsecT Sources st m (Future st Meta) yamlBsToMeta pMetaValue bstr = do case Yaml.decodeAllEither' bstr of Right (Object o:_) -> fmap Meta <$> yamlMap pMetaValue o @@ -50,10 +50,10 @@ yamlBsToMeta pMetaValue bstr = do -- Returns filtered list of references. yamlBsToRefs :: (PandocMonad m, HasLastStrPosition st) - => ParserT Sources st m (Future st MetaValue) + => ParsecT Sources st m (Future st MetaValue) -> (Text -> Bool) -- ^ Filter for id -> B.ByteString - -> ParserT Sources st m (Future st [MetaValue]) + -> ParsecT Sources st m (Future st [MetaValue]) yamlBsToRefs pMetaValue idpred bstr = case Yaml.decodeAllEither' bstr of Right (Object m : _) -> do @@ -74,9 +74,9 @@ yamlBsToRefs pMetaValue idpred bstr = $ T.pack $ Yaml.prettyPrintParseException err' normalizeMetaValue :: (PandocMonad m, HasLastStrPosition st) - => ParserT Sources st m (Future st MetaValue) + => ParsecT Sources st m (Future st MetaValue) -> Text - -> ParserT Sources st m (Future st MetaValue) + -> ParsecT Sources st m (Future st MetaValue) normalizeMetaValue pMetaValue x = -- Note: a standard quoted or unquoted YAML value will -- not end in a newline, but a "block" set off with @@ -92,9 +92,9 @@ normalizeMetaValue pMetaValue x = isSpaceChar _ = False yamlToMetaValue :: (PandocMonad m, HasLastStrPosition st) - => ParserT Sources st m (Future st MetaValue) + => ParsecT Sources st m (Future st MetaValue) -> Value - -> ParserT Sources st m (Future st MetaValue) + -> ParsecT Sources st m (Future st MetaValue) yamlToMetaValue pMetaValue v = case v of String t -> normalizeMetaValue pMetaValue t @@ -112,9 +112,9 @@ yamlToMetaValue pMetaValue v = Object o -> fmap MetaMap <$> yamlMap pMetaValue o yamlMap :: (PandocMonad m, HasLastStrPosition st) - => ParserT Sources st m (Future st MetaValue) + => ParsecT Sources st m (Future st MetaValue) -> Object - -> ParserT Sources st m (Future st (M.Map Text MetaValue)) + -> ParsecT Sources st m (Future st (M.Map Text MetaValue)) yamlMap pMetaValue o = do case fromJSON (Object o) of Error err' -> throwError $ PandocParseError $ T.pack err' @@ -131,8 +131,8 @@ yamlMap pMetaValue o = do -- | Parse a YAML metadata block using the supplied 'MetaValue' parser. yamlMetaBlock :: (HasLastStrPosition st, PandocMonad m) - => ParserT Sources st m (Future st MetaValue) - -> ParserT Sources st m (Future st Meta) + => ParsecT Sources st m (Future st MetaValue) + -> ParsecT Sources st m (Future st Meta) yamlMetaBlock parser = try $ do string "---" blankline @@ -143,5 +143,5 @@ yamlMetaBlock parser = try $ do optional blanklines yamlBsToMeta parser $ UTF8.fromText rawYaml -stopLine :: Monad m => ParserT Sources st m () +stopLine :: Monad m => ParsecT Sources st m () stopLine = try $ (string "---" <|> string "...") >> blankline >> return () diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index a0d4534f1..c6a5ff06c 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -23,7 +23,7 @@ import Control.Monad.Reader import Control.Monad.Except (throwError) import Data.Bifunctor import Data.Default -import Data.List (transpose, uncons) +import Data.List (transpose) import qualified Data.Map as M import qualified Data.Set as Set import Data.Maybe (fromMaybe, isNothing, maybeToList) @@ -83,7 +83,7 @@ instance Default MuseEnv where , museInPara = False } -type MuseParser m = ParserT Sources MuseState (ReaderT MuseEnv m) +type MuseParser m = ParsecT Sources MuseState (ReaderT MuseEnv m) instance HasReaderOptions MuseState where extractReaderOptions = museOptions @@ -156,7 +156,7 @@ firstColumn = getPosition >>= \pos -> guard (sourceColumn pos == 1) -- * Parsers -- | Parse end-of-line, which can be either a newline or end-of-file. -eol :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s st m () +eol :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m () eol = void newline <|> eof getIndent :: PandocMonad m @@ -652,7 +652,10 @@ museToPandocTable (MuseTable caption headers body footers) = [TableBody nullAttr 0 [] $ map toRow $ rows ++ body ++ footers] (TableFoot nullAttr []) where attrs = (AlignDefault, ColWidthDefault) <$ transpose (headers ++ body ++ footers) - (headRow, rows) = fromMaybe ([], []) $ uncons headers + (headRow, rows) = + case headers of + (r:rs) -> (r, rs) + [] -> ([], []) toRow = Row nullAttr . map B.simpleCell toHeaderRow l = [toRow l | not (null l)] diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 21e42876c..0821b6b69 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -114,7 +114,7 @@ import Control.Monad (guard) import Control.Monad.Reader (ReaderT) -- | The parser used to read org files. -type OrgParser m = ParserT Sources OrgParserState (ReaderT OrgParserLocal m) +type OrgParser m = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) -- -- Adaptions and specializations of parsing utilities @@ -163,7 +163,7 @@ inList = do -- | Parse in different context withContext :: Monad m => ParserContext -- ^ New parser context - -> OrgParser m a -- ^ Parser to run in that context + -> OrgParser m a -- ^ Parsec to run in that context -> OrgParser m a withContext context parser = do oldContext <- orgStateParserContext <$> getState @@ -173,7 +173,7 @@ withContext context parser = do return result -- --- Parser state functions +-- Parsec state functions -- -- | Get an export setting. diff --git a/src/Text/Pandoc/Readers/RIS.hs b/src/Text/Pandoc/Readers/RIS.hs index d4d471050..36335105c 100644 --- a/src/Text/Pandoc/Readers/RIS.hs +++ b/src/Text/Pandoc/Readers/RIS.hs @@ -59,7 +59,7 @@ readRIS _opts inp = do B.doc mempty Left e -> throwError e -type RISParser m = ParserT Sources () m +type RISParser m = ParsecT Sources () m risLine :: PandocMonad m => RISParser m (Text, Text) risLine = do diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 0b824ad33..e9e53ae46 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -55,7 +55,7 @@ readRST opts s = do Right result -> return result Left e -> throwError e -type RSTParser m = ParserT Sources ParserState m +type RSTParser m = ParsecT Sources ParserState m -- -- Constants and data structure definitions @@ -355,7 +355,7 @@ singleHeader' = try $ do -- hrule block -- -hrule :: Monad m => ParserT Sources st m Blocks +hrule :: Monad m => ParsecT Sources st m Blocks hrule = try $ do chr <- oneOf underlineChars count 3 (char chr) @@ -370,7 +370,7 @@ hrule = try $ do -- read a line indented by a given string indentedLine :: (HasReaderOptions st, Monad m) - => Int -> ParserT Sources st m Text + => Int -> ParsecT Sources st m Text indentedLine indents = try $ do lookAhead spaceChar gobbleAtMostSpaces indents @@ -379,7 +379,7 @@ indentedLine indents = try $ do -- one or more indented lines, possibly separated by blank lines. -- any amount of indentation will work. indentedBlock :: (HasReaderOptions st, Monad m) - => ParserT Sources st m Text + => ParsecT Sources st m Text indentedBlock = try $ do indents <- length <$> lookAhead (many1 spaceChar) lns <- many1 $ try $ do b <- option "" blanklines @@ -388,20 +388,20 @@ indentedBlock = try $ do optional blanklines return $ T.unlines lns -quotedBlock :: Monad m => ParserT Sources st m Text +quotedBlock :: Monad m => ParsecT Sources st m Text quotedBlock = try $ do quote <- lookAhead $ oneOf "!\"#$%&'()*+,-./:;<=>?@[\\]^_`{|}~" lns <- many1 $ lookAhead (char quote) >> anyLine optional blanklines return $ T.unlines lns -codeBlockStart :: Monad m => ParserT Sources st m Char +codeBlockStart :: Monad m => ParsecT Sources st m Char codeBlockStart = string "::" >> blankline >> blankline -codeBlock :: Monad m => ParserT Sources ParserState m Blocks +codeBlock :: Monad m => ParsecT Sources ParserState m Blocks codeBlock = try $ codeBlockStart >> codeBlockBody -codeBlockBody :: Monad m => ParserT Sources ParserState m Blocks +codeBlockBody :: Monad m => ParsecT Sources ParserState m Blocks codeBlockBody = do lang <- stateRstHighlight <$> getState try $ B.codeBlockWith ("", maybeToList lang, []) . stripTrailingNewlines <$> @@ -417,14 +417,14 @@ lhsCodeBlock = try $ do return $ B.codeBlockWith ("", ["haskell","literate"], []) $ T.intercalate "\n" lns -latexCodeBlock :: Monad m => ParserT Sources st m [Text] +latexCodeBlock :: Monad m => ParsecT Sources st m [Text] latexCodeBlock = try $ do try (latexBlockLine "\\begin{code}") many1Till anyLine (try $ latexBlockLine "\\end{code}") where latexBlockLine s = skipMany spaceChar >> string s >> blankline -birdCodeBlock :: Monad m => ParserT Sources st m [Text] +birdCodeBlock :: Monad m => ParsecT Sources st m [Text] birdCodeBlock = filterSpace <$> many1 birdTrackLine where filterSpace lns = -- if (as is normal) there is always a space after >, drop it @@ -432,7 +432,7 @@ birdCodeBlock = filterSpace <$> many1 birdTrackLine then map (T.drop 1) lns else lns -birdTrackLine :: Monad m => ParserT Sources st m Text +birdTrackLine :: Monad m => ParsecT Sources st m Text birdTrackLine = char '>' >> anyLine -- @@ -509,7 +509,7 @@ definitionList :: PandocMonad m => RSTParser m Blocks definitionList = B.definitionList <$> many1 definitionListItem -- parses bullet list start and returns its length (inc. following whitespace) -bulletListStart :: Monad m => ParserT Sources st m Int +bulletListStart :: Monad m => ParsecT Sources st m Int bulletListStart = try $ do notFollowedBy' hrule -- because hrules start out just like lists marker <- oneOf bulletListMarkers @@ -1106,7 +1106,7 @@ quotedReferenceName = try $ do -- plus isolated (no two adjacent) internal hyphens, underscores, -- periods, colons and plus signs; no whitespace or other characters -- are allowed. -simpleReferenceName :: Monad m => ParserT Sources st m Text +simpleReferenceName :: Monad m => ParsecT Sources st m Text simpleReferenceName = do x <- alphaNum xs <- many $ alphaNum @@ -1125,7 +1125,7 @@ referenceKey = do -- return enough blanks to replace key return $ T.replicate (sourceLine endPos - sourceLine startPos) "\n" -targetURI :: Monad m => ParserT Sources st m Text +targetURI :: Monad m => ParsecT Sources st m Text targetURI = do skipSpaces optional $ try $ newline >> notFollowedBy blankline @@ -1253,13 +1253,13 @@ headerBlock = do -- - ensure that rightmost column span does not need to reach end -- - require at least 2 columns -dashedLine :: Monad m => Char -> ParserT Sources st m (Int, Int) +dashedLine :: Monad m => Char -> ParsecT Sources st m (Int, Int) dashedLine ch = do dashes <- many1 (char ch) sp <- many (char ' ') return (length dashes, length $ dashes ++ sp) -simpleDashedLines :: Monad m => Char -> ParserT Sources st m [(Int,Int)] +simpleDashedLines :: Monad m => Char -> ParsecT Sources st m [(Int,Int)] simpleDashedLines ch = try $ many1 (dashedLine ch) -- Parse a table row separator @@ -1383,7 +1383,7 @@ hyphens = do -- don't want to treat endline after hyphen or dash as a space return $ B.str result -escapedChar :: Monad m => ParserT Sources st m Inlines +escapedChar :: Monad m => ParsecT Sources st m Inlines escapedChar = do c <- escaped anyChar return $ if c == ' ' || c == '\n' || c == '\r' -- '\ ' is null in RST diff --git a/src/Text/Pandoc/Readers/RTF.hs b/src/Text/Pandoc/Readers/RTF.hs index 5931ca242..5d09ac26c 100644 --- a/src/Text/Pandoc/Readers/RTF.hs +++ b/src/Text/Pandoc/Readers/RTF.hs @@ -184,7 +184,7 @@ instance Default Properties where , gInTable = False } -type RTFParser m = ParserT Sources RTFState m +type RTFParser m = ParsecT Sources RTFState m data ListType = Bullet | Ordered ListAttributes deriving (Show, Eq) diff --git a/src/Text/Pandoc/Readers/Roff.hs b/src/Text/Pandoc/Readers/Roff.hs index 47f16ef4b..ccd1509ae 100644 --- a/src/Text/Pandoc/Readers/Roff.hs +++ b/src/Text/Pandoc/Readers/Roff.hs @@ -121,16 +121,16 @@ instance Default RoffState where , afterConditional = False } -type RoffLexer m = ParserT Sources RoffState m +type RoffLexer m = ParsecT Sources RoffState m -- -- Lexer: T.Text -> RoffToken -- -eofline :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s u m () +eofline :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s u m () eofline = void newline <|> eof <|> () <$ lookAhead (string "\\}") -spacetab :: (Stream s m Char, UpdateSourcePos s Char) => ParserT s u m Char +spacetab :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s u m Char spacetab = char ' ' <|> char '\t' characterCodeMap :: M.Map T.Text Char diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index 7ce4e593c..54b69c34f 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -43,7 +43,7 @@ readTWiki opts s = do Left e -> throwError e Right d -> return d -type TWParser = ParserT Sources ParserState +type TWParser = ParsecT Sources ParserState -- -- utility functions diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 45ef1e260..bd96bb403 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -67,7 +67,7 @@ readTextile opts s = do Right result -> return result Left e -> throwError e -type TextileParser = ParserT Sources ParserState +type TextileParser = ParsecT Sources ParserState -- | Generate a Pandoc ADT from a textile document parseTextile :: PandocMonad m => TextileParser m Pandoc @@ -681,9 +681,9 @@ langAttr = do -- | Parses material surrounded by a parser. surrounded :: (PandocMonad m, Show t) - => ParserT Sources st m t -- ^ surrounding parser - -> ParserT Sources st m a -- ^ content parser (to be used repeatedly) - -> ParserT Sources st m [a] + => ParsecT Sources st m t -- ^ surrounding parser + -> ParsecT Sources st m a -- ^ content parser (to be used repeatedly) + -> ParsecT Sources st m [a] surrounded border = enclosed (border *> notFollowedBy (oneOf " \t\n\r")) (try border) @@ -713,5 +713,5 @@ groupedInlineMarkup = try $ do char ']' return $ sp1 <> result <> sp2 -eof' :: Monad m => ParserT Sources s m Char +eof' :: Monad m => ParsecT Sources s m Char eof' = '\n' <$ eof diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs index 2275646b9..10714ca9f 100644 --- a/src/Text/Pandoc/Readers/TikiWiki.hs +++ b/src/Text/Pandoc/Readers/TikiWiki.hs @@ -46,7 +46,7 @@ readTikiWiki opts s = do Left e -> throwError e Right d -> return d -type TikiWikiParser = ParserT Sources ParserState +type TikiWikiParser = ParsecT Sources ParserState -- -- utility functions diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index b5cf5a0f3..a129a463b 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -35,7 +35,7 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (space, spaces, uri) import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI) -type T2T = ParserT Sources ParserState (Reader T2TMeta) +type T2T = ParsecT Sources ParserState (Reader T2TMeta) -- | An object for the T2T macros meta information -- the contents of each field is simply substituted verbatim into the file @@ -402,7 +402,7 @@ tagged = do target <- getTarget inlineMarkup (T.singleton <$> anyChar) (B.rawInline target) '\'' id --- Parser for markup indicated by a double character. +-- Parsec for markup indicated by a double character. -- Inline markup is greedy and glued -- Greedy meaning ***a*** = Bold [Str "*a*"] -- Glued meaning that markup must be tight to content diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs index 794993ef4..771009a81 100644 --- a/src/Text/Pandoc/Readers/Vimwiki.hs +++ b/src/Text/Pandoc/Readers/Vimwiki.hs @@ -70,7 +70,7 @@ import Text.Pandoc.Definition (Attr, Block (BulletList, OrderedList), ListNumberStyle (..), Pandoc (..), nullMeta) import Text.Pandoc.Options (ReaderOptions) -import Text.Pandoc.Parsing (ParserState, ParserT, blanklines, emailAddress, +import Text.Pandoc.Parsing (ParserState, ParsecT, blanklines, emailAddress, many1Till, orderedListMarker, readWithM, registerHeader, spaceChar, stateMeta, stateOptions, uri, manyTillChar, manyChar, textStr, @@ -95,7 +95,7 @@ readVimwiki opts s = do Left e -> throwError e Right result -> return result -type VwParser = ParserT Sources ParserState +type VwParser = ParsecT Sources ParserState -- constants diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 859172376..789cddacf 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -36,8 +36,8 @@ import Text.Pandoc.Shared (renderTags', trim, tshow) import Text.Pandoc.URI (isURI) import Text.Pandoc.UTF8 (toString, toText, fromText) import Text.Parsec (ParsecT, runParserT) -import Control.Monad.Except (throwError, catchError) import qualified Text.Parsec as P +import Control.Monad.Except (throwError, catchError) isOk :: Char -> Bool isOk c = isAscii c && isAlphaNum c diff --git a/src/Text/Pandoc/TeX.hs b/src/Text/Pandoc/TeX.hs index 7ada8617b..21b161041 100644 --- a/src/Text/Pandoc/TeX.hs +++ b/src/Text/Pandoc/TeX.hs @@ -20,7 +20,7 @@ module Text.Pandoc.TeX ( Tok(..) ) where import Data.Text (Text) -import Text.Parsec.Pos (SourcePos, sourceName) +import Text.Parsec (SourcePos, sourceName) import Text.Pandoc.Sources import Data.List (groupBy) diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 2822b3ef8..e1691c110 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -112,7 +112,7 @@ escapeString t escChar c = T.singleton c -- | Ordered list start parser for use in Para below. -olMarker :: Parser Text ParserState Char +olMarker :: Parsec Text ParserState Char olMarker = do (start, style', delim) <- anyOrderedListMarker if delim == Period && (style' == UpperAlpha || (style' == UpperRoman && diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index e5a13d611..c6200f5b0 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -311,7 +311,7 @@ classOrAttrsToMarkdown ("",[cls],[]) = literal cls classOrAttrsToMarkdown attrs = attrsToMarkdown attrs -- | Ordered list start parser for use in Para below. -olMarker :: Parser Text ParserState () +olMarker :: Parsec Text ParserState () olMarker = do (start, style', delim) <- anyOrderedListMarker if delim == Period && (style' == UpperAlpha || (style' == UpperRoman && |
