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.
This commit is contained in:
parent
40128754ab
commit
ea8b8114e1
3 changed files with 25 additions and 9 deletions
|
@ -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
|
||||
|
|
|
@ -38,6 +38,10 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "asterisk",Space,Str "1"]]
|
||||
,[Plain [Str "asterisk",Space,Str "2"]]
|
||||
,[Plain [Str "asterisk",Space,Str "3"]]]
|
||||
,Para [Str "With",Space,Str "line",Space,Str "breaks",Str ":"]
|
||||
,BulletList
|
||||
[[Plain [Str "asterisk",Space,Str "1",LineBreak,Str "newline"]]
|
||||
,[Plain [Str "asterisk",Space,Str "2"]]]
|
||||
,Header 2 [Str "Ordered"]
|
||||
,Para [Str "Tight",Str ":"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
|
|
|
@ -91,6 +91,12 @@ Asterisks tight:
|
|||
* asterisk 2
|
||||
* asterisk 3
|
||||
|
||||
With line breaks:
|
||||
|
||||
* asterisk 1
|
||||
newline
|
||||
* asterisk 2
|
||||
|
||||
h2. Ordered
|
||||
|
||||
Tight:
|
||||
|
|
Loading…
Add table
Reference in a new issue