summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-11-28 03:22:33 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-11-28 03:22:33 +0000
commit98ff6b2fd06288598a7acf1f19b84418db47e6db (patch)
treeb2338fb523b95b3bf004f335f135256111e6b4e5 /src/Text/Pandoc
parent7c6467a115b0b692de35fe5c60142403c00bad76 (diff)
Better looking simple tables. Resolves Issue #180.
* Markdown reader: simple tables are now given column widths of 0. * Column width of 0 is interpreted as meaning: use default column width. * Writers now include explicit column width information only for multiline tables. (Exception: RTF writer, which requires column widths. In this case, columns are given equal widths, adding up to the text width.) * Simple tables should now look better in most output formats. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1631 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Definition.hs6
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs5
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs10
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs28
-rw-r--r--src/Text/Pandoc/Writers/Man.hs4
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs18
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs8
-rw-r--r--src/Text/Pandoc/Writers/RST.hs10
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs9
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs14
10 files changed, 71 insertions, 41 deletions
diff --git a/src/Text/Pandoc/Definition.hs b/src/Text/Pandoc/Definition.hs
index 92ce094d4..8b91ba322 100644
--- a/src/Text/Pandoc/Definition.hs
+++ b/src/Text/Pandoc/Definition.hs
@@ -86,9 +86,9 @@ data Block
| HorizontalRule -- ^ Horizontal rule
| Table [Inline] [Alignment] [Double] [[Block]] [[[Block]]] -- ^ Table,
-- with caption, column alignments,
- -- relative column widths, column headers
- -- (each a list of blocks), and rows
- -- (each a list of lists of blocks)
+ -- relative column widths (0 = default),
+ -- column headers (each a list of blocks), and
+ -- rows (each a list of lists of blocks)
| Null -- ^ Nothing
deriving (Eq, Read, Show, Typeable, Data)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 7a16f1578..47a3dbd55 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -761,7 +761,10 @@ tableWith headerParser lineParser footerParser = try $ do
-- Parse a simple table with '---' header and one line per row.
simpleTable :: GenParser Char ParserState Block
-simpleTable = tableWith simpleTableHeader tableLine blanklines
+simpleTable = do
+ Table c a _w h l <- tableWith simpleTableHeader tableLine blanklines
+ -- Simple tables get 0s for relative column widths (i.e., use default)
+ return $ Table c a (replicate (length a) 0) h l
-- Parse a multiline table: starts with row of '-' on top, then header
-- (which may be multiline), then the rows,
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 014751968..25902387b 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -192,15 +192,16 @@ blockToConTeXt (Header level lst) = do
text base <> char '{' <> contents <> char '}'
else contents
blockToConTeXt (Table caption aligns widths heads rows) = do
- let colWidths = map printDecimal widths
let colDescriptor colWidth alignment = (case alignment of
AlignLeft -> 'l'
AlignRight -> 'r'
AlignCenter -> 'c'
AlignDefault -> 'l'):
- "p(" ++ colWidth ++ "\\textwidth)|"
+ if colWidth == 0
+ then "|"
+ else ("p(" ++ printf "%.2f" colWidth ++ "\\textwidth)|")
let colDescriptors = "|" ++ (concat $
- zipWith colDescriptor colWidths aligns)
+ zipWith colDescriptor widths aligns)
headers <- tableRowToConTeXt heads
captionText <- inlineListToConTeXt caption
let captionText' = if null caption then text "none" else captionText
@@ -210,9 +211,6 @@ blockToConTeXt (Table caption aligns widths heads rows) = do
text "\\HL" $$ headers $$ text "\\HL" $$
vcat rows' $$ text "\\HL\n\\stoptable"
-printDecimal :: Double -> String
-printDecimal = printf "%.2f"
-
tableRowToConTeXt :: [[Block]] -> State WriterState Doc
tableRowToConTeXt cols = do
cols' <- mapM blockListToConTeXt cols
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index a0f9e9004..9a74a069e 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -197,17 +197,7 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
headers <- tableRowToLaTeX heads
captionText <- inlineListToLaTeX caption
rows' <- mapM tableRowToLaTeX rows
- let colWidths = map (printf "%.2f") widths
- let colDescriptors = concat $ zipWith
- (\width align -> ">{\\PBS" ++
- (case align of
- AlignLeft -> "\\raggedright"
- AlignRight -> "\\raggedleft"
- AlignCenter -> "\\centering"
- AlignDefault -> "\\raggedright") ++
- "\\hspace{0pt}}p{" ++ width ++
- "\\columnwidth}")
- colWidths aligns
+ let colDescriptors = concat $ zipWith toColDescriptor widths aligns
let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$
headers $$ text "\\hline" $$ vcat rows' $$
text "\\end{tabular}"
@@ -221,6 +211,22 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
else text "\\begin{table}[h]" $$ centered tableBody $$
inCmd "caption" captionText $$ text "\\end{table}\n"
+toColDescriptor :: Double -> Alignment -> String
+toColDescriptor 0 align =
+ case align of
+ AlignLeft -> "l"
+ AlignRight -> "r"
+ AlignCenter -> "c"
+ AlignDefault -> "l"
+toColDescriptor width align = ">{\\PBS" ++
+ (case align of
+ AlignLeft -> "\\raggedright"
+ AlignRight -> "\\raggedleft"
+ AlignCenter -> "\\centering"
+ AlignDefault -> "\\raggedright") ++
+ "\\hspace{0pt}}p{" ++ printf "%.2f" width ++
+ "\\columnwidth}"
+
blockListToLaTeX :: [Block] -> State WriterState Doc
blockListToLaTeX lst = mapM blockToLaTeX lst >>= return . vcat
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 89c865754..616795e31 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -171,7 +171,9 @@ blockToMan opts (Table caption alignments widths headers rows) =
in do
caption' <- inlineListToMan opts caption
modify (\(notes, preprocessors) -> (notes, "t":preprocessors))
- let iwidths = map (printf "w(%0.2fn)" . (70 *)) widths
+ let iwidths = if all (== 0) widths
+ then repeat ""
+ else map (printf "w(%0.2fn)" . (70 *)) widths
-- 78n default width - 8n indent = 70n
let coldescriptions = text $ intercalate " "
(zipWith (\align width -> aligncode align ++ width)
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index a18e1ecd6..d500d4caf 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -34,7 +34,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Blocks
import Text.ParserCombinators.Parsec ( parse, GenParser )
-import Data.List ( group, isPrefixOf, drop, find, intersperse, intercalate )
+import Data.List ( group, isPrefixOf, drop, find, intersperse, intercalate, transpose )
import Text.PrettyPrint.HughesPJ hiding ( Str )
import Control.Monad.State
@@ -218,25 +218,29 @@ blockToMarkdown opts (Table caption aligns widths headers rows) = do
then empty
else text "" $+$ (text "Table: " <> caption')
headers' <- mapM (blockListToMarkdown opts) headers
- let widthsInChars = map (floor . (78 *)) widths
let alignHeader alignment = case alignment of
AlignLeft -> leftAlignBlock
AlignCenter -> centerAlignBlock
AlignRight -> rightAlignBlock
AlignDefault -> leftAlignBlock
+ rawRows <- mapM (mapM (blockListToMarkdown opts)) rows
+ let isSimple = all (==0) widths
+ let numChars = maximum . map (length . render)
+ let widthsInChars =
+ if isSimple
+ then map ((+2) . numChars) $ transpose (headers' : rawRows)
+ else map (floor . (78 *)) widths
let makeRow = hsepBlocks . (zipWith alignHeader aligns) .
(zipWith docToBlock widthsInChars)
let head' = makeRow headers'
- rows' <- mapM (\row -> do cols <- mapM (blockListToMarkdown opts) row
- return $ makeRow cols) rows
+ let rows' = map makeRow rawRows
let maxRowHeight = maximum $ map heightOfBlock (head':rows')
- let isMultilineTable = maxRowHeight > 1
let underline = hsep $
map (\width -> text $ replicate width '-') widthsInChars
- let border = if isMultilineTable
+ let border = if maxRowHeight > 1
then text $ replicate (sum widthsInChars + (length widthsInChars - 1)) '-'
else empty
- let spacer = if isMultilineTable
+ let spacer = if maxRowHeight > 1
then text ""
else empty
let body = vcat $ intersperse spacer $ map blockToDoc rows'
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 52438f81e..7ef70a0d2 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -467,13 +467,15 @@ tableStyle num wcs =
table = inTags True "style:style"
[("style:name", tableId)] $
selfClosingTag "style:table-properties"
- [ ("style:rel-width", "100%" )
- , ("table:align" , "center")]
+ [("table:align" , "center")]
+ colStyle (c,0) = selfClosingTag "style:style"
+ [ ("style:name" , tableId ++ "." ++ [c])
+ , ("style:family", "table-column" )]
colStyle (c,w) = inTags True "style:style"
[ ("style:name" , tableId ++ "." ++ [c])
, ("style:family", "table-column" )] $
selfClosingTag "style:table-column-properties"
- [("style:column-width", printf "%.2f" (7 * w) ++ "in")]
+ [("style:rel-column-width", printf "%d*" $ (floor $ w * 65535 :: Integer))]
cellStyle = inTags True "style:style"
[ ("style:name" , tableId ++ ".A1")
, ("style:family", "table-cell" )] $
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 0bff38db7..22d453620 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -33,7 +33,7 @@ module Text.Pandoc.Writers.RST ( writeRST) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Blocks
-import Data.List ( isPrefixOf, isSuffixOf, drop, intersperse )
+import Data.List ( isPrefixOf, isSuffixOf, drop, intersperse, transpose )
import Text.PrettyPrint.HughesPJ hiding ( Str )
import Control.Monad.State
import Control.Applicative ( (<$>) )
@@ -198,7 +198,13 @@ blockToRST (Table caption _ widths headers rows) = do
then empty
else text "" $+$ (text "Table: " <> caption')
headers' <- mapM blockListToRST headers
- let widthsInChars = map (floor . (78 *)) widths
+ rawRows <- mapM (mapM blockListToRST) rows
+ let isSimple = all (==0) widths && all (all (\bs -> length bs == 1)) rows
+ let numChars = maximum . map (length . render)
+ let widthsInChars =
+ if isSimple
+ then map ((+2) . numChars) $ transpose (headers' : rawRows)
+ else map (floor . (78 *)) widths
let hpipeBlocks blocks = hcatBlocks [beg, middle, end]
where height = maximum (map heightOfBlock blocks)
sep' = TextBlock 3 height (replicate height " | ")
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 62d8c4a0c..f8bd0cd2b 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -191,9 +191,12 @@ blockToRTF indent alignment (Table caption aligns sizes headers rows) =
rtfPar indent 0 alignment (inlineListToRTF caption)
tableRowToRTF :: Bool -> Int -> [Alignment] -> [Double] -> [[Block]] -> String
-tableRowToRTF header indent aligns sizes cols =
- let columns = concat $ zipWith (tableItemToRTF indent) aligns cols
- totalTwips = 6 * 1440 -- 6 inches
+tableRowToRTF header indent aligns sizes' cols =
+ let totalTwips = 6 * 1440 -- 6 inches
+ sizes = if all (== 0) sizes'
+ then take (length cols) $ repeat (1.0 / fromIntegral (length cols))
+ else sizes'
+ columns = concat $ zipWith (tableItemToRTF indent) aligns cols
rightEdges = tail $ scanl (\sofar new -> sofar + floor (new * totalTwips))
(0 :: Integer) sizes
cellDefs = map (\edge -> (if header
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 840d64d71..a0986241b 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -32,7 +32,8 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
import Text.Printf ( printf )
-import Data.List ( isSuffixOf )
+import Data.List ( isSuffixOf, transpose, maximumBy )
+import Data.Ord ( comparing )
import Data.Char ( chr, ord )
import qualified Data.Set as S
import Control.Monad.State
@@ -225,9 +226,14 @@ blockToTexinfo (Table caption aligns widths heads rows) = do
headers <- tableHeadToTexinfo aligns heads
captionText <- inlineListToTexinfo caption
rowsText <- mapM (tableRowToTexinfo aligns) rows
- let colWidths = map (printf "%.2f ") widths
- let colDescriptors = concat colWidths
- let tableBody = text ("@multitable @columnfractions " ++ colDescriptors) $$
+ colDescriptors <-
+ if all (== 0) widths
+ then do -- use longest entry instead of column widths
+ cols <- mapM (mapM (liftM (render . hcat) . mapM blockToTexinfo)) $
+ transpose $ heads : rows
+ return $ concatMap ((\x -> "{"++x++"} ") . maximumBy (comparing length)) cols
+ else return $ "@columnfractions " ++ concatMap (printf "%.2f ") widths
+ let tableBody = text ("@multitable " ++ colDescriptors) $$
headers $$
vcat rowsText $$
text "@end multitable"