aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs37
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs31
2 files changed, 41 insertions, 27 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 651d46753..7c7845c71 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -121,6 +121,9 @@ data DState = DState { docxAnchorMap :: M.Map String String
, docxMediaBag :: MediaBag
, docxDropCap :: Inlines
, docxWarnings :: [String]
+ -- keep track of (numId, lvl) values for
+ -- restarting
+ , docxListState :: M.Map (String, String) Integer
}
instance Default DState where
@@ -128,6 +131,7 @@ instance Default DState where
, docxMediaBag = mempty
, docxDropCap = mempty
, docxWarnings = []
+ , docxListState = M.empty
}
data DEnv = DEnv { docxOptions :: ReaderOptions
@@ -539,22 +543,25 @@ bodyPartToBlocks (Paragraph pPr parparts)
then return mempty
else return $ parStyleToTransform pPr $ para ils'
bodyPartToBlocks (ListItem pPr numId lvl (Just levelInfo) parparts) = do
- let
- kvs = case levelInfo of
- (_, fmt, txt, Just start) -> [ ("level", lvl)
- , ("num-id", numId)
- , ("format", fmt)
- , ("text", txt)
- , ("start", show start)
- ]
-
- (_, fmt, txt, Nothing) -> [ ("level", lvl)
- , ("num-id", numId)
- , ("format", fmt)
- , ("text", txt)
- ]
+ -- We check whether this current numId has previously been used,
+ -- since Docx expects us to pick up where we left off.
+ listState <- gets docxListState
+ let startFromState = M.lookup (numId, lvl) listState
+ (_, fmt,txt, startFromLevelInfo) = levelInfo
+ start = case startFromState of
+ Just n -> n + 1
+ Nothing -> case startFromLevelInfo of
+ Just n' -> n'
+ Nothing -> 1
+ kvs = [ ("level", lvl)
+ , ("num-id", numId)
+ , ("format", fmt)
+ , ("text", txt)
+ , ("start", show start)
+ ]
+ modify $ \st -> st{ docxListState = M.insert (numId, lvl) start listState}
blks <- bodyPartToBlocks (Paragraph pPr parparts)
- return $ divWith ("", ["list-item"], kvs) blks
+ return $ divWith ("", ["list-item"], kvs) blks
bodyPartToBlocks (ListItem pPr _ _ _ parparts) =
let pPr' = pPr {pStyle = "ListParagraph": pStyle pPr}
in
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'')