Support rowspans and colspans in grid tables (#8202)

* Add tests for zero-width and fullwidth chars in grid tables

* T.P.Parsing: simplify `gridTableWith'`, `gridTableWith` [API Change]
  The functions `gridTableWith` and `gridTableWith'` no longer takes a
  boolean argument that toggles whether a table head should be parsed:
  both, tables with heads and without heads, are always accepted now.

* Support colspans, rowspans, and multirow headers in grid tables.

  Grid tables in Markdown, reStructuredText, and Org can now contain cells
  spanning over multiple columns and/or multiple rows; table headers
  containing multiple rows are supported as well.

Note: the markdown writer does not yet support these more complex grid
table features.
This commit is contained in:
Albert Krewinkel 2022-07-30 17:56:44 +02:00 committed by GitHub
parent de5620b04d
commit c015c35a8a
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
10 changed files with 587 additions and 120 deletions

View file

@ -491,6 +491,7 @@ library
exceptions >= 0.8 && < 0.11, exceptions >= 0.8 && < 0.11,
file-embed >= 0.0 && < 0.1, file-embed >= 0.0 && < 0.1,
filepath >= 1.1 && < 1.5, filepath >= 1.1 && < 1.5,
gridtables >= 0.0.2 && < 0.1,
haddock-library >= 1.10 && < 1.11, haddock-library >= 1.10 && < 1.11,
hslua-module-doclayout>= 1.0.4 && < 1.1, hslua-module-doclayout>= 1.0.4 && < 1.1,
hslua-module-path >= 1.0 && < 1.1, hslua-module-path >= 1.0 && < 1.1,

View file

@ -23,8 +23,7 @@ module Text.Pandoc.Parsing.GridTable
) )
where where
import Control.Monad (guard) import Data.Array (elems)
import Data.List (transpose)
import Data.Text (Text) import Data.Text (Text)
import Safe (lastDef) import Safe (lastDef)
import Text.Pandoc.Options (ReaderOptions (readerColumns)) import Text.Pandoc.Options (ReaderOptions (readerColumns))
@ -33,12 +32,11 @@ import Text.Pandoc.Definition
import Text.Pandoc.Parsing.Capabilities import Text.Pandoc.Parsing.Capabilities
import Text.Pandoc.Parsing.General import Text.Pandoc.Parsing.General
import Text.Pandoc.Parsing.Types import Text.Pandoc.Parsing.Types
import Text.Pandoc.Shared (compactify, splitTextByIndices, trim, trimr)
import Text.Pandoc.Sources import Text.Pandoc.Sources
import Text.Parsec import Text.Parsec (Stream (..), optional, sepEndBy1, try)
( Stream (..), many1, notFollowedBy, option, optional, sepEndBy1, try )
import qualified Data.Text as T import qualified Data.Text as T
import qualified Text.GridTable as GT
import qualified Text.Pandoc.Builder as B import qualified Text.Pandoc.Builder as B
-- | Collection of components making up a Table block. -- | Collection of components making up a Table block.
@ -106,11 +104,9 @@ data TableNormalization
-- line). -- line).
gridTableWith :: (Monad m, Monad mf, HasLastStrPosition st, HasReaderOptions st) gridTableWith :: (Monad m, Monad mf, HasLastStrPosition st, HasReaderOptions st)
=> ParserT Sources st m (mf Blocks) -- ^ Block list parser => ParserT Sources st m (mf Blocks) -- ^ Block list parser
-> Bool -- ^ Headerless table
-> ParserT Sources st m (mf Blocks) -> ParserT Sources st m (mf Blocks)
gridTableWith blocks headless = gridTableWith blocks = fmap tableFromComponents <$>
tableWith (gridTableHeader headless blocks) (gridTableRow blocks) gridTableWith' NoNormalization blocks
(gridTableSep '-') gridTableFooter
-- | Like @'gridTableWith'@, but returns 'TableComponents' instead of a -- | Like @'gridTableWith'@, but returns 'TableComponents' instead of a
-- Table. -- Table.
@ -118,97 +114,46 @@ gridTableWith' :: (Monad m, Monad mf,
HasReaderOptions st, HasLastStrPosition st) HasReaderOptions st, HasLastStrPosition st)
=> TableNormalization => TableNormalization
-> ParserT Sources st m (mf Blocks) -- ^ Block list parser -> ParserT Sources st m (mf Blocks) -- ^ Block list parser
-> Bool -- ^ Headerless table
-> ParserT Sources st m (mf TableComponents) -> ParserT Sources st m (mf TableComponents)
gridTableWith' normalization blocks headless = gridTableWith' normalization blocks = do
tableWith' normalization tbl <- GT.gridTable <* optional blanklines
(gridTableHeader headless blocks) (gridTableRow blocks) let blkTbl = GT.mapCells
(gridTableSep '-') gridTableFooter (\lns -> parseFromString' blocks
. flip T.snoc '\n' -- ensure proper block parsing
gridTableSplitLine :: [Int] -> Text -> [Text] . T.unlines
gridTableSplitLine indices line = map removeFinalBar $ tail $ . removeOneLeadingSpace
splitTextByIndices (init indices) $ trimr line $ map T.stripEnd lns)
tbl
-- | Parses a grid segment, where the grid line is made up from the let rows = GT.rows blkTbl
-- given char and terminated with a plus (@+@). The grid line may begin let toPandocCell (GT.Cell c (GT.RowSpan rs) (GT.ColSpan cs)) =
-- and/or end with a colon, signaling column alignment. Returns the size fmap (B.cell AlignDefault (B.RowSpan rs) (B.ColSpan cs) . plainify) <$> c
-- of the grid part and column alignment rows' <- mapM (mapM toPandocCell) rows
gridPart :: Monad m => Char -> ParserT Sources st m (Int, Alignment) columns <- getOption readerColumns
gridPart ch = do let colspecs = zipWith (\cs w -> (convAlign $ fst cs, B.ColWidth w))
leftColon <- option False (True <$ char ':') (elems $ GT.arrayTableColSpecs tbl)
dashes <- many1 (char ch) (fractionalColumnWidths tbl columns)
rightColon <- option False (True <$ char ':') let caption = B.emptyCaption
char '+' return $ do
let lengthDashes = length dashes + (if leftColon then 1 else 0) + rows'' <- mapM sequence rows'
(if rightColon then 1 else 0) let (hRows, bRows) =
let alignment = case (leftColon, rightColon) of splitAt (maybe 0 GT.fromRowIndex $ GT.arrayTableHead tbl)
(True, True) -> AlignCenter (map (B.Row B.nullAttr) rows'')
(True, False) -> AlignLeft let thead = B.TableHead B.nullAttr $ case (hRows, normalization) of
(False, True) -> AlignRight -- normalize header if necessary: remove header if it contains
(False, False) -> AlignDefault -- only a single row in which all cells are empty.
return (lengthDashes + 1, alignment) ([hrow], NormalizeHeader) ->
let Row _attr cells = hrow
gridDashedLines :: Monad m simple = \case
=> Char -> ParserT Sources st m [(Int, Alignment)] Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [] ->
gridDashedLines ch = try $ char '+' >> many1 (gridPart ch) <* blankline True
_ ->
removeFinalBar :: Text -> Text False
removeFinalBar = T.dropWhileEnd go . T.dropWhileEnd (=='|') in [B.Row nullAttr cells | not (null cells) &&
where not (all simple cells)]
go c = T.any (== c) " \t" _ -> hRows
let tfoot = B.TableFoot B.nullAttr []
-- | Separator between rows of grid table. let tbody = B.TableBody B.nullAttr 0 [] bRows
gridTableSep :: Monad m => Char -> ParserT Sources st m Char return $ TableComponents nullAttr caption colspecs thead [tbody] tfoot
gridTableSep ch = try $ gridDashedLines ch >> return '\n'
-- | Parse header for a grid table.
gridTableHeader :: (Monad m, Monad mf, HasLastStrPosition st)
=> Bool -- ^ Headerless table
-> ParserT Sources st m (mf Blocks)
-> ParserT Sources st m (mf [Blocks], [Alignment], [Int])
gridTableHeader True _ = do
optional blanklines
dashes <- gridDashedLines '-'
let aligns = map snd dashes
let lines' = map fst dashes
let indices = scanl (+) 0 lines'
return (return [], aligns, indices)
gridTableHeader False blocks = try $ do
optional blanklines
dashes <- gridDashedLines '-'
rawContent <- many1 (notFollowedBy (gridTableSep '=') >> char '|' >>
T.pack <$> many1Till anyChar newline)
underDashes <- gridDashedLines '='
guard $ length dashes == length underDashes
let lines' = map fst underDashes
let indices = scanl (+) 0 lines'
let aligns = map snd underDashes
let rawHeads = map (T.unlines . map trim) $ transpose
$ map (gridTableSplitLine indices) rawContent
heads <- sequence <$> mapM (parseFromString' blocks . trim) rawHeads
return (heads, aligns, indices)
gridTableRawLine :: (Stream s m Char, UpdateSourcePos s Char)
=> [Int] -> ParserT s st m [Text]
gridTableRawLine indices = do
char '|'
line <- many1Till anyChar newline
return (gridTableSplitLine indices $ T.pack line)
-- | Parse row of grid table.
gridTableRow :: (Monad m, Monad mf, HasLastStrPosition st)
=> ParserT Sources st m (mf Blocks)
-> [Int]
-> ParserT Sources st m (mf [Blocks])
gridTableRow blocks indices = do
colLines <- many1 (gridTableRawLine indices)
let cols = map ((<> "\n") . T.unlines . removeOneLeadingSpace) $
transpose colLines
compactifyCell bs = case compactify [bs] of
[] -> mempty
x:_ -> x
cells <- sequence <$> mapM (parseFromString' blocks) cols
return $ fmap (map compactifyCell) cells
removeOneLeadingSpace :: [Text] -> [Text] removeOneLeadingSpace :: [Text] -> [Text]
removeOneLeadingSpace xs = removeOneLeadingSpace xs =
@ -219,10 +164,23 @@ removeOneLeadingSpace xs =
Nothing -> True Nothing -> True
Just (c, _) -> c == ' ' Just (c, _) -> c == ' '
-- | Parse footer for a grid table. plainify :: B.Blocks -> B.Blocks
gridTableFooter :: (Stream s m Char, UpdateSourcePos s Char) plainify blks = case B.toList blks of
=> ParserT s st m () [Para x] -> B.fromList [Plain x]
gridTableFooter = optional blanklines _ -> blks
convAlign :: GT.Alignment -> B.Alignment
convAlign GT.AlignLeft = B.AlignLeft
convAlign GT.AlignRight = B.AlignRight
convAlign GT.AlignCenter = B.AlignCenter
convAlign GT.AlignDefault = B.AlignDefault
fractionalColumnWidths :: GT.ArrayTable a -> Int -> [Double]
fractionalColumnWidths gt charColumns =
let widths = map ((+1) . snd) $ -- include width of separator
(elems $ GT.arrayTableColSpecs gt)
norm = fromIntegral $ max (sum widths + length widths - 2) charColumns
in map (\w -> fromIntegral w / norm) widths
--- ---

View file

@ -1362,9 +1362,9 @@ multilineTableHeader headless = try $ do
-- (which may be grid), then the rows, -- (which may be grid), then the rows,
-- which may be grid, separated by blank lines, and -- which may be grid, separated by blank lines, and
-- ending with a footer (dashed line followed by blank line). -- ending with a footer (dashed line followed by blank line).
gridTable :: PandocMonad m => Bool -- ^ Headerless table gridTable :: PandocMonad m
-> MarkdownParser m (F TableComponents) => MarkdownParser m (F TableComponents)
gridTable headless = gridTableWith' NormalizeHeader parseBlocks headless gridTable = gridTableWith' NormalizeHeader parseBlocks
pipeBreak :: PandocMonad m => MarkdownParser m ([Alignment], [Int]) pipeBreak :: PandocMonad m => MarkdownParser m ([Alignment], [Int])
pipeBreak = try $ do pipeBreak = try $ do
@ -1466,7 +1466,7 @@ table = try $ do
(guardEnabled Ext_multiline_tables >> (guardEnabled Ext_multiline_tables >>
try (multilineTable True)) <|> try (multilineTable True)) <|>
(guardEnabled Ext_grid_tables >> (guardEnabled Ext_grid_tables >>
try (gridTable False <|> gridTable True)) <?> "table" try gridTable) <?> "table"
optional blanklines optional blanklines
caption <- case frontCaption of caption <- case frontCaption of
Nothing -> option (return mempty) tableCaption Nothing -> option (return mempty) tableCaption

View file

@ -624,7 +624,7 @@ data OrgTable = OrgTable
table :: PandocMonad m => OrgParser m (F Blocks) table :: PandocMonad m => OrgParser m (F Blocks)
table = do table = do
withTables <- getExportSetting exportWithTables withTables <- getExportSetting exportWithTables
tbl <- gridTableWith blocks True <|> orgTable tbl <- gridTableWith blocks <|> orgTable
return $ if withTables then tbl else mempty return $ if withTables then tbl else mempty
-- | A normal org table -- | A normal org table

View file

@ -1252,9 +1252,6 @@ headerBlock = do
-- - multiline support -- - multiline support
-- - ensure that rightmost column span does not need to reach end -- - ensure that rightmost column span does not need to reach end
-- - require at least 2 columns -- - require at least 2 columns
--
-- Grid tables TODO:
-- - column spans
dashedLine :: Monad m => Char -> ParserT Sources st m (Int, Int) dashedLine :: Monad m => Char -> ParserT Sources st m (Int, Int)
dashedLine ch = do dashedLine ch = do
@ -1344,14 +1341,12 @@ simpleTable headless = do
rewidth = fmap $ fmap $ const ColWidthDefault rewidth = fmap $ fmap $ const ColWidthDefault
gridTable :: PandocMonad m gridTable :: PandocMonad m
=> Bool -- ^ Headerless table => RSTParser m Blocks
-> RSTParser m Blocks gridTable = runIdentity <$>
gridTable headerless = runIdentity <$> gridTableWith (Identity <$> parseBlocks)
gridTableWith (Identity <$> parseBlocks) headerless
table :: PandocMonad m => RSTParser m Blocks table :: PandocMonad m => RSTParser m Blocks
table = gridTable False <|> simpleTable False <|> table = gridTable <|> simpleTable False <|> simpleTable True <?> "table"
gridTable True <|> simpleTable True <?> "table"
-- --
-- inline -- inline

View file

@ -10,6 +10,7 @@ extra-deps:
- skylighting-core-0.12.3.1 - skylighting-core-0.12.3.1
- skylighting-0.12.3.1 - skylighting-0.12.3.1
- emojis-0.1.2 - emojis-0.1.2
- gridtables-0.0.2.0
- lpeg-1.0.3 - lpeg-1.0.3
- hslua-2.2.1 - hslua-2.2.1
- hslua-aeson-2.2.1 - hslua-aeson-2.2.1

View file

@ -1022,7 +1022,7 @@ Pandoc
1 1
( "col-1" , [] , [] ) ( "col-1" , [] , [] )
[ Str "col" , Space , Str "1" ] [ Str "col" , Space , Str "1" ]
, Plain [ Str "col" , Space , Str "1" ] , Para [ Str "col" , Space , Str "1" ]
] ]
, Cell , Cell
( "" , [] , [] ) ( "" , [] , [] )
@ -1033,7 +1033,7 @@ Pandoc
1 1
( "col-2" , [] , [] ) ( "col-2" , [] , [] )
[ Str "col" , Space , Str "2" ] [ Str "col" , Space , Str "2" ]
, Plain [ Str "col" , Space , Str "2" ] , Para [ Str "col" , Space , Str "2" ]
] ]
, Cell , Cell
( "" , [] , [] ) ( "" , [] , [] )
@ -1044,7 +1044,7 @@ Pandoc
1 1
( "col-3" , [] , [] ) ( "col-3" , [] , [] )
[ Str "col" , Space , Str "3" ] [ Str "col" , Space , Str "3" ]
, Plain [ Str "col" , Space , Str "3" ] , Para [ Str "col" , Space , Str "3" ]
] ]
] ]
, Row , Row
@ -1261,6 +1261,239 @@ Pandoc
] ]
] ]
(TableFoot ( "" , [] , [] ) []) (TableFoot ( "" , [] , [] ) [])
, Para
[ Str "Table"
, Space
, Str "with"
, Space
, Str "cells"
, Space
, Str "spanning"
, Space
, Str "multiple"
, Space
, Str "rows"
, Space
, Str "or"
, Space
, Str "columns:"
]
, Table
( "" , [] , [] )
(Caption Nothing [])
[ ( AlignDefault , ColWidth 0.19444444444444445 )
, ( AlignDefault , ColWidth 0.1111111111111111 )
, ( AlignDefault , ColWidth 0.1527777777777778 )
]
(TableHead
( "" , [] , [] )
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 2)
[ Plain [ Str "Property" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "Earth" ] ]
]
])
[ TableBody
( "" , [] , [] )
(RowHeadColumns 0)
[]
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 3)
(ColSpan 1)
[ Plain
[ Str "Temperature"
, SoftBreak
, Str "1961-1990"
]
]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "min" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "-89.2" , Space , Str "\176C" ] ]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "mean" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "14" , Space , Str "\176C" ] ]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "min" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "56.7" , Space , Str "\176C" ] ]
]
]
]
(TableFoot ( "" , [] , [] ) [])
, Para
[ Str "Table"
, Space
, Str "with"
, Space
, Str "complex"
, Space
, Str "header:"
]
, Table
( "" , [] , [] )
(Caption Nothing [])
[ ( AlignDefault , ColWidth 0.3055555555555556 )
, ( AlignDefault , ColWidth 0.1111111111111111 )
, ( AlignDefault , ColWidth 0.1111111111111111 )
, ( AlignDefault , ColWidth 0.1111111111111111 )
]
(TableHead
( "" , [] , [] )
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 2)
(ColSpan 1)
[ Plain [ Str "Location" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 3)
[ Plain
[ Str "Temperature"
, Space
, Str "1961-1990"
, SoftBreak
, Str "in"
, Space
, Str "degree"
, Space
, Str "Celsius"
]
]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "min" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "mean" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "max" ] ]
]
])
[ TableBody
( "" , [] , [] )
(RowHeadColumns 0)
[]
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "Antarctica" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "-89.2" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "N/A" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "19.8" ] ]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "Earth" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "-89.2" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "14" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "56.7" ] ]
]
]
]
(TableFoot ( "" , [] , [] ) [])
, Header , Header
2 2
( "entities-in-links-and-titles" , [] , [] ) ( "entities-in-links-and-titles" , [] , [] )

View file

@ -286,6 +286,32 @@ Empty cells
| | | | | |
+---+---+ +---+---+
Table with cells spanning multiple rows or columns:
+---------------------+----------+
| Property | Earth |
+=============+=======+==========+
| | min | -89.2 °C |
| Temperature +-------+----------+
| 1961-1990 | mean | 14 °C |
| +-------+----------+
| | min | 56.7 °C |
+-------------+-------+----------+
Table with complex header:
+---------------------+-----------------------+
| Location | Temperature 1961-1990 |
| | in degree Celsius |
| +-------+-------+-------+
| | min | mean | max |
+=====================+=======+=======+=======+
| Antarctica | -89.2 | N/A | 19.8 |
+---------------------+-------+-------+-------+
| Earth | -89.2 | 14 | 56.7 |
+---------------------+-------+-------+-------+
## Entities in links and titles ## Entities in links and titles
[link](/&uuml;rl "&ouml;&ouml;!") [link](/&uuml;rl "&ouml;&ouml;!")

View file

@ -1474,6 +1474,234 @@ Pandoc
] ]
] ]
(TableFoot ( "" , [] , [] ) []) (TableFoot ( "" , [] , [] ) [])
, Para
[ Str "Table"
, Space
, Str "with"
, Space
, Str "cells"
, Space
, Str "spanning"
, Space
, Str "multiple"
, Space
, Str "rows"
, Space
, Str "or"
, Space
, Str "columns:"
]
, Table
( "" , [] , [] )
(Caption Nothing [])
[ ( AlignDefault , ColWidth 0.175 )
, ( AlignDefault , ColWidth 0.1 )
, ( AlignDefault , ColWidth 0.1375 )
]
(TableHead
( "" , [] , [] )
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 2)
[ Plain [ Str "Property" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "Earth" ] ]
]
])
[ TableBody
( "" , [] , [] )
(RowHeadColumns 0)
[]
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 3)
(ColSpan 1)
[ Plain [ Str "Temperature" , SoftBreak , Str "1961-1990" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "min" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "-89.2" , Space , Str "\176C" ] ]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "mean" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "14" , Space , Str "\176C" ] ]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "min" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "56.7" , Space , Str "\176C" ] ]
]
]
]
(TableFoot ( "" , [] , [] ) [])
, Para
[ Str "Table"
, Space
, Str "with"
, Space
, Str "complex"
, Space
, Str "header:"
]
, Table
( "" , [] , [] )
(Caption Nothing [])
[ ( AlignDefault , ColWidth 0.275 )
, ( AlignDefault , ColWidth 0.1 )
, ( AlignDefault , ColWidth 0.1 )
, ( AlignDefault , ColWidth 0.1 )
]
(TableHead
( "" , [] , [] )
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 2)
(ColSpan 1)
[ Plain [ Str "Location" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 3)
[ Plain
[ Str "Temperature"
, Space
, Str "1961-1990"
, SoftBreak
, Str "in"
, Space
, Str "degree"
, Space
, Str "Celsius"
]
]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "min" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "mean" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "max" ] ]
]
])
[ TableBody
( "" , [] , [] )
(RowHeadColumns 0)
[]
[ Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "Antarctica" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "-89.2" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "N/A" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "19.8" ] ]
]
, Row
( "" , [] , [] )
[ Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "Earth" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "-89.2" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "14" ] ]
, Cell
( "" , [] , [] )
AlignDefault
(RowSpan 1)
(ColSpan 1)
[ Plain [ Str "56.7" ] ]
]
]
]
(TableFoot ( "" , [] , [] ) [])
, Header 1 ( "footnotes" , [] , [] ) [ Str "Footnotes" ] , Header 1 ( "footnotes" , [] , [] ) [ Str "Footnotes" ]
, Para , Para
[ Note [ Note

View file

@ -543,6 +543,31 @@ Multiple blocks in a cell
| r1 bis | - b 2 | c 2 | | r1 bis | - b 2 | c 2 |
+------------------+-----------+------------+ +------------------+-----------+------------+
Table with cells spanning multiple rows or columns:
+---------------------+----------+
| Property | Earth |
+=============+=======+==========+
| | min | -89.2 °C |
| Temperature +-------+----------+
| 1961-1990 | mean | 14 °C |
| +-------+----------+
| | min | 56.7 °C |
+-------------+-------+----------+
Table with complex header:
+---------------------+-----------------------+
| Location | Temperature 1961-1990 |
| | in degree Celsius |
| +-------+-------+-------+
| | min | mean | max |
+=====================+=======+=======+=======+
| Antarctica | -89.2 | N/A | 19.8 |
+---------------------+-------+-------+-------+
| Earth | -89.2 | 14 | 56.7 |
+---------------------+-------+-------+-------+
Footnotes Footnotes
========= =========