Move indentWith to Text.Pandoc.Parsing (#3687)

This commit is contained in:
Alexander Krotov 2017-05-22 11:10:15 +03:00 committed by John MacFarlane
parent aa1e39858d
commit 30a3deadcc
5 changed files with 13 additions and 21 deletions

View file

@ -37,6 +37,7 @@ A utility library with parsers used in pandoc readers.
-}
module Text.Pandoc.Parsing ( anyLine,
anyLineNewline,
indentWith,
many1Till,
notFollowedBy',
oneOfStrings,
@ -260,6 +261,17 @@ anyLine = do
anyLineNewline :: Stream [Char] m Char => ParserT [Char] st m [Char]
anyLineNewline = (++ "\n") <$> anyLine
-- | Parse indent by specified number of spaces (or equiv. tabs)
indentWith :: Stream [Char] m Char
=> HasReaderOptions st
=> Int -> ParserT [Char] st m [Char]
indentWith num = do
tabStop <- getOption readerTabStop
if (num < tabStop)
then count num (char ' ')
else choice [ try (count num (char ' '))
, try (char '\t' >> indentWith (num - tabStop)) ]
-- | Like @manyTill@, but reads at least one item.
many1Till :: Stream s m t
=> ParserT s st m a

View file

@ -828,12 +828,3 @@ listContinuation markerLength = try $
<*> many blankline)
where
listLine = try $ indentWith markerLength *> anyLineNewline
-- indent by specified number of spaces (or equiv. tabs)
indentWith :: Monad m => Int -> OrgParser m String
indentWith num = do
tabStop <- getOption readerTabStop
if num < tabStop
then count num (char ' ')
else choice [ try (count num (char ' '))
, try (char '\t' >> count (num - tabStop) (char ' ')) ]

View file

@ -32,6 +32,7 @@ module Text.Pandoc.Readers.Org.Parsing
( OrgParser
, anyLine
, anyLineNewline
, indentWith
, blanklines
, newline
, parseFromString

View file

@ -561,15 +561,6 @@ listLine markerLength = try $ do
indentWith markerLength
anyLineNewline
-- indent by specified number of spaces (or equiv. tabs)
indentWith :: Monad m => Int -> RSTParser m [Char]
indentWith num = do
tabStop <- getOption readerTabStop
if (num < tabStop)
then count num (char ' ')
else choice [ try (count num (char ' ')),
(try (char '\t' >> count (num - tabStop) (char ' '))) ]
-- parse raw text for one list item, excluding start marker and continuations
rawListItem :: Monad m => RSTParser m Int
-> RSTParser m (Int, [Char])

View file

@ -277,9 +277,6 @@ listContinuation markerLength = try $
<*> many blankline)
where listLine = try $ indentWith markerLength *> anyLineNewline
indentWith :: Int -> T2T String
indentWith n = count n spaceChar
-- Table
table :: T2T Blocks