aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2023-05-08 13:09:04 -0700
committerJohn MacFarlane <[email protected]>2023-05-08 13:09:04 -0700
commit05ad84a0c6c027c2c78bdb3ec0e25864d8725efd (patch)
treeab029df7d958dc6b3012ab2f185aa99e9a2da133
parentca5940bf2c36e4329cf6bc726763817e928a30db (diff)
LaTeX writer: better fix for colspecs for multicolumn table.
Improves on the last commit; closes #8831.
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Table.hs88
-rw-r--r--test/tables/planets.latex8
-rw-r--r--test/tables/students.latex6
3 files changed, 61 insertions, 41 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX/Table.hs b/src/Text/Pandoc/Writers/LaTeX/Table.hs
index 6ebcaa559..1d9b117ca 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Table.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Table.hs
@@ -47,6 +47,11 @@ tableToLaTeX :: PandocMonad m
tableToLaTeX inlnsToLaTeX blksToLaTeX tbl = do
let (Ann.Table (ident, _, _) caption specs thead tbodies tfoot) = tbl
CaptionDocs capt captNotes <- captionToLaTeX inlnsToLaTeX caption ident
+ let isSimpleTable = all (all isSimpleCell) $ mconcat
+ [ headRows thead
+ , concatMap bodyRows tbodies
+ , footRows tfoot
+ ]
let removeNote (Note _) = Span ("", [], []) []
removeNote x = x
let colCount = ColumnCount $ length specs
@@ -56,7 +61,7 @@ tableToLaTeX inlnsToLaTeX blksToLaTeX tbl = do
-- making the caption part of the first head. The downside is that we must
-- duplicate the header rows for this.
head' <- do
- let mkHead = headToLaTeX blksToLaTeX colCount
+ let mkHead = headToLaTeX blksToLaTeX isSimpleTable colCount
case (not $ isEmpty capt, not $ isEmptyHead thead) of
(False, False) -> return "\\toprule\\noalign{}"
(False, True) -> mkHead thead
@@ -66,20 +71,21 @@ tableToLaTeX inlnsToLaTeX blksToLaTeX tbl = do
firsthead <- mkHead thead
repeated <- mkHead (walk removeNote thead)
return $ capt $$ firsthead $$ "\\endfirsthead" $$ repeated
- rows' <- mapM (rowToLaTeX blksToLaTeX colCount BodyCell) $
+ rows' <- mapM (rowToLaTeX blksToLaTeX isSimpleTable colCount BodyCell) $
mconcat (map bodyRows tbodies)
foot' <- if isEmptyFoot tfoot
then pure empty
else do
- lastfoot <- mapM (rowToLaTeX blksToLaTeX colCount BodyCell) $
- footRows tfoot
+ lastfoot <- mapM
+ (rowToLaTeX blksToLaTeX isSimpleTable colCount BodyCell) $
+ footRows tfoot
pure $ "\\midrule\\noalign{}" $$ vcat lastfoot
modify $ \s -> s{ stTable = True }
notes <- notesToLaTeX <$> gets stNotes
beamer <- gets stBeamer
return
$ "\\begin{longtable}[]" <>
- braces ("@{}" <> colDescriptors tbl <> "@{}")
+ braces ("@{}" <> colDescriptors isSimpleTable tbl <> "@{}")
-- the @{} removes extra space at beginning and end
$$ head'
$$ "\\endhead"
@@ -102,20 +108,26 @@ tableToLaTeX inlnsToLaTeX blksToLaTeX tbl = do
$$ captNotes
$$ notes
+isSimpleCell :: Ann.Cell -> Bool
+isSimpleCell (Ann.Cell _ _ (Cell _attr _align _rowspan _colspan blocks)) =
+ case blocks of
+ [Para _] -> True
+ [Plain _] -> True
+ [] -> True
+ _ -> False
+
+
+
-- | Total number of columns in a table.
newtype ColumnCount = ColumnCount Int
-- | Creates column descriptors for the table.
-colDescriptors :: Ann.Table -> Doc Text
-colDescriptors (Ann.Table _attr _caption specs thead tbodies tfoot) =
+colDescriptors :: Bool -> Ann.Table -> Doc Text
+colDescriptors isSimpleTable
+ (Ann.Table _attr _caption specs _thead _tbodies _tfoot) =
let (aligns, widths) = unzip specs
defaultWidthsOnly = all (== ColWidthDefault) widths
- isSimpleTable = all (all isSimpleCell) $ mconcat
- [ headRows thead
- , concatMap bodyRows tbodies
- , footRows tfoot
- ]
relativeWidths = if defaultWidthsOnly
then replicate (length specs)
@@ -136,13 +148,6 @@ colDescriptors (Ann.Table _attr _caption specs thead tbodies tfoot) =
((numcols - 1) * 2)
width
- isSimpleCell (Ann.Cell _ _ (Cell _attr _align _rowspan _colspan blocks)) =
- case blocks of
- [Para _] -> True
- [Plain _] -> True
- [] -> True
- _ -> False
-
toRelWidth ColWidthDefault = 0
toRelWidth (ColWidth w) = w
@@ -188,24 +193,29 @@ type BlocksWriter m = [Block] -> LW m (Doc Text)
headToLaTeX :: PandocMonad m
=> BlocksWriter m
+ -> Bool
-> ColumnCount
-> Ann.TableHead
-> LW m (Doc Text)
-headToLaTeX blocksWriter colCount (Ann.TableHead _attr headerRows) = do
+headToLaTeX blocksWriter isSimpleTable
+ colCount (Ann.TableHead _attr headerRows) = do
rowsContents <-
- mapM (rowToLaTeX blocksWriter colCount HeaderCell . headerRowCells)
+ mapM (rowToLaTeX blocksWriter isSimpleTable
+ colCount HeaderCell . headerRowCells)
headerRows
return ("\\toprule\\noalign{}" $$ vcat rowsContents $$ "\\midrule\\noalign{}")
-- | Converts a row of table cells into a LaTeX row.
rowToLaTeX :: PandocMonad m
=> BlocksWriter m
+ -> Bool
-> ColumnCount
-> CellType
-> [Ann.Cell]
-> LW m (Doc Text)
-rowToLaTeX blocksWriter colCount celltype row = do
- cellsDocs <- mapM (cellToLaTeX blocksWriter colCount celltype) (fillRow row)
+rowToLaTeX blocksWriter isSimpleTable colCount celltype row = do
+ cellsDocs <- mapM (cellToLaTeX blocksWriter isSimpleTable
+ colCount celltype) (fillRow row)
return $ hsep (intersperse "&" cellsDocs) <> " \\\\"
-- | Pads row with empty cells to adjust for rowspans above this row.
@@ -280,11 +290,12 @@ displayMathToInline x = x
cellToLaTeX :: PandocMonad m
=> BlocksWriter m
+ -> Bool
-> ColumnCount
-> CellType
-> Ann.Cell
-> LW m (Doc Text)
-cellToLaTeX blockListToLaTeX colCount celltype annotatedCell = do
+cellToLaTeX blockListToLaTeX isSimpleTable colCount celltype annotatedCell = do
let (Ann.Cell specs colnum cell) = annotatedCell
let colWidths = NonEmpty.map snd specs
let hasWidths = NonEmpty.head colWidths /= ColWidthDefault
@@ -329,7 +340,8 @@ cellToLaTeX blockListToLaTeX colCount celltype annotatedCell = do
let inMultiColumn x = case colspan of
(ColSpan 1) -> x
(ColSpan n) ->
- let colDescr = multicolumnDescriptor align
+ let colDescr = multicolumnDescriptor isSimpleTable
+ align
colWidths
colCount
colnum
@@ -346,12 +358,14 @@ cellToLaTeX blockListToLaTeX colCount celltype annotatedCell = do
return . inMultiColumn . inMultiRow $ result
-- | Returns the width of a cell spanning @n@ columns.
-multicolumnDescriptor :: Alignment
+multicolumnDescriptor :: Bool
+ -> Alignment
-> NonEmpty ColWidth
-> ColumnCount
-> Ann.ColNumber
-> Text
-multicolumnDescriptor align
+multicolumnDescriptor isSimpleTable
+ align
colWidths
(ColumnCount numcols)
(Ann.ColNumber colnum) =
@@ -364,13 +378,19 @@ multicolumnDescriptor align
-- no column separators at beginning of first and end of last column.
skipColSep = "@{}" :: String
in T.pack $
- printf "%s>{%s\\arraybackslash}p{(\\columnwidth - %d\\tabcolsep) * \\real{%0.4f} + %d\\tabcolsep}%s"
- (if colnum == 0 then skipColSep else "")
- (T.unpack (alignCommand align))
- (2 * (numcols - 1))
- width
- (2 * (colspan - 1))
- (if colnum + colspan >= numcols then skipColSep else "")
+ if isSimpleTable
+ then printf "%s%s%s"
+ (if colnum == 0 then skipColSep else "")
+ (T.unpack (colAlign align))
+ (if colnum + colspan >= numcols then skipColSep else "")
+
+ else printf "%s>{%s\\arraybackslash}p{(\\columnwidth - %d\\tabcolsep) * \\real{%0.4f} + %d\\tabcolsep}%s"
+ (if colnum == 0 then skipColSep else "")
+ (T.unpack (alignCommand align))
+ (2 * (numcols - 1))
+ width
+ (2 * (colspan - 1))
+ (if colnum + colspan >= numcols then skipColSep else "")
-- | Perform a conversion, assuming that the context is a minipage.
inMinipage :: Monad m => LW m a -> LW m a
diff --git a/test/tables/planets.latex b/test/tables/planets.latex
index ac7b7d911..8b013e3a8 100644
--- a/test/tables/planets.latex
+++ b/test/tables/planets.latex
@@ -1,14 +1,14 @@
\begin{longtable}[]{@{}cclrrrrrrrrl@{}}
\caption{Data about the planets of our solar system.}\tabularnewline
\toprule\noalign{}
-\multicolumn{2}{@{}>{\centering\arraybackslash}p{(\columnwidth - 22\tabcolsep) * \real{0.0000} + 2\tabcolsep}}{%
+\multicolumn{2}{@{}c}{%
} & Name & Mass (10\^{}24kg) & Diameter (km) & Density (kg/m\^{}3) & Gravity
(m/s\^{}2) & Length of day (hours) & Distance from Sun (10\^{}6km) & Mean
temperature (C) & Number of moons & Notes \\
\midrule\noalign{}
\endfirsthead
\toprule\noalign{}
-\multicolumn{2}{@{}>{\centering\arraybackslash}p{(\columnwidth - 22\tabcolsep) * \real{0.0000} + 2\tabcolsep}}{%
+\multicolumn{2}{@{}c}{%
} & Name & Mass (10\^{}24kg) & Diameter (km) & Density (kg/m\^{}3) & Gravity
(m/s\^{}2) & Length of day (hours) & Distance from Sun (10\^{}6km) & Mean
temperature (C) & Number of moons & Notes \\
@@ -16,7 +16,7 @@ temperature (C) & Number of moons & Notes \\
\endhead
\bottomrule\noalign{}
\endlastfoot
-\multicolumn{2}{@{}>{\centering\arraybackslash}p{(\columnwidth - 22\tabcolsep) * \real{0.0000} + 2\tabcolsep}}{%
+\multicolumn{2}{@{}c}{%
\multirow{4}{*}{Terrestrial planets}} & Mercury & 0.330 & 4,879 & 5427 & 3.7 &
4222.6 & 57.9 & 167 & 0 & Closest to the Sun \\
& & Venus & 4.87 & 12,104 & 5243 & 8.9 & 2802.0 & 108.2 & 464 & 0 & \\
@@ -29,7 +29,7 @@ planet \\
& \multirow{2}{*}{Ice giants} & Uranus & 86.8 & 51,118 & 1271 & 8.7 & 17.2 &
2872.5 & -195 & 27 & \\
& & Neptune & 102 & 49,528 & 1638 & 11.0 & 16.1 & 4495.1 & -200 & 14 & \\
-\multicolumn{2}{@{}>{\centering\arraybackslash}p{(\columnwidth - 22\tabcolsep) * \real{0.0000} + 2\tabcolsep}}{%
+\multicolumn{2}{@{}c}{%
Dwarf planets} & Pluto & 0.0146 & 2,370 & 2095 & 0.7 & 153.3 & 5906.4 & -225 & 5
& Declassified as a planet in 2006. \\
\end{longtable}
diff --git a/test/tables/students.latex b/test/tables/students.latex
index 802b00c60..f20aa027c 100644
--- a/test/tables/students.latex
+++ b/test/tables/students.latex
@@ -20,15 +20,15 @@ Name
\endhead
\bottomrule\noalign{}
\endlastfoot
-\multicolumn{2}{@{}>{\raggedright\arraybackslash}p{(\columnwidth - 2\tabcolsep) * \real{1.0000} + 2\tabcolsep}@{}}{%
+\multicolumn{2}{@{}l@{}}{%
Computer Science} \\
3741255 & Jones, Martha \\
4077830 & Pierce, Benjamin \\
5151701 & Kirk, James \\
-\multicolumn{2}{@{}>{\raggedright\arraybackslash}p{(\columnwidth - 2\tabcolsep) * \real{1.0000} + 2\tabcolsep}@{}}{%
+\multicolumn{2}{@{}l@{}}{%
Russian Literature} \\
3971244 & Nim, Victor \\
-\multicolumn{2}{@{}>{\raggedright\arraybackslash}p{(\columnwidth - 2\tabcolsep) * \real{1.0000} + 2\tabcolsep}@{}}{%
+\multicolumn{2}{@{}l@{}}{%
Astrophysics} \\
4100332 & Petrov, Alexandra \\
4100332 & Toyota, Hiroko \\