aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Parsing.hs10
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs21
-rw-r--r--tests/tables.latex173
3 files changed, 75 insertions, 129 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 05d644a4b..ce74a4dde 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -488,8 +488,8 @@ gridTableWith block tableCaption headless =
tableWith (gridTableHeader headless block) (gridTableRow block) (gridTableSep '-') gridTableFooter tableCaption
gridTableSplitLine :: [Int] -> String -> [String]
-gridTableSplitLine indices line =
- map removeFinalBar $ tail $ splitByIndices (init indices) line
+gridTableSplitLine indices line = map removeFinalBar $ tail $
+ splitByIndices (init indices) $ removeTrailingSpace line
gridPart :: Char -> GenParser Char st (Int, Int)
gridPart ch = do
@@ -501,8 +501,8 @@ gridDashedLines :: Char -> GenParser Char st [(Int,Int)]
gridDashedLines ch = try $ char '+' >> many1 (gridPart ch) >>~ blankline
removeFinalBar :: String -> String
-removeFinalBar = reverse . dropWhile (=='|') . dropWhile (`elem` " \t") .
- reverse
+removeFinalBar =
+ reverse . dropWhile (`elem` " \t") . dropWhile (=='|') . reverse
-- | Separator between rows of grid table.
gridTableSep :: Char -> GenParser Char ParserState Char
@@ -539,7 +539,7 @@ gridTableRawLine :: [Int] -> GenParser Char ParserState [String]
gridTableRawLine indices = do
char '|'
line <- many1Till anyChar newline
- return (gridTableSplitLine indices $ removeTrailingSpace line)
+ return (gridTableSplitLine indices line)
-- | Parse row of grid table.
gridTableRow :: GenParser Char ParserState Block
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 6ed605a05..fbf443a03 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -34,7 +34,7 @@ import Text.Pandoc.Generic
import Text.Pandoc.Shared
import Text.Pandoc.Templates
import Text.Printf ( printf )
-import Data.List ( (\\), isSuffixOf, isPrefixOf, intercalate )
+import Data.List ( (\\), isSuffixOf, isPrefixOf, intercalate, intersperse )
import Data.Char ( toLower, isPunctuation )
import Control.Monad.State
import Text.Pandoc.Pretty
@@ -241,9 +241,9 @@ blockToLaTeX (Header level lst) = do
blockToLaTeX (Table caption aligns widths heads rows) = do
headers <- if all null heads
then return empty
- else liftM ($$ "\\hline") $ tableRowToLaTeX heads
+ else liftM ($$ "\\hline") $ (tableRowToLaTeX widths) heads
captionText <- inlineListToLaTeX caption
- rows' <- mapM tableRowToLaTeX rows
+ rows' <- mapM (tableRowToLaTeX widths) rows
let colDescriptors = concat $ zipWith toColDescriptor widths aligns
let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$
headers $$ vcat rows' $$ "\\end{tabular}"
@@ -267,16 +267,19 @@ toColDescriptor width align = ">{\\PBS" ++
AlignRight -> "\\raggedleft"
AlignCenter -> "\\centering"
AlignDefault -> "\\raggedright") ++
- "\\hspace{0pt}}p{" ++ printf "%.2f" width ++
- "\\columnwidth}"
+ "\\hspace{0pt}}p{" ++ printf "%.2f" width ++ "\\columnwidth}"
blockListToLaTeX :: [Block] -> State WriterState Doc
blockListToLaTeX lst = mapM blockToLaTeX lst >>= return . vcat
-tableRowToLaTeX :: [[Block]] -> State WriterState Doc
-tableRowToLaTeX cols = mapM blockListToLaTeX cols >>=
- return . ($$ text "\\\\") . foldl (\row item -> row $$
- (if isEmpty row then text "" else text " & ") <> item) empty
+tableRowToLaTeX :: [Double] -> [[Block]] -> State WriterState Doc
+tableRowToLaTeX widths cols = do
+ renderedCells <- mapM blockListToLaTeX cols
+ let toCell 0 c = c
+ toCell w c = "\\parbox{" <> text (printf "%.2f" w) <>
+ "\\columnwidth}{" <> c <> cr <> "}"
+ let cells = zipWith toCell widths renderedCells
+ return $ (hcat $ intersperse (" & ") cells) <> "\\\\"
listItemToLaTeX :: [Block] -> State WriterState Doc
listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
diff --git a/tests/tables.latex b/tests/tables.latex
index 7f29b72c3..89bcf9d9f 100644
--- a/tests/tables.latex
+++ b/tests/tables.latex
@@ -3,27 +3,11 @@ Simple table with caption:
\begin{table}[h]
\begin{center}
\begin{tabular}{rlcl}
-Right
- & Left
- & Center
- & Default
-\\
+Right & Left & Center & Default\\
\hline
-12
- & 12
- & 12
- & 12
-\\
-123
- & 123
- & 123
- & 123
-\\
-1
- & 1
- & 1
- & 1
-\\
+12 & 12 & 12 & 12\\
+123 & 123 & 123 & 123\\
+1 & 1 & 1 & 1\\
\end{tabular}
\end{center}
\caption{Demonstration of simple table syntax.}
@@ -33,27 +17,11 @@ Simple table without caption:
\begin{center}
\begin{tabular}{rlcl}
-Right
- & Left
- & Center
- & Default
-\\
+Right & Left & Center & Default\\
\hline
-12
- & 12
- & 12
- & 12
-\\
-123
- & 123
- & 123
- & 123
-\\
-1
- & 1
- & 1
- & 1
-\\
+12 & 12 & 12 & 12\\
+123 & 123 & 123 & 123\\
+1 & 1 & 1 & 1\\
\end{tabular}
\end{center}
@@ -62,27 +30,11 @@ Simple table indented two spaces:
\begin{table}[h]
\begin{center}
\begin{tabular}{rlcl}
-Right
- & Left
- & Center
- & Default
-\\
+Right & Left & Center & Default\\
\hline
-12
- & 12
- & 12
- & 12
-\\
-123
- & 123
- & 123
- & 123
-\\
-1
- & 1
- & 1
- & 1
-\\
+12 & 12 & 12 & 12\\
+123 & 123 & 123 & 123\\
+1 & 1 & 1 & 1\\
\end{tabular}
\end{center}
\caption{Demonstration of simple table syntax.}
@@ -93,22 +45,23 @@ Multiline table with caption:
\begin{table}[h]
\begin{center}
\begin{tabular}{>{\PBS\centering\hspace{0pt}}p{0.15\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.14\columnwidth}>{\PBS\raggedleft\hspace{0pt}}p{0.16\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.34\columnwidth}}
-Centered Header
- & Left Aligned
- & Right Aligned
- & Default aligned
-\\
+\parbox{0.15\columnwidth}{Centered Header
+} & \parbox{0.14\columnwidth}{Left Aligned
+} & \parbox{0.16\columnwidth}{Right Aligned
+} & \parbox{0.34\columnwidth}{Default aligned
+}\\
\hline
-First
- & row
- & 12.0
- & Example of a row that spans multiple lines.
-\\
-Second
- & row
- & 5.0
- & Here's another one. Note the blank line between rows.
-\\
+\parbox{0.15\columnwidth}{First
+} & \parbox{0.14\columnwidth}{row
+} & \parbox{0.16\columnwidth}{12.0
+} & \parbox{0.34\columnwidth}{Example of a row that spans multiple lines.
+}\\
+\parbox{0.15\columnwidth}{Second
+} & \parbox{0.14\columnwidth}{row
+} & \parbox{0.16\columnwidth}{5.0
+} & \parbox{0.34\columnwidth}{Here's another one. Note the blank line between
+rows.
+}\\
\end{tabular}
\end{center}
\caption{Here's the caption. It may span multiple lines.}
@@ -118,22 +71,23 @@ Multiline table without caption:
\begin{center}
\begin{tabular}{>{\PBS\centering\hspace{0pt}}p{0.15\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.14\columnwidth}>{\PBS\raggedleft\hspace{0pt}}p{0.16\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.34\columnwidth}}
-Centered Header
- & Left Aligned
- & Right Aligned
- & Default aligned
-\\
+\parbox{0.15\columnwidth}{Centered Header
+} & \parbox{0.14\columnwidth}{Left Aligned
+} & \parbox{0.16\columnwidth}{Right Aligned
+} & \parbox{0.34\columnwidth}{Default aligned
+}\\
\hline
-First
- & row
- & 12.0
- & Example of a row that spans multiple lines.
-\\
-Second
- & row
- & 5.0
- & Here's another one. Note the blank line between rows.
-\\
+\parbox{0.15\columnwidth}{First
+} & \parbox{0.14\columnwidth}{row
+} & \parbox{0.16\columnwidth}{12.0
+} & \parbox{0.34\columnwidth}{Example of a row that spans multiple lines.
+}\\
+\parbox{0.15\columnwidth}{Second
+} & \parbox{0.14\columnwidth}{row
+} & \parbox{0.16\columnwidth}{5.0
+} & \parbox{0.34\columnwidth}{Here's another one. Note the blank line between
+rows.
+}\\
\end{tabular}
\end{center}
@@ -141,21 +95,9 @@ Table without column headers:
\begin{center}
\begin{tabular}{rlcr}
-12
- & 12
- & 12
- & 12
-\\
-123
- & 123
- & 123
- & 123
-\\
-1
- & 1
- & 1
- & 1
-\\
+12 & 12 & 12 & 12\\
+123 & 123 & 123 & 123\\
+1 & 1 & 1 & 1\\
\end{tabular}
\end{center}
@@ -163,16 +105,17 @@ Multiline table without column headers:
\begin{center}
\begin{tabular}{>{\PBS\centering\hspace{0pt}}p{0.15\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.14\columnwidth}>{\PBS\raggedleft\hspace{0pt}}p{0.16\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.34\columnwidth}}
-First
- & row
- & 12.0
- & Example of a row that spans multiple lines.
-\\
-Second
- & row
- & 5.0
- & Here's another one. Note the blank line between rows.
-\\
+\parbox{0.15\columnwidth}{First
+} & \parbox{0.14\columnwidth}{row
+} & \parbox{0.16\columnwidth}{12.0
+} & \parbox{0.34\columnwidth}{Example of a row that spans multiple lines.
+}\\
+\parbox{0.15\columnwidth}{Second
+} & \parbox{0.14\columnwidth}{row
+} & \parbox{0.16\columnwidth}{5.0
+} & \parbox{0.34\columnwidth}{Here's another one. Note the blank line between
+rows.
+}\\
\end{tabular}
\end{center}