LaTeX reader: Handle block structure inside table cells.

minipage is no longer required.

Closes #3709.
This commit is contained in:
John MacFarlane 2017-06-01 11:16:28 +02:00
parent a61dce88e8
commit 1e7ba5ccd7

View file

@ -276,8 +276,6 @@ block = (mempty <$ comment)
<|> blockCommand <|> blockCommand
<|> paragraph <|> paragraph
<|> grouped block <|> grouped block
<|> (mempty <$ char '&') -- loose & in table environment
blocks :: PandocMonad m => LP m Blocks blocks :: PandocMonad m => LP m Blocks
blocks = mconcat <$> many block blocks = mconcat <$> many block
@ -1168,12 +1166,12 @@ environments = M.fromList
, ("subfigure", env "subfigure" $ skipopts *> tok *> figure) , ("subfigure", env "subfigure" $ skipopts *> tok *> figure)
, ("center", env "center" blocks) , ("center", env "center" blocks)
, ("longtable", env "longtable" $ , ("longtable", env "longtable" $
resetCaption *> simpTable False >>= addTableCaption) resetCaption *> simpTable "longtable" False >>= addTableCaption)
, ("table", env "table" $ , ("table", env "table" $
resetCaption *> skipopts *> blocks >>= addTableCaption) resetCaption *> skipopts *> blocks >>= addTableCaption)
, ("tabular*", env "tabular" $ simpTable True) , ("tabular*", env "tabular" $ simpTable "tabular*" True)
, ("tabularx", env "tabularx" $ simpTable True) , ("tabularx", env "tabularx" $ simpTable "tabularx" True)
, ("tabular", env "tabular" $ simpTable False) , ("tabular", env "tabular" $ simpTable "tabular" False)
, ("quote", blockQuote <$> env "quote" blocks) , ("quote", blockQuote <$> env "quote" blocks)
, ("quotation", blockQuote <$> env "quotation" blocks) , ("quotation", blockQuote <$> env "quotation" blocks)
, ("verse", blockQuote <$> env "verse" blocks) , ("verse", blockQuote <$> env "verse" blocks)
@ -1489,25 +1487,27 @@ amp :: PandocMonad m => LP m ()
amp = () <$ try (spaces' *> char '&' <* spaces') amp = () <$ try (spaces' *> char '&' <* spaces')
parseTableRow :: PandocMonad m parseTableRow :: PandocMonad m
=> Int -- ^ number of columns => String -- ^ table environment name
-> Int -- ^ number of columns
-> [String] -- ^ prefixes -> [String] -- ^ prefixes
-> [String] -- ^ suffixes -> [String] -- ^ suffixes
-> LP m [Blocks] -> LP m [Blocks]
parseTableRow cols prefixes suffixes = try $ do parseTableRow envname cols prefixes suffixes = try $ do
let tableCellRaw = concat <$> many let tableCellRaw = concat <$> many
(do notFollowedBy (amp <|> lbreak <|> (() <$ try (string "\\end"))) (do notFollowedBy amp
notFollowedBy lbreak
notFollowedBy $ () <$ try (string ("\\end{" ++ envname ++ "}"))
many1 (noneOf "&%\n\r\\") many1 (noneOf "&%\n\r\\")
<|> try (string "\\&") <|> try (string "\\&")
<|> count 1 anyChar) <|> count 1 anyChar)
let minipage = try $ controlSeq "begin" *> string "{minipage}" *> let plainify bs = case toList bs of
env "minipage" [Para ils] -> plain (fromList ils)
(skipopts *> spaces' *> optional braced *> spaces' *> blocks) _ -> bs
let tableCell = minipage <|>
((plain . trimInlines . mconcat) <$> many inline)
rawcells <- sepBy1 tableCellRaw amp rawcells <- sepBy1 tableCellRaw amp
guard $ length rawcells == cols guard $ length rawcells == cols
let rawcells' = zipWith3 (\c p s -> p ++ trim c ++ s) let rawcells' = zipWith3 (\c p s -> p ++ trim c ++ s)
rawcells prefixes suffixes rawcells prefixes suffixes
let tableCell = plainify <$> blocks
cells' <- mapM (parseFromString' tableCell) rawcells' cells' <- mapM (parseFromString' tableCell) rawcells'
let numcells = length cells' let numcells = length cells'
guard $ numcells <= cols && numcells >= 1 guard $ numcells <= cols && numcells >= 1
@ -1520,8 +1520,8 @@ parseTableRow cols prefixes suffixes = try $ do
spaces' :: PandocMonad m => LP m () spaces' :: PandocMonad m => LP m ()
spaces' = spaces *> skipMany (comment *> spaces) spaces' = spaces *> skipMany (comment *> spaces)
simpTable :: PandocMonad m => Bool -> LP m Blocks simpTable :: PandocMonad m => String -> Bool -> LP m Blocks
simpTable hasWidthParameter = try $ do simpTable envname hasWidthParameter = try $ do
when hasWidthParameter $ () <$ (spaces' >> tok) when hasWidthParameter $ () <$ (spaces' >> tok)
skipopts skipopts
(prefixes, aligns, suffixes) <- unzip3 <$> parseAligns (prefixes, aligns, suffixes) <- unzip3 <$> parseAligns
@ -1531,10 +1531,10 @@ simpTable hasWidthParameter = try $ do
spaces' spaces'
skipMany hline skipMany hline
spaces' spaces'
header' <- option [] $ try (parseTableRow cols prefixes suffixes <* header' <- option [] $ try (parseTableRow envname cols prefixes suffixes <*
lbreak <* many1 hline) lbreak <* many1 hline)
spaces' spaces'
rows <- sepEndBy (parseTableRow cols prefixes suffixes) rows <- sepEndBy (parseTableRow envname cols prefixes suffixes)
(lbreak <* optional (skipMany hline)) (lbreak <* optional (skipMany hline))
spaces' spaces'
optional $ controlSeq "caption" *> skipopts *> setCaption optional $ controlSeq "caption" *> skipopts *> setCaption