aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Markdown.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Markdown.hs')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs31
1 files changed, 19 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 2d7c12e99..9ffdbf00d 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -863,14 +863,16 @@ listLineCommon = concat <$> manyTill
-- parse raw text for one list item, excluding start marker and continuations
rawListItem :: PandocMonad m
- => MarkdownParser m a
+ => Bool -- four space rule
+ -> MarkdownParser m a
-> MarkdownParser m (String, Int)
-rawListItem start = try $ do
+rawListItem fourSpaceRule start = try $ do
pos1 <- getPosition
start
pos2 <- getPosition
- continuationIndent <- (4 <$ guardEnabled Ext_four_space_rule)
- <|> return (sourceColumn pos2 - sourceColumn pos1)
+ let continuationIndent = if fourSpaceRule
+ then 4
+ else (sourceColumn pos2 - sourceColumn pos1)
first <- listLineCommon
rest <- many (do notFollowedBy listStart
notFollowedBy (() <$ codeBlockFenced)
@@ -914,10 +916,11 @@ notFollowedByHtmlCloser = do
Nothing -> return ()
listItem :: PandocMonad m
- => MarkdownParser m a
+ => Bool -- four-space rule
+ -> MarkdownParser m a
-> MarkdownParser m (F Blocks)
-listItem start = try $ do
- (first, continuationIndent) <- rawListItem start
+listItem fourSpaceRule start = try $ do
+ (first, continuationIndent) <- rawListItem fourSpaceRule start
continuations <- many (listContinuation continuationIndent)
-- parsing with ListItemState forces markers at beginning of lines to
-- count as list item markers, even if not separated by blank space.
@@ -938,14 +941,18 @@ orderedList = try $ do
delim `elem` [DefaultDelim, Period]) $
guardEnabled Ext_fancy_lists
when (style == Example) $ guardEnabled Ext_example_lists
- items <- fmap sequence $ many1 $ listItem
+ fourSpaceRule <- (True <$ guardEnabled Ext_four_space_rule)
+ <|> return (style == Example)
+ items <- fmap sequence $ many1 $ listItem fourSpaceRule
(orderedListStart (Just (style, delim)))
start' <- (start <$ guardEnabled Ext_startnum) <|> return 1
return $ B.orderedListWith (start', style, delim) <$> fmap compactify items
bulletList :: PandocMonad m => MarkdownParser m (F Blocks)
bulletList = do
- items <- fmap sequence $ many1 $ listItem bulletListStart
+ fourSpaceRule <- (True <$ guardEnabled Ext_four_space_rule)
+ <|> return False
+ items <- fmap sequence $ many1 $ listItem fourSpaceRule bulletListStart
return $ B.bulletList <$> fmap compactify items
-- definition lists
@@ -1267,7 +1274,7 @@ tableCaption :: PandocMonad m => MarkdownParser m (F Inlines)
tableCaption = try $ do
guardEnabled Ext_table_captions
skipNonindentSpaces
- (string ":" <* notFollowedBy (string "::")) <|> string "Table:"
+ (string ":" <* notFollowedBy (satisfy isPunctuation)) <|> string "Table:"
trimInlinesF <$> inlines1 <* blanklines
-- Parse a simple table with '---' header and one line per row.
@@ -1353,8 +1360,8 @@ pipeTable = try $ do
numColumns <- getOption readerColumns
let widths = if maxlength > numColumns
then map (\len ->
- fromIntegral (len + 1) / fromIntegral numColumns)
- seplengths
+ fromIntegral len / fromIntegral (sum seplengths))
+ seplengths
else replicate (length aligns) 0.0
return (aligns, widths, heads', sequence lines'')