aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Parsing.hs10
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs21
2 files changed, 17 insertions, 14 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" $$) .