From 98ff6b2fd06288598a7acf1f19b84418db47e6db Mon Sep 17 00:00:00 2001
From: fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>
Date: Sat, 28 Nov 2009 03:22:33 +0000
Subject: [PATCH] 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
---
 README                                  | 26 ++++-----
 src/Text/Pandoc/Definition.hs           |  6 +-
 src/Text/Pandoc/Readers/Markdown.hs     |  5 +-
 src/Text/Pandoc/Writers/ConTeXt.hs      | 10 ++--
 src/Text/Pandoc/Writers/LaTeX.hs        | 28 ++++++----
 src/Text/Pandoc/Writers/Man.hs          |  4 +-
 src/Text/Pandoc/Writers/Markdown.hs     | 18 +++---
 src/Text/Pandoc/Writers/OpenDocument.hs |  8 ++-
 src/Text/Pandoc/Writers/RST.hs          | 10 +++-
 src/Text/Pandoc/Writers/RTF.hs          |  9 ++-
 src/Text/Pandoc/Writers/Texinfo.hs      | 14 +++--
 tests/tables.context                    |  6 +-
 tests/tables.docbook                    | 24 ++++----
 tests/tables.html                       | 24 ++++----
 tests/tables.latex                      |  6 +-
 tests/tables.man                        |  6 +-
 tests/tables.markdown                   | 30 +++++-----
 tests/tables.mediawiki                  | 24 ++++----
 tests/tables.native                     |  6 +-
 tests/tables.opendocument               | 74 +++++++++----------------
 tests/tables.rst                        | 54 +++++++++---------
 tests/tables.rtf                        | 24 ++++----
 tests/tables.texinfo                    |  6 +-
 23 files changed, 214 insertions(+), 208 deletions(-)

diff --git a/README b/README
index 6ee7a96c1..f16a045c3 100644
--- a/README
+++ b/README
@@ -664,11 +664,11 @@ a fixed-width font, such as Courier.
 
 Simple tables look like this:
 
-      Right     Left     Center     Default   
-    -------     ------ ----------   -------   
-         12     12        12            12    
-        123     123       123          123    
-          1     1          1             1    
+      Right     Left     Center     Default
+    -------     ------ ----------   -------
+         12     12        12            12
+        123     123       123          123
+          1     1          1             1
 
     Table:  Demonstration of simple table syntax.
 
@@ -692,11 +692,6 @@ The table must end with a blank line.  Optionally, a caption may be
 provided (as illustrated in the example above).  A caption is a paragraph
 beginning with the string `Table:`, which will be stripped off.
 
-The table parser pays attention to the widths of the columns, and
-the writers try to reproduce these relative widths in the output.
-So, if you find that one of the columns is too narrow in the output,
-try widening it in the markdown source.
-
 Multiline tables allow headers and table rows to span multiple lines
 of text.  Here is an example:
 
@@ -706,12 +701,12 @@ of text.  Here is an example:
     ----------- ------- --------------- -------------------------
        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.
     -------------------------------------------------------------
-    
+
     Table: Here's the caption. It, too, may span
     multiple lines.
 
@@ -719,7 +714,12 @@ These work like simple tables, but with the following differences:
 
   - They must begin with a row of dashes, before the header text.
   - They must end with a row of dashes, then a blank line.
-  - The rows must be separated by blank lines. 
+  - The rows must be separated by blank lines.
+
+In multiline tables, the table parser pays attention to the widths of
+the columns, and the writers try to reproduce these relative widths in
+the output. So, if you find that one of the columns is too narrow in the
+output, try widening it in the markdown source.
 
 Delimited Code blocks
 ---------------------
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" 
diff --git a/tests/tables.context b/tests/tables.context
index 87ed08e25..ad9868559 100644
--- a/tests/tables.context
+++ b/tests/tables.context
@@ -1,7 +1,7 @@
 Simple table with caption:
 
 \placetable[here]{Demonstration of simple table syntax.}
-\starttable[|rp(0.15\textwidth)|lp(0.09\textwidth)|cp(0.16\textwidth)|lp(0.13\textwidth)|]
+\starttable[|r|l|c|l|]
 \HL
 \NC Right
 \NC Left
@@ -30,7 +30,7 @@ Simple table with caption:
 Simple table without caption:
 
 \placetable[here]{none}
-\starttable[|rp(0.15\textwidth)|lp(0.09\textwidth)|cp(0.16\textwidth)|lp(0.13\textwidth)|]
+\starttable[|r|l|c|l|]
 \HL
 \NC Right
 \NC Left
@@ -59,7 +59,7 @@ Simple table without caption:
 Simple table indented two spaces:
 
 \placetable[here]{Demonstration of simple table syntax.}
-\starttable[|rp(0.15\textwidth)|lp(0.09\textwidth)|cp(0.16\textwidth)|lp(0.13\textwidth)|]
+\starttable[|r|l|c|l|]
 \HL
 \NC Right
 \NC Left
diff --git a/tests/tables.docbook b/tests/tables.docbook
index ffeebdc57..6f5eac970 100644
--- a/tests/tables.docbook
+++ b/tests/tables.docbook
@@ -6,16 +6,16 @@
     Demonstration of simple table syntax.
   </caption>
   <tr>
-    <th align="right" style="{width: 15%;}">
+    <th align="right">
       Right
     </th>
-    <th align="left" style="{width: 8%;}">
+    <th align="left">
       Left
     </th>
-    <th align="center" style="{width: 16%;}">
+    <th align="center">
       Center
     </th>
-    <th align="left" style="{width: 12%;}">
+    <th align="left">
       Default
     </th>
   </tr>
@@ -67,16 +67,16 @@
 </para>
 <informaltable>
   <tr>
-    <th align="right" style="{width: 15%;}">
+    <th align="right">
       Right
     </th>
-    <th align="left" style="{width: 8%;}">
+    <th align="left">
       Left
     </th>
-    <th align="center" style="{width: 16%;}">
+    <th align="center">
       Center
     </th>
-    <th align="left" style="{width: 12%;}">
+    <th align="left">
       Default
     </th>
   </tr>
@@ -131,16 +131,16 @@
     Demonstration of simple table syntax.
   </caption>
   <tr>
-    <th align="right" style="{width: 15%;}">
+    <th align="right">
       Right
     </th>
-    <th align="left" style="{width: 8%;}">
+    <th align="left">
       Left
     </th>
-    <th align="center" style="{width: 16%;}">
+    <th align="center">
       Center
     </th>
-    <th align="left" style="{width: 12%;}">
+    <th align="left">
       Default
     </th>
   </tr>
diff --git a/tests/tables.html b/tests/tables.html
index 7626b326d..49b44661c 100644
--- a/tests/tables.html
+++ b/tests/tables.html
@@ -4,13 +4,13 @@
 ><caption
   >Demonstration of simple table syntax.</caption
   ><tr class="header"
-  ><th align="right" style="width: 15%;"
+  ><th align="right"
     >Right</th
-    ><th align="left" style="width: 8%;"
+    ><th align="left"
     >Left</th
-    ><th align="center" style="width: 16%;"
+    ><th align="center"
     >Center</th
-    ><th align="left" style="width: 12%;"
+    ><th align="left"
     >Default</th
     ></tr
   ><tr class="odd"
@@ -48,13 +48,13 @@
 >Simple table without caption:</p
 ><table
 ><tr class="header"
-  ><th align="right" style="width: 15%;"
+  ><th align="right"
     >Right</th
-    ><th align="left" style="width: 8%;"
+    ><th align="left"
     >Left</th
-    ><th align="center" style="width: 16%;"
+    ><th align="center"
     >Center</th
-    ><th align="left" style="width: 12%;"
+    ><th align="left"
     >Default</th
     ></tr
   ><tr class="odd"
@@ -94,13 +94,13 @@
 ><caption
   >Demonstration of simple table syntax.</caption
   ><tr class="header"
-  ><th align="right" style="width: 15%;"
+  ><th align="right"
     >Right</th
-    ><th align="left" style="width: 8%;"
+    ><th align="left"
     >Left</th
-    ><th align="center" style="width: 16%;"
+    ><th align="center"
     >Center</th
-    ><th align="left" style="width: 12%;"
+    ><th align="left"
     >Default</th
     ></tr
   ><tr class="odd"
diff --git a/tests/tables.latex b/tests/tables.latex
index d4466b9c0..0dec7e4b0 100644
--- a/tests/tables.latex
+++ b/tests/tables.latex
@@ -2,7 +2,7 @@ Simple table with caption:
 
 \begin{table}[h]
 \begin{center}
-\begin{tabular}{>{\PBS\raggedleft\hspace{0pt}}p{0.15\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.09\columnwidth}>{\PBS\centering\hspace{0pt}}p{0.16\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.13\columnwidth}}
+\begin{tabular}{rlcl}
 Right
  & Left
  & Center
@@ -32,7 +32,7 @@ Right
 Simple table without caption:
 
 \begin{center}
-\begin{tabular}{>{\PBS\raggedleft\hspace{0pt}}p{0.15\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.09\columnwidth}>{\PBS\centering\hspace{0pt}}p{0.16\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.13\columnwidth}}
+\begin{tabular}{rlcl}
 Right
  & Left
  & Center
@@ -61,7 +61,7 @@ Simple table indented two spaces:
 
 \begin{table}[h]
 \begin{center}
-\begin{tabular}{>{\PBS\raggedleft\hspace{0pt}}p{0.15\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.09\columnwidth}>{\PBS\centering\hspace{0pt}}p{0.16\columnwidth}>{\PBS\raggedright\hspace{0pt}}p{0.13\columnwidth}}
+\begin{tabular}{rlcl}
 Right
  & Left
  & Center
diff --git a/tests/tables.man b/tests/tables.man
index 019fa3d83..f49d07b0b 100644
--- a/tests/tables.man
+++ b/tests/tables.man
@@ -4,7 +4,7 @@ Simple table with caption:
 Demonstration of simple table syntax.
 .TS
 tab(@);
-rw(10.50n) lw(6.13n) cw(11.38n) lw(8.75n).
+r l c l.
 T{
 Right
 T}@T{
@@ -48,7 +48,7 @@ Simple table without caption:
 .PP
 .TS
 tab(@);
-rw(10.50n) lw(6.13n) cw(11.38n) lw(8.75n).
+r l c l.
 T{
 Right
 T}@T{
@@ -93,7 +93,7 @@ Simple table indented two spaces:
 Demonstration of simple table syntax.
 .TS
 tab(@);
-rw(10.50n) lw(6.13n) cw(11.38n) lw(8.75n).
+r l c l.
 T{
 Right
 T}@T{
diff --git a/tests/tables.markdown b/tests/tables.markdown
index 21fb015bc..4e05cdc35 100644
--- a/tests/tables.markdown
+++ b/tests/tables.markdown
@@ -1,28 +1,28 @@
 Simple table with caption:
 
-        Right Left      Center    Default
-  ----------- ------ ------------ ---------
-           12 12          12      12
-          123 123        123      123
-            1 1           1       1
+    Right Left    Center  Default
+  ------- ------ -------- ---------
+       12 12        12    12
+      123 123      123    123
+        1 1         1     1
   
   Table: Demonstration of simple table syntax.
 
 Simple table without caption:
 
-        Right Left      Center    Default
-  ----------- ------ ------------ ---------
-           12 12          12      12
-          123 123        123      123
-            1 1           1       1
+    Right Left    Center  Default
+  ------- ------ -------- ---------
+       12 12        12    12
+      123 123      123    123
+        1 1         1     1
 
 Simple table indented two spaces:
 
-        Right Left      Center    Default
-  ----------- ------ ------------ ---------
-           12 12          12      12
-          123 123        123      123
-            1 1           1       1
+    Right Left    Center  Default
+  ------- ------ -------- ---------
+       12 12        12    12
+      123 123      123    123
+        1 1         1     1
   
   Table: Demonstration of simple table syntax.
 
diff --git a/tests/tables.mediawiki b/tests/tables.mediawiki
index 989159846..2f505e6aa 100644
--- a/tests/tables.mediawiki
+++ b/tests/tables.mediawiki
@@ -2,10 +2,10 @@ Simple table with caption:
 
 <table>
 <caption>Demonstration of simple table syntax.</caption><tr>
-<th align="right" style="width: 15%;">Right</th>
-<th align="left" style="width: 8%;">Left</th>
-<th align="center" style="width: 16%;">Center</th>
-<th align="left" style="width: 12%;">Default</th>
+<th align="right">Right</th>
+<th align="left">Left</th>
+<th align="center">Center</th>
+<th align="left">Default</th>
 </tr><tr>
 <td align="right">12</td>
 <td align="left">12</td>
@@ -29,10 +29,10 @@ Simple table without caption:
 
 <table>
 <tr>
-<th align="right" style="width: 15%;">Right</th>
-<th align="left" style="width: 8%;">Left</th>
-<th align="center" style="width: 16%;">Center</th>
-<th align="left" style="width: 12%;">Default</th>
+<th align="right">Right</th>
+<th align="left">Left</th>
+<th align="center">Center</th>
+<th align="left">Default</th>
 </tr><tr>
 <td align="right">12</td>
 <td align="left">12</td>
@@ -56,10 +56,10 @@ Simple table indented two spaces:
 
 <table>
 <caption>Demonstration of simple table syntax.</caption><tr>
-<th align="right" style="width: 15%;">Right</th>
-<th align="left" style="width: 8%;">Left</th>
-<th align="center" style="width: 16%;">Center</th>
-<th align="left" style="width: 12%;">Default</th>
+<th align="right">Right</th>
+<th align="left">Left</th>
+<th align="center">Center</th>
+<th align="left">Default</th>
 </tr><tr>
 <td align="right">12</td>
 <td align="left">12</td>
diff --git a/tests/tables.native b/tests/tables.native
index af3f11f94..13610fad9 100644
--- a/tests/tables.native
+++ b/tests/tables.native
@@ -1,6 +1,6 @@
 Pandoc (Meta [] [] "")
 [ Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"]
-, Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.15,8.75e-2,0.1625,0.125]
+, Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.0,0.0,0.0,0.0]
   [ [ Plain [Str "Right"] ]
   , [ Plain [Str "Left"] ]
   , [ Plain [Str "Center"] ]
@@ -18,7 +18,7 @@ Pandoc (Meta [] [] "")
   , [ Plain [Str "1"] ]
   , [ Plain [Str "1"] ] ] ]
 , Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"]
-, Table [] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.15,8.75e-2,0.1625,0.125]
+, Table [] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.0,0.0,0.0,0.0]
   [ [ Plain [Str "Right"] ]
   , [ Plain [Str "Left"] ]
   , [ Plain [Str "Center"] ]
@@ -36,7 +36,7 @@ Pandoc (Meta [] [] "")
   , [ Plain [Str "1"] ]
   , [ Plain [Str "1"] ] ] ]
 , Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"]
-, Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.15,8.75e-2,0.1625,0.125]
+, Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.0,0.0,0.0,0.0]
   [ [ Plain [Str "Right"] ]
   , [ Plain [Str "Left"] ]
   , [ Plain [Str "Center"] ]
diff --git a/tests/tables.opendocument b/tests/tables.opendocument
index 1b81cddf2..18a7b3cbd 100644
--- a/tests/tables.opendocument
+++ b/tests/tables.opendocument
@@ -67,91 +67,67 @@
       <style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
     </style:style>
     <style:style style:name="Table1">
-      <style:table-properties style:rel-width="100%" table:align="center" />
-    </style:style>
-    <style:style style:name="Table1.A" style:family="table-column">
-      <style:table-column-properties style:column-width="1.05in" />
-    </style:style>
-    <style:style style:name="Table1.B" style:family="table-column">
-      <style:table-column-properties style:column-width="0.61in" />
-    </style:style>
-    <style:style style:name="Table1.C" style:family="table-column">
-      <style:table-column-properties style:column-width="1.14in" />
-    </style:style>
-    <style:style style:name="Table1.D" style:family="table-column">
-      <style:table-column-properties style:column-width="0.88in" />
+      <style:table-properties table:align="center" />
     </style:style>
+    <style:style style:name="Table1.A" style:family="table-column" />
+    <style:style style:name="Table1.B" style:family="table-column" />
+    <style:style style:name="Table1.C" style:family="table-column" />
+    <style:style style:name="Table1.D" style:family="table-column" />
     <style:style style:name="Table1.A1" style:family="table-cell">
       <style:table-cell-properties fo:border="none" />
     </style:style>
     <style:style style:name="Table2">
-      <style:table-properties style:rel-width="100%" table:align="center" />
-    </style:style>
-    <style:style style:name="Table2.A" style:family="table-column">
-      <style:table-column-properties style:column-width="1.05in" />
-    </style:style>
-    <style:style style:name="Table2.B" style:family="table-column">
-      <style:table-column-properties style:column-width="0.61in" />
-    </style:style>
-    <style:style style:name="Table2.C" style:family="table-column">
-      <style:table-column-properties style:column-width="1.14in" />
-    </style:style>
-    <style:style style:name="Table2.D" style:family="table-column">
-      <style:table-column-properties style:column-width="0.88in" />
+      <style:table-properties table:align="center" />
     </style:style>
+    <style:style style:name="Table2.A" style:family="table-column" />
+    <style:style style:name="Table2.B" style:family="table-column" />
+    <style:style style:name="Table2.C" style:family="table-column" />
+    <style:style style:name="Table2.D" style:family="table-column" />
     <style:style style:name="Table2.A1" style:family="table-cell">
       <style:table-cell-properties fo:border="none" />
     </style:style>
     <style:style style:name="Table3">
-      <style:table-properties style:rel-width="100%" table:align="center" />
-    </style:style>
-    <style:style style:name="Table3.A" style:family="table-column">
-      <style:table-column-properties style:column-width="1.05in" />
-    </style:style>
-    <style:style style:name="Table3.B" style:family="table-column">
-      <style:table-column-properties style:column-width="0.61in" />
-    </style:style>
-    <style:style style:name="Table3.C" style:family="table-column">
-      <style:table-column-properties style:column-width="1.14in" />
-    </style:style>
-    <style:style style:name="Table3.D" style:family="table-column">
-      <style:table-column-properties style:column-width="0.88in" />
+      <style:table-properties table:align="center" />
     </style:style>
+    <style:style style:name="Table3.A" style:family="table-column" />
+    <style:style style:name="Table3.B" style:family="table-column" />
+    <style:style style:name="Table3.C" style:family="table-column" />
+    <style:style style:name="Table3.D" style:family="table-column" />
     <style:style style:name="Table3.A1" style:family="table-cell">
       <style:table-cell-properties fo:border="none" />
     </style:style>
     <style:style style:name="Table4">
-      <style:table-properties style:rel-width="100%" table:align="center" />
+      <style:table-properties table:align="center" />
     </style:style>
     <style:style style:name="Table4.A" style:family="table-column">
-      <style:table-column-properties style:column-width="1.05in" />
+      <style:table-column-properties style:rel-column-width="9830*" />
     </style:style>
     <style:style style:name="Table4.B" style:family="table-column">
-      <style:table-column-properties style:column-width="0.96in" />
+      <style:table-column-properties style:rel-column-width="9011*" />
     </style:style>
     <style:style style:name="Table4.C" style:family="table-column">
-      <style:table-column-properties style:column-width="1.14in" />
+      <style:table-column-properties style:rel-column-width="10649*" />
     </style:style>
     <style:style style:name="Table4.D" style:family="table-column">
-      <style:table-column-properties style:column-width="2.36in" />
+      <style:table-column-properties style:rel-column-width="22118*" />
     </style:style>
     <style:style style:name="Table4.A1" style:family="table-cell">
       <style:table-cell-properties fo:border="none" />
     </style:style>
     <style:style style:name="Table5">
-      <style:table-properties style:rel-width="100%" table:align="center" />
+      <style:table-properties table:align="center" />
     </style:style>
     <style:style style:name="Table5.A" style:family="table-column">
-      <style:table-column-properties style:column-width="1.05in" />
+      <style:table-column-properties style:rel-column-width="9830*" />
     </style:style>
     <style:style style:name="Table5.B" style:family="table-column">
-      <style:table-column-properties style:column-width="0.96in" />
+      <style:table-column-properties style:rel-column-width="9011*" />
     </style:style>
     <style:style style:name="Table5.C" style:family="table-column">
-      <style:table-column-properties style:column-width="1.14in" />
+      <style:table-column-properties style:rel-column-width="10649*" />
     </style:style>
     <style:style style:name="Table5.D" style:family="table-column">
-      <style:table-column-properties style:column-width="2.36in" />
+      <style:table-column-properties style:rel-column-width="22118*" />
     </style:style>
     <style:style style:name="Table5.A1" style:family="table-cell">
       <style:table-cell-properties fo:border="none" />
diff --git a/tests/tables.rst b/tests/tables.rst
index db5c1c3d8..0db3efcc5 100644
--- a/tests/tables.rst
+++ b/tests/tables.rst
@@ -1,40 +1,40 @@
 Simple table with caption:
 
-+-------------+--------+--------------+-----------+
-| Right       | Left   | Center       | Default   |
-+=============+========+==============+===========+
-| 12          | 12     | 12           | 12        |
-+-------------+--------+--------------+-----------+
-| 123         | 123    | 123          | 123       |
-+-------------+--------+--------------+-----------+
-| 1           | 1      | 1            | 1         |
-+-------------+--------+--------------+-----------+
++---------+--------+----------+-----------+
+| Right   | Left   | Center   | Default   |
++=========+========+==========+===========+
+| 12      | 12     | 12       | 12        |
++---------+--------+----------+-----------+
+| 123     | 123    | 123      | 123       |
++---------+--------+----------+-----------+
+| 1       | 1      | 1        | 1         |
++---------+--------+----------+-----------+
 
 Table: Demonstration of simple table syntax.
 
 Simple table without caption:
 
-+-------------+--------+--------------+-----------+
-| Right       | Left   | Center       | Default   |
-+=============+========+==============+===========+
-| 12          | 12     | 12           | 12        |
-+-------------+--------+--------------+-----------+
-| 123         | 123    | 123          | 123       |
-+-------------+--------+--------------+-----------+
-| 1           | 1      | 1            | 1         |
-+-------------+--------+--------------+-----------+
++---------+--------+----------+-----------+
+| Right   | Left   | Center   | Default   |
++=========+========+==========+===========+
+| 12      | 12     | 12       | 12        |
++---------+--------+----------+-----------+
+| 123     | 123    | 123      | 123       |
++---------+--------+----------+-----------+
+| 1       | 1      | 1        | 1         |
++---------+--------+----------+-----------+
 
 Simple table indented two spaces:
 
-+-------------+--------+--------------+-----------+
-| Right       | Left   | Center       | Default   |
-+=============+========+==============+===========+
-| 12          | 12     | 12           | 12        |
-+-------------+--------+--------------+-----------+
-| 123         | 123    | 123          | 123       |
-+-------------+--------+--------------+-----------+
-| 1           | 1      | 1            | 1         |
-+-------------+--------+--------------+-----------+
++---------+--------+----------+-----------+
+| Right   | Left   | Center   | Default   |
++=========+========+==========+===========+
+| 12      | 12     | 12       | 12        |
++---------+--------+----------+-----------+
+| 123     | 123    | 123      | 123       |
++---------+--------+----------+-----------+
+| 1       | 1      | 1        | 1         |
++---------+--------+----------+-----------+
 
 Table: Demonstration of simple table syntax.
 
diff --git a/tests/tables.rtf b/tests/tables.rtf
index 0485d4978..bd0a88467 100644
--- a/tests/tables.rtf
+++ b/tests/tables.rtf
@@ -1,7 +1,7 @@
 {\pard \ql \f0 \sa180 \li0 \fi0 Simple table with caption:\par}
 {
 \trowd \trgaph120
-\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2052\clbrdrb\brdrs\cellx3456\clbrdrb\brdrs\cellx4536
+\clbrdrb\brdrs\cellx2160\clbrdrb\brdrs\cellx4320\clbrdrb\brdrs\cellx6480\clbrdrb\brdrs\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 Right\par}
@@ -16,7 +16,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 12\par}
@@ -31,7 +31,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 123\par}
@@ -46,7 +46,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 1\par}
@@ -63,7 +63,7 @@
 {\pard \ql \f0 \sa180 \li0 \fi0 Simple table without caption:\par}
 {
 \trowd \trgaph120
-\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2052\clbrdrb\brdrs\cellx3456\clbrdrb\brdrs\cellx4536
+\clbrdrb\brdrs\cellx2160\clbrdrb\brdrs\cellx4320\clbrdrb\brdrs\cellx6480\clbrdrb\brdrs\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 Right\par}
@@ -78,7 +78,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 12\par}
@@ -93,7 +93,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 123\par}
@@ -108,7 +108,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 1\par}
@@ -125,7 +125,7 @@
 {\pard \ql \f0 \sa180 \li0 \fi0 Simple table indented two spaces:\par}
 {
 \trowd \trgaph120
-\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2052\clbrdrb\brdrs\cellx3456\clbrdrb\brdrs\cellx4536
+\clbrdrb\brdrs\cellx2160\clbrdrb\brdrs\cellx4320\clbrdrb\brdrs\cellx6480\clbrdrb\brdrs\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 Right\par}
@@ -140,7 +140,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 12\par}
@@ -155,7 +155,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 123\par}
@@ -170,7 +170,7 @@
 \intbl\row}
 {
 \trowd \trgaph120
-\cellx1296\cellx2052\cellx3456\cellx4536
+\cellx2160\cellx4320\cellx6480\cellx8640
 \trkeep\intbl
 {
 {\intbl {\pard \qr \f0 \sa0 \li0 \fi0 1\par}
diff --git a/tests/tables.texinfo b/tests/tables.texinfo
index 2b637d7d5..592e36855 100644
--- a/tests/tables.texinfo
+++ b/tests/tables.texinfo
@@ -4,7 +4,7 @@
 Simple table with caption:
 
 @float
-@multitable @columnfractions 0.15 0.09 0.16 0.13 
+@multitable {Right} {Left} {Center} {Default} 
 @headitem 
 Right
  @tab Left
@@ -30,7 +30,7 @@ Right
 @end float
 Simple table without caption:
 
-@multitable @columnfractions 0.15 0.09 0.16 0.13 
+@multitable {Right} {Left} {Center} {Default} 
 @headitem 
 Right
  @tab Left
@@ -56,7 +56,7 @@ Right
 Simple table indented two spaces:
 
 @float
-@multitable @columnfractions 0.15 0.09 0.16 0.13 
+@multitable {Right} {Left} {Center} {Default} 
 @headitem 
 Right
  @tab Left