aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Textile.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-10-13 10:44:38 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-10-13 10:44:38 -0700
commitea8b8114e125bb0237a58b3e70e7fba59436ed24 (patch)
treeb693e09be439862133cf9aa429b5dcb5241266c8 /src/Text/Pandoc/Readers/Textile.hs
parent40128754ab20105bce68cd072607f8877f10dca1 (diff)
downloadpandoc-ea8b8114e125bb0237a58b3e70e7fba59436ed24.tar.gz
Textile reader: Fixed bug with list items containing line breaks.
Now pandoc correctly handles hard line breaks inside list items. Previously they broke list parsing. Thanks to Pablo Rodríguez for pointing out the problem.
Diffstat (limited to 'src/Text/Pandoc/Readers/Textile.hs')
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs24
1 files changed, 15 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 922ebc44e..da5d8bee8 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -200,7 +200,7 @@ hrule = try $ do
-- strict in the nesting, sublist must start at exactly "parent depth
-- plus one"
anyList :: Parser [Char] ParserState Block
-anyList = try $ ( (anyListAtDepth 1) <* blanklines )
+anyList = try $ anyListAtDepth 1 <* blanklines
-- | This allow one type of list to be nested into an other type,
-- provided correct nesting
@@ -234,14 +234,23 @@ orderedListItemAtDepth = genericListItemAtDepth '#'
genericListItemAtDepth :: Char -> Int -> Parser [Char] ParserState [Block]
genericListItemAtDepth c depth = try $ do
count depth (char c) >> optional attributes >> whitespace
- p <- inlines
+ p <- many listInline
+ newline
sublist <- option [] (singleton <$> anyListAtDepth (depth + 1))
- return ((Plain p):sublist)
+ return (Plain p : sublist)
-- | A definition list is a set of consecutive definition items
definitionList :: Parser [Char] ParserState Block
definitionList = try $ DefinitionList <$> many1 definitionListItem
+-- | List start character.
+listStart :: Parser [Char] st Char
+listStart = oneOf "*#-"
+
+listInline :: Parser [Char] ParserState Inline
+listInline = try (notFollowedBy newline >> inline)
+ <|> try (endline <* notFollowedBy listStart)
+
-- | A definition list item in textile begins with '- ', followed by
-- the term defined, then spaces and ":=". The definition follows, on
-- the same single line, or spaned on multiple line, after a line
@@ -250,10 +259,11 @@ definitionListItem :: Parser [Char] ParserState ([Inline], [[Block]])
definitionListItem = try $ do
string "- "
term <- many1Till inline (try (whitespace >> string ":="))
- def' <- inlineDef <|> multilineDef
+ def' <- multilineDef <|> inlineDef
return (term, def')
where inlineDef :: Parser [Char] ParserState [[Block]]
- inlineDef = liftM (\d -> [[Plain d]]) $ try (whitespace >> inlines)
+ inlineDef = liftM (\d -> [[Plain d]])
+ $ optional whitespace >> many listInline <* newline
multilineDef :: Parser [Char] ParserState [[Block]]
multilineDef = try $ do
optional whitespace >> newline
@@ -348,10 +358,6 @@ maybeExplicitBlock name blk = try $ do
inline :: Parser [Char] ParserState Inline
inline = choice inlineParsers <?> "inline"
--- | List of consecutive inlines before a newline
-inlines :: Parser [Char] ParserState [Inline]
-inlines = manyTill inline newline
-
-- | Inline parsers tried in order
inlineParsers :: [Parser [Char] ParserState Inline]
inlineParsers = [ autoLink