diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index e571da5ad..1c6954279 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -2338,10 +2338,9 @@ parseAligns = try $ do parseTableRow :: PandocMonad m => Text -- ^ table environment name -> [([Tok], [Tok])] -- ^ pref/suffixes - -> LP m [Blocks] + -> LP m Row parseTableRow envname prefsufs = do notFollowedBy (spaces *> end_ envname) - let cols = length prefsufs -- add prefixes and suffixes in token stream: let celltoks (pref, suff) = do prefpos <- getPosition @@ -2360,21 +2359,62 @@ parseTableRow envname prefsufs = do cells <- mapM (\ts -> setInput ts >> parseTableCell) rawcells setInput oldInput spaces - let numcells = length cells - guard $ numcells <= cols && numcells >= 1 - guard $ cells /= [mempty] - -- note: a & b in a three-column table leaves an empty 3rd cell: - return $ cells ++ replicate (cols - numcells) mempty + return $ Row nullAttr cells -parseTableCell :: PandocMonad m => LP m Blocks +parseTableCell :: PandocMonad m => LP m Cell parseTableCell = do - let plainify bs = case toList bs of - [Para ils] -> plain (fromList ils) - _ -> bs updateState $ \st -> st{ sInTableCell = True } - cells <- plainify <$> blocks + cell' <- parseMultiCell <|> parseSimpleCell updateState $ \st -> st{ sInTableCell = False } - return cells + return cell' + +cellAlignment :: PandocMonad m => LP m Alignment +cellAlignment = skipMany (symbol '|') *> alignment <* skipMany (symbol '|') + where + alignment = do + c <- untoken <$> singleChar + return $ case c of + "l" -> AlignLeft + "r" -> AlignRight + "c" -> AlignCenter + "*" -> AlignDefault + _ -> AlignDefault + +plainify :: Blocks -> Blocks +plainify bs = case toList bs of + [Para ils] -> plain (fromList ils) + _ -> bs + +parseMultiCell :: PandocMonad m => LP m Cell +parseMultiCell = (controlSeq "multirow" >> parseMultirowCell) + <|> (controlSeq "multicolumn" >> parseMulticolCell) + where + parseMultirowCell = parseMultiXCell RowSpan (const $ ColSpan 1) + parseMulticolCell = parseMultiXCell (const $ RowSpan 1) ColSpan + + parseMultiXCell rowspanf colspanf = do + span' <- fmap (fromMaybe 1 . safeRead . untokenize) braced + alignment <- symbol '{' *> cellAlignment <* symbol '}' + + -- Two possible contents: either a nested \multirow/\multicol, or content. + -- E.g. \multirow{1}{c}{\multicol{1}{c}{content}} + let singleCell = do + content <- plainify <$> blocks + return $ cell alignment (rowspanf span') (colspanf span') content + + let nestedCell = do + (Cell _ _ (RowSpan rs) (ColSpan cs) bs) <- parseMultiCell + return $ cell + alignment + (RowSpan $ max span' rs) + (ColSpan $ max span' cs) + (fromList bs) + + symbol '{' *> (nestedCell <|> singleCell) <* symbol '}' + +-- Parse a simple cell, i.e. not multirow/multicol +parseSimpleCell :: PandocMonad m => LP m Cell +parseSimpleCell = simpleCell <$> (plainify <$> blocks) simpTable :: PandocMonad m => Text -> Bool -> LP m Blocks simpTable envname hasWidthParameter = try $ do @@ -2390,8 +2430,8 @@ simpTable envname hasWidthParameter = try $ do spaces skipMany hline spaces - header' <- option [] $ try (parseTableRow envname prefsufs <* - lbreak <* many1 hline) + header' <- option [] . try . fmap (:[]) $ + parseTableRow envname prefsufs <* lbreak <* many1 hline spaces rows <- sepEndBy (parseTableRow envname prefsufs) (lbreak <* optional (skipMany hline)) @@ -2403,12 +2443,10 @@ simpTable envname hasWidthParameter = try $ do optional lbreak spaces lookAhead $ controlSeq "end" -- make sure we're at end - let toRow = Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] return $ table emptyCaption (zip aligns widths) - (TableHead nullAttr $ toHeaderRow header') - [TableBody nullAttr 0 [] $ map toRow rows] + (TableHead nullAttr $ header') + [TableBody nullAttr 0 [] rows] (TableFoot nullAttr []) addTableCaption :: PandocMonad m => Blocks -> LP m Blocks diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 821747f26..74906fab4 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -35,13 +35,17 @@ infix 4 =: => String -> (Text, c) -> TestTree (=:) = test latex -simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks -simpleTable' aligns rows +table' :: [Alignment] -> [Row] -> Blocks +table' aligns rows = table emptyCaption (zip aligns (repeat ColWidthDefault)) (TableHead nullAttr []) - [TableBody nullAttr 0 [] $ map toRow rows] + [TableBody nullAttr 0 [] rows] (TableFoot nullAttr []) + +simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks +simpleTable' aligns rows + = table' aligns (map toRow rows) where toRow = Row nullAttr . map simpleCell @@ -137,6 +141,54 @@ tests = [ testGroup "tokenization" , "Table with vertical alignment argument" =: "\\begin{tabular}[t]{r|r}One & Two\\\\ \\end{tabular}" =?> simpleTable' [AlignRight,AlignRight] [[plain "One", plain "Two"]] + , "Table with multicolumn item" =: + "\\begin{tabular}{l c r}\\multicolumn{2}{c}{One} & Two\\\\ \\end{tabular}" =?> + table' [AlignLeft, AlignCenter, AlignRight] + [ Row nullAttr [ cell AlignCenter (RowSpan 1) (ColSpan 2) (plain "One") + , simpleCell (plain "Two") + ] + ] + , "Table with multirow item" =: + T.unlines ["\\begin{tabular}{c}" + ,"\\multirow{2}{c}{One}\\\\Two\\\\" + ,"\\end{tabular}" + ] =?> + table' [AlignCenter] + [ Row nullAttr [ cell AlignCenter (RowSpan 2) (ColSpan 1) (plain "One") ] + , Row nullAttr [ simpleCell (plain "Two") ] + ] + , "Table with nested multirow/multicolumn item" =: + T.unlines [ "\\begin{tabular}{c c c}" + , "\\multirow{2}{c}{\\multicolumn{2}{c}{One}}&Two\\\\" + , "Three\\\\" + , "Four&Five&Six\\\\" + , "\\end{tabular}" + ] =?> + table' [AlignCenter, AlignCenter, AlignCenter] + [ Row nullAttr [ cell AlignCenter (RowSpan 2) (ColSpan 2) (plain "One") + , simpleCell (plain "Two") + ] + , Row nullAttr [ simpleCell (plain "Three") ] + , Row nullAttr [ simpleCell (plain "Four") + , simpleCell (plain "Five") + , simpleCell (plain "Six") + ] + ] + , "Table with multicolumn header" =: + T.unlines [ "\\begin{tabular}{ |l|l| }" + , "\\hline\\multicolumn{2}{|c|}{Header}\\\\" + , "\\hline key & val\\\\" + , "\\hline\\end{tabular}" + ] =?> + table emptyCaption + (zip [AlignLeft, AlignLeft] (repeat ColWidthDefault)) + (TableHead nullAttr [ Row nullAttr [cell AlignCenter (RowSpan 1) (ColSpan 2) (plain "Header")]]) + [TableBody nullAttr 0 [] [Row nullAttr [ simpleCell (plain "key") + , simpleCell (plain "val") + ] + ] + ] + (TableFoot nullAttr []) ] , testGroup "citations"