diff options
| author | Tuong Nguyen Manh <[email protected]> | 2025-11-03 20:30:33 +0100 |
|---|---|---|
| committer | GitHub <[email protected]> | 2025-11-03 20:30:33 +0100 |
| commit | 594f1099561790453f4fb4bd8558621f4eec724b (patch) | |
| tree | 6da2f86d2c39dee618cb60c4f9eba22369a22110 | |
| parent | a7778c80f3c6a09f728904a93d585c0c955dc447 (diff) | |
asciidoc writer: Add more table features (#11267)
This adds the following table features:
- row span and column span
- footer row
- individual horizontal cell alignment
[API change] T.P.Writers.Shared: Add functions `allRowsEmpty` and
`tableBodiesToRows` from the RST writer for reuse in other writers.
Also fix hlint warning about `unzip` from `NonEmpty`:
The exported polymorphic function will become
monomorphic in the future. Restrict the `NonEmpty`
import to use the Prelude `unzip` function.
| -rw-r--r-- | src/Text/Pandoc/Writers/AsciiDoc.hs | 244 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 15 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Shared.hs | 18 | ||||
| -rw-r--r-- | test/command/7326.md | 1227 | ||||
| -rw-r--r-- | test/command/8665.md | 4 |
5 files changed, 1472 insertions, 36 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index fb0ce0db1..d0150bb37 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {- | @@ -28,9 +29,15 @@ import Control.Monad (foldM) import Control.Monad.State.Strict ( StateT, MonadState(get), gets, modify, evalStateT ) import Data.Char (isPunctuation, isSpace) -import Data.List (delete, intercalate, intersperse) -import Data.List.NonEmpty (NonEmpty(..)) -import Data.Maybe (fromMaybe, isJust) +#if MIN_VERSION_base(4,19,0) +import Data.List (delete, intercalate, intersperse, mapAccumL, uncons, sortOn, unsnoc) +#else +import Data.List (delete, intercalate, intersperse, mapAccumL, uncons, sortOn) +#endif +import Data.List.NonEmpty (NonEmpty((:|)), (<|)) +import qualified Data.List.NonEmpty as NonEmpty +import Data.Maybe (fromMaybe, isJust, catMaybes) +import qualified Data.Map as M import qualified Data.Set as Set import qualified Data.Text as T import Data.Text (Text) @@ -43,12 +50,18 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (blankline, space) import Text.DocLayout +import Text.Pandoc.Builder (emptyCell) import Text.Pandoc.Shared import Text.Pandoc.URI import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared import Text.Pandoc.Walk (walk) +#if !MIN_VERSION_base(4,19,0) +unsnoc :: [a] -> Maybe ([a], a) +unsnoc = foldr (\x -> Just . maybe ([], x) (\(~(a, b)) -> (x : a, b))) Nothing +#endif + data WriterState = WriterState { defListMarker :: Text , orderedListLevel :: Int , bulletListLevel :: Int @@ -269,9 +282,12 @@ blockToAsciiDoc opts (BlockQuote blocks) = do else contents let bar = text "____" return $ bar $$ chomp contents' $$ bar <> blankline -blockToAsciiDoc opts block@(Table _ blkCapt specs thead tbody tfoot) = do - let (caption, aligns, widths, headers, rows) = - toLegacyTable blkCapt specs thead tbody tfoot +blockToAsciiDoc opts block@(Table _ blkCapt specs thead@(TableHead _ originalHeaders) originalTbody tfoot@(TableFoot _ originalFooters)) = do + let (caption, aligns, widths, _, _) = + toLegacyTable blkCapt specs thead originalTbody tfoot + let headers = adjustEmptyRows originalHeaders + let rows = adjustEmptyRows $ tableBodiesToRows originalTbody + let footers = adjustEmptyRows originalFooters caption' <- inlineListToAsciiDoc opts caption let caption'' = if null caption then empty @@ -290,15 +306,19 @@ blockToAsciiDoc opts block@(Table _ blkCapt specs thead tbody tfoot) = do ws -> ws let totalwidth :: Integer totalwidth = floor $ sum widths * 100 - let colspec al wi = (case al of - AlignLeft -> "<" - AlignCenter -> "^" - AlignRight -> ">" - AlignDefault -> "") ++ + let alignmentOperator AlignLeft = "<" + alignmentOperator AlignCenter = "^" + alignmentOperator AlignRight = ">" + alignmentOperator AlignDefault = "" + let colspec al wi = (alignmentOperator al) ++ if wi == 0 then "" else show wi ++ "%" - let headerspec = if all null headers + let optionSpecForRows rowList spec = if allRowsEmpty rowList then Nothing else Just spec + let headerspec = optionSpecForRows headers "header" + let footerspec = optionSpecForRows footers "footer" + let optionsList = catMaybes [headerspec, footerspec] + let optionsspec = if null optionsList then empty - else text "options=\"header\"," + else text "options=\"" <> text (intercalate "," optionsList) <> text "\"," let widthspec = if totalwidth == 0 then empty else text "width=" @@ -310,7 +330,7 @@ blockToAsciiDoc opts block@(Table _ blkCapt specs thead tbody tfoot) = do <> doubleQuotes (text $ intercalate "," $ zipWith colspec aligns widths') <> text "," - <> headerspec <> text "]" + <> optionsspec <> text "]" -- construct cells and recurse in case of nested tables parentTableLevel <- gets tableNestingLevel @@ -335,19 +355,48 @@ blockToAsciiDoc opts block@(Table _ blkCapt specs thead tbody tfoot) = do d <- blockListToAsciiDoc opts bs return $ (text "a" <> separator) $$ d - let makeRow cells = hsep `fmap` mapM makeCell cells - rows' <- mapM makeRow rows - head' <- makeRow headers + let colSpanFactor (ColSpan colSpan) = if colSpan > 1 + then text $ show colSpan + else empty + let rowSpanFactor (RowSpan rowSpan) = if rowSpan > 1 + then text $ "." ++ show rowSpan + else empty + + let makeCellWithSpansAndAlignment (Cell _ alignment rowSpan colSpan blocks) = do + let spanFactor = colSpanFactor colSpan <> rowSpanFactor rowSpan + cell <- makeCell blocks + let alignedCell = alignmentOperator alignment <> cell + + return $ if null spanFactor + then alignedCell + else spanFactor <> text "+" <> alignedCell + + let makeRow (Row attr []) = makeRow $ Row attr $ replicate (length widths') emptyCell + makeRow (Row _ cells) = hsep `fmap` mapM makeCellWithSpansAndAlignment cells + + -- AsciiDoc only supports 1 header row and 1 footer row. + let headerRow = Data.List.uncons $ adjustHeaders headers + let footerRow = unsnoc $ adjustFooters footers + let tailHeaderRows = if allRowsEmpty headers then [] else maybe [] snd headerRow + let initFooterRows = if allRowsEmpty footers then [] else maybe [] fst footerRow + rows' <- mapM makeRow $ tailHeaderRows ++ rows ++ initFooterRows + head' <- case headerRow of + Nothing -> return empty + Just (headerRow', _) -> makeRow headerRow' + foot <- case footerRow of + Nothing -> return empty + Just (_, footerRow') -> makeRow footerRow' modify $ \st -> st{ tableNestingLevel = parentTableLevel } - let head'' = if all null headers then empty else head' + let head'' = if allRowsEmpty headers then empty else head' + let foot' = if allRowsEmpty footers then empty else foot let colwidth = if writerWrapText opts == WrapAuto then writerColumns opts else 100000 - let maxwidth = maximum $ fmap offset (head' :| rows') + let maxwidth = maximum $ fmap offset (foot <| (head' :| rows')) let body = if maxwidth > colwidth then vsep rows' else vcat rows' let border = separator <> text "===" return $ - caption'' $$ tablespec $$ border $$ head'' $$ body $$ border $$ blankline + caption'' $$ tablespec $$ border $$ head'' $$ body $$ foot' $$ border $$ blankline blockToAsciiDoc opts (BulletList items) = do inlist <- gets inList modify $ \st -> st{ inList = True } @@ -715,3 +764,158 @@ imageArguments opts attr altText src title = do then empty else "," <> mconcat (intersperse "," dimList) return $ literal src <> "[" <> linktext <> linktitle <> dims <> "]" + +-- | Adjust header rows for the fact that AsciiDoc only supports a single header row. +-- +-- The first header row will become the single header row in AsciiDoc with the +-- other rows becoming the top body rows. +-- All cells of the first header row with a RowSpan > 1 will be mapped to +-- RowSpan 1 and the remaining RowSpans of those cells wll be added as empty +-- columns into the second row beneath them to preserve the original layout. +adjustHeaders :: [Row] -> [Row] +adjustHeaders [] = [] +adjustHeaders [row] = [row] +adjustHeaders (Row attr firstHeaderCells:secondRow:remainingRows) = + let ((_, emptyHeaderCells), headerRow) = mapAccumL adjustHeaderRowCell (0, []) firstHeaderCells + secondRow' = applyEmptyCells secondRow emptyHeaderCells + in Row attr headerRow:secondRow':remainingRows + where + adjustHeaderRowCell (columnPosition, emptyCells) cell@(Cell cellAttr alignment (RowSpan rowSpan) (ColSpan colSpan) blocks) = + let nextColumnPosition = columnPosition + colSpan + adjustedHeaderCell = Cell cellAttr alignment (RowSpan 1) (ColSpan colSpan) blocks + emptyHeaderRowCell = Cell nullAttr AlignDefault (RowSpan rowSpan - 1) (ColSpan colSpan) [] + emptyCellPosition = (columnPosition, emptyHeaderRowCell) + in if rowSpan > 1 + then ((nextColumnPosition, emptyCellPosition:emptyCells), adjustedHeaderCell) + else ((nextColumnPosition, emptyCells), cell) + +-- | Adjust footer rows for the fact that AsciiDoc only supports a single footer row. +-- +-- The last footer row will become the single footer row in AsciiDoc with the +-- previous footer rows becoming the bottom body rows. +-- All column indices of cells whose RowSpans would reach that last footer row +-- are collected and subtracted by 1. Those collected column indices will then +-- be applied as empty columns into the last footer row to preserve the original +-- layout. +adjustFooters :: [Row] -> [Row] +adjustFooters [] = [] +adjustFooters [row] = [row] +adjustFooters rows = adjustFooters' [] (0, length rows) M.empty rows + where + adjustFooters' _ _ _ [] = [] + adjustFooters' columnIndices _ _ [row] = [applyEmptyCells row columnIndices] + adjustFooters' columnIndices rowInfo@(rowIndex, footerLength) previousRowSpans (row:rest) = + -- Need to keep track of RowSpans from previous rows and how they occupy + -- space in rows beneath them to be able to apply the correct column + -- position of RowSpans that would reach the last footer row. + let (previousRowSpans', row', columnIndices') = adjustFooterRow rowInfo previousRowSpans row + rows' = adjustFooters' (columnIndices ++ columnIndices') (rowIndex + 1, footerLength) previousRowSpans' rest + in row':rows' + + adjustFooterRow rowInfo previousRowSpans (Row attr cells) = + let ((nextColumnPosition, previousRowSpans'), cells') = mapAccumL (adjustFooterCell rowInfo) (0, previousRowSpans) cells + (cells'', columnIndices) = unzip cells' + + -- Apply row spans from a previous row that are next to the end of the + -- current row's cells to keep track of the correct column position. + previousRowSpans'' = M.mapWithKey (applyTrailingPreviousRowSpans nextColumnPosition) previousRowSpans' + in (previousRowSpans'', Row attr cells'', catMaybes columnIndices) + + applyTrailingPreviousRowSpans nextColumnPosition columnPosition previousRowSpan@(RowSpan rowSpan, ColSpan colSpan) = + if columnPosition >= nextColumnPosition && rowSpan >= 1 + then (RowSpan rowSpan - 1, ColSpan colSpan) + else previousRowSpan + +-- | Adjust footer cell for the fact that AsciiDoc only supports a single footer row. +-- +-- Collects cells whose RowSpan would reach to the last footer row and applies +-- them as empty cells to that last footer row. +adjustFooterCell :: (Int, Int) -> (Int, M.Map Int (RowSpan, ColSpan)) -> Cell -> ((Int, M.Map Int (RowSpan, ColSpan)), (Cell, Maybe (Int, Cell))) +adjustFooterCell rowInfo@(rowIndex, footerLength) (columnPosition, previousSpans) cell@(Cell _ _ (RowSpan rowSpan) (ColSpan colSpan) _) + | Just previous@(RowSpan previousRowSpan, ColSpan previousColSpan) <- M.lookup columnPosition previousSpans + , previousRowSpan >= 1 = + -- Apply row span from a previous row that occupies this column to keep + -- track of the correct column position. + adjustFooterCell rowInfo (columnPosition + previousColSpan, updatePreviousRowSpan previous) cell + | rowSpan > 1 && rowIndex + rowSpan >= footerLength = + -- Adjust row span that would reach all the way to the last footer row and + -- keep track of that to apply it to the last footer row. + ((nextColumnPosition, previousRowSpans'), (decrementRowSpanInCell cell, Just (columnPosition, emptyCellWithColSpan))) + | otherwise = ((nextColumnPosition, previousRowSpans'), (cell, Nothing)) + where + -- Keep track of this cell's RowSpan for the rows following it. + previousRowSpans' = if rowSpan > 1 + then M.insert columnPosition (RowSpan rowSpan - 1, ColSpan colSpan) previousSpans -- Minus its own row. + else previousSpans + + updatePreviousRowSpan (RowSpan previousRowSpan, previousColSpan) = + if previousRowSpan > 1 + then M.insert columnPosition (RowSpan previousRowSpan - 1, previousColSpan) previousSpans + else M.delete columnPosition previousSpans + + nextColumnPosition = columnPosition + colSpan + emptyCellWithColSpan = Cell nullAttr AlignDefault (RowSpan 1) (ColSpan colSpan) [] + +-- | Adjust empty rows for AsciiDoc. +-- +-- An empty row without any cells decrements RowSpans that cover it and is +-- removed by them to adjust for being unable to express empty rows with no +-- cells in AsciiDoc. +adjustEmptyRows :: [Row] -> [Row] +adjustEmptyRows = adjustEmptyRows' . map applyInitialRowsLeft + where + adjustEmptyRows' [] = [] + adjustEmptyRows' (row:rest) + | maxRowSpan' <- maxRowSpan row + , maxRowSpan' > 1 = + -- Consume empty rows within the row's span. + let followingRows = take (maxRowSpan' - 1) rest + rows = consumeEmptyRows (row :| []) followingRows + rest' = drop (length followingRows) rest + in rowFromCellsWithRowsLeft (NonEmpty.head rows) : adjustEmptyRows' (NonEmpty.tail rows ++ rest') + | otherwise = rowFromCellsWithRowsLeft row : adjustEmptyRows' rest + + rowFromCellsWithRowsLeft (attr, cellsWithRowsLeft) = Row attr $ map fst cellsWithRowsLeft + cellRowSpan (Cell _ _ (RowSpan rowSpan) _ _) = rowSpan + + consumeEmptyRows rows [] = NonEmpty.reverse rows + consumeEmptyRows rows (followingRow:restRows) = + if null (snd followingRow) && any rowHasRowSpanAndRowsLeft rows + then consumeEmptyRows (fmap (subtractRowsLeft decrementRowSpanInCell) rows) restRows -- Consume empty row for RowSpan and remove it + else consumeEmptyRows (followingRow <| fmap (subtractRowsLeft id) rows) restRows + + rowHasRowSpanAndRowsLeft (_, cells) = any cellHasRowSpanAndRowsLeft cells + cellHasRowSpanAndRowsLeft (cell, rowsLeft) = cellRowSpan cell > 1 && rowsLeft >= 1 + + subtractRowsLeft changeCell (attr, cells) = (attr, map (subtractRowsLeftCell changeCell) cells) + + subtractRowsLeftCell changeCell cellPair@(cell, rowsLeft) + | rowsLeft >= 1 = (changeCell cell, rowsLeft - 1) + | otherwise = cellPair + + applyInitialRowsLeft (Row attr cells) = (attr, map applyInitialRowsLeftCell cells) + + applyInitialRowsLeftCell cell + | rowSpan <- cellRowSpan cell, rowSpan > 1 = (cell, rowSpan - 1) -- Minus its own row + | otherwise = (cell, 0) + + maxRowSpan (_, []) = 0 + maxRowSpan (_, cells) = maximum $ map (cellRowSpan . fst) cells + +-- | Decrement the RowSpan of a Cell if that RowSpan > 1. +decrementRowSpanInCell :: Cell -> Cell +decrementRowSpanInCell cell@(Cell attr alignment (RowSpan rowSpan) colSpan blocks) = + if rowSpan > 1 + then Cell attr alignment (RowSpan rowSpan - 1) colSpan blocks + else cell + +-- | Apply empty table cells at the given positions inside a Row. +applyEmptyCells :: Row -> [(Int, Cell)] -> Row +applyEmptyCells (Row attr cells) = Row attr . applyEmptyCells' 0 cells . sortOn fst + where + applyEmptyCells' _ cells' [] = cells' + applyEmptyCells' currentPosition cells' ((columnPosition, columnEmptyCell@(Cell _ _ _ (ColSpan colSpan) _)):rest) + | columnPosition == currentPosition = columnEmptyCell : applyEmptyCells' (currentPosition + colSpan) cells' rest + applyEmptyCells' _ [] _ = [] + applyEmptyCells' currentPosition (cell@(Cell _ _ _ (ColSpan currentCellColSpan) _):restCells) emptyCellList = + cell : applyEmptyCells' (currentPosition + currentCellColSpan) restCells emptyCellList diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 7a6bc29b9..680b3b07c 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -925,23 +925,19 @@ simpleTable :: PandocMonad m -> TableFoot -> m (Doc Text) simpleTable opts blocksToDoc (TableHead _ headers) tbody (TableFoot _ footers) = do - headerDocs <- if all isEmptyRow headers + headerDocs <- if allRowsEmpty headers then return [] else fixEmpties <$> mapM rowToDoc headers rowDocs <- fixEmpties <$> mapM rowToDoc ((tableBodiesToRows tbody) ++ footers) let numChars = maybe 0 maximum . NE.nonEmpty . map (offset . fst) let colWidths = map numChars $ transpose (headerDocs ++ rowDocs) let hline = nowrap $ hsep (map (\n -> literal (T.replicate n "=")) colWidths) - let hdr = if all isEmptyRow headers + let hdr = if allRowsEmpty headers then mempty else hline $$ mapToRow colWidths headerDocs let bdy = mapToRow colWidths rowDocs return $ hdr $$ hline $$ bdy $$ hline where - isEmptyRow (Row _ cells) = all isEmptyCell cells - - isEmptyCell (Cell _ _ _ _ blocks) = null blocks - -- can't have empty cells in first column: fixEmpties (d:ds) = fixEmpties' d : ds fixEmpties [] = [] @@ -991,10 +987,3 @@ simpleTable opts blocksToDoc (TableHead _ headers) tbody (TableFoot _ footers) = then colWidthsSum + colWidthsLength - 1 else colWidthsSum in literal $ T.replicate dashLength "-" - --- | Concatenates the header and body Rows of a List of TableBody into a flat --- List of Rows. -tableBodiesToRows :: [TableBody] -> [Row] -tableBodiesToRows = concatMap tableBodyToRows - where - tableBodyToRows (TableBody _ _ headerRows bodyRows) = headerRows ++ bodyRows diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index 9d71f2fb3..2fdb8de5d 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -50,6 +50,8 @@ module Text.Pandoc.Writers.Shared ( , isOrderedListMarker , toTaskListItem , delimited + , allRowsEmpty + , tableBodiesToRows ) where import Safe (lastMay, maximumMay) @@ -59,7 +61,7 @@ import Data.Either (isRight) import Data.Aeson (ToJSON (..), encode) import Data.Char (chr, ord, isSpace, isLetter, isUpper) import Data.List (groupBy, intersperse, foldl', transpose) -import Data.List.NonEmpty (NonEmpty(..)) +import Data.List.NonEmpty (NonEmpty((:|))) import Data.Text.Conversions (FromText(..)) import qualified Data.Map as M import qualified Data.Text as T @@ -857,3 +859,17 @@ delimited opener closer content = toList (Concat (Concat a b) c) = toList (Concat a (Concat b c)) toList (Concat a b) = a : toList b toList x = [x] + +-- | Determine whether all rows and their cells are empty. +allRowsEmpty :: [Row] -> Bool +allRowsEmpty = all isEmptyRow + where + isEmptyRow (Row _ cells) = all isEmptyCell cells + isEmptyCell (Cell _ _ _ _ blocks) = null blocks + +-- | Concatenates the header and body Rows of a List of TableBody into a flat +-- List of Rows. +tableBodiesToRows :: [TableBody] -> [Row] +tableBodiesToRows = concatMap tableBodyToRows + where + tableBodyToRows (TableBody _ _ headerRows bodyRows) = headerRows ++ bodyRows diff --git a/test/command/7326.md b/test/command/7326.md new file mode 100644 index 000000000..7d807b105 --- /dev/null +++ b/test/command/7326.md @@ -0,0 +1,1227 @@ +Table with row and column spans +``` +% pandoc -f html -t asciidoc +<table> + <colgroup> + <col style="width: 17%" /> + <col style="width: 16%" /> + <col style="width: 15%" /> + <col style="width: 52%" /> + </colgroup> + <thead> + <tr> + <th>Header 1</th> + <th>Header 2</th> + <th>Header 3</th> + <th>Header 4</th> + </tr> + </thead> + <tbody> + <tr> + <td>body row 1</td> + <td>column 2</td> + <td>column 3</td> + <td>column 4</td> + </tr> + <tr> + <td>body row 2</td> + <td colspan="2">Cells may span columns.</td> + <td>fff</td> + </tr> + <tr> + <td>body row 3</td> + <td rowspan="2">Cells may span rows.</td> + <td rowspan="2"> + <ul> + <li>Cells</li> + <li>can</li> + <li>contain</li> + <li>blocks.</li> + </ul> + </td> + <td rowspan="2"> + <ul> + <li>This is a very long line of text</li> + <li><a href="http://www.python.org/">Python</a></li> + <li>b</li> + <li>c</li> + </ul> + </td> + </tr> + <tr> + <td>body row 4</td> + </tr> + </tbody> +</table> +^D +[width="100%",cols="17%,16%,15%,52%",options="header",] +|=== +|Header 1 |Header 2 |Header 3 |Header 4 +|body row 1 |column 2 |column 3 |column 4 +|body row 2 2+|Cells may span columns. |fff +|body row 3 .2+|Cells may span rows. .2+a| +* Cells +* can +* contain +* blocks. + +.2+a| +* This is a very long line of text +* http://www.python.org/[Python] +* b +* c + +|body row 4 +|=== +``` + +Header and footer. +AsciiDoc only supports 1 header and 1 footer row. +So for multiple header and/or footer rows all the extra rows become part of the table body. +``` +% pandoc -f html -t asciidoc +<table> + <thead> + <tr> + <th colspan="2">Inputs</th> + <th>Output</th> + </tr> + <tr> + <th>A</th> + <th>B</th> + <th>A or B</th> + </tr> + </thead> + <tbody> + <tr> + <td>False</td> + <td>False</td> + <td>False</td> + </tr> + <tr> + <td>True</td> + <td>False</td> + <td>True</td> + </tr> + <tr> + <td>False</td> + <td>True</td> + <td>True</td> + </tr> + <tr> + <td>True</td> + <td>True</td> + <td>True</td> + </tr> + </tbody> + <tfoot> + <tr> + <td>A</td> + <td>B</td> + <td>A or B</td> + </tr> + <tr> + <td colspan="2">Inputs</td> + <td>Output</td> + </tr> + </tfoot> +</table> +<table> + <thead> + <tr> + <th colspan="2">Header</th> + </tr> + </thead> + <tbody> + <tr> + <td>Body 1-1</td> + <td>Body 2-1</td> + </tr> + </tbody> + <tfoot> + <tr> + <td colspan="2">Footer</td> + </tr> + </tfoot> +</table> +^D +[cols=",,",options="header,footer",] +|=== +2+|Inputs |Output +|A |B |A or B +|False |False |False +|True |False |True +|False |True |True +|True |True |True +|A |B |A or B +2+|Inputs |Output +|=== + +[cols=",",options="header,footer",] +|=== +2+|Header +|Body 1-1 |Body 2-1 +2+|Footer +|=== +``` + +Table without header but with footer rows +``` +% pandoc -f html -t asciidoc +<table> + <colgroup> + <col style="width: 37%" /> + <col style="width: 37%" /> + <col style="width: 26%" /> + </colgroup> + <tbody> + <tr> + <td>False</td> + <td>False</td> + <td>False</td> + </tr> + <tr> + <td>True</td> + <td>False</td> + <td>True</td> + </tr> + <tr> + <td>False</td> + <td>True</td> + <td>True</td> + </tr> + <tr> + <td>True</td> + <td>True</td> + <td>True</td> + </tr> + </tbody> + <tfoot> + <tr> + <td>A</td> + <td>B</td> + <td>A or B</td> + </tr> + <tr> + <td colspan="2">Inputs</td> + <td>Output</td> + </tr> + </tfoot> +</table> +^D +[width="100%",cols="37%,37%,26%",options="footer",] +|=== +|False |False |False +|True |False |True +|False |True |True +|True |True |True +|A |B |A or B +2+|Inputs |Output +|=== +``` + +Adjust row span for multiple header rows +``` +% pandoc -f html -t asciidoc +<table style="width: 63%"> + <colgroup> + <col style="width: 30%" /> + <col style="width: 11%" /> + <col style="width: 11%" /> + <col style="width: 11%" /> + </colgroup> + <thead> + <tr> + <th rowspan="2">Location</th> + <th colspan="3">Temperature 1961-1990 in degree Celsius</th> + </tr> + <tr> + <th>min</th> + <th>mean</th> + <th>max</th> + </tr> + </thead> + <tbody> + <tr> + <td>Antarctica</td> + <td>-89.2</td> + <td>N/A</td> + <td>19.8</td> + </tr> + <tr> + <td>Earth</td> + <td>-89.2</td> + <td>14</td> + <td>56.7</td> + </tr> + </tbody> +</table> +<table style="width: 63%"> + <colgroup> + <col style="width: 11%" /> + <col style="width: 11%" /> + <col style="width: 11%" /> + <col style="width: 30%" /> + </colgroup> + <thead> + <tr> + <th colspan="3">Temperature 1961-1990 in degree Celsius</th> + <th rowspan="2">Location</th> + </tr> + <tr> + <th>min</th> + <th>mean</th> + <th>max</th> + </tr> + </thead> + <tbody> + <tr> + <td>-89.2</td> + <td>N/A</td> + <td>19.8</td> + <td>Antarctica</td> + </tr> + <tr> + <td>-89.2</td> + <td>14</td> + <td>56.7</td> + <td>Earth</td> + </tr> + </tbody> +</table> +<table style="width: 65%"> + <colgroup> + <col style="width: 11%" /> + <col style="width: 11%" /> + <col style="width: 11%" /> + <col style="width: 18%" /> + <col style="width: 14%" /> + </colgroup> + <thead> + <tr> + <th colspan="3">Temperature 1961-1990 in degree Celsius</th> + <th rowspan="2">Location</th> + <th>Extra</th> + </tr> + <tr> + <th>min</th> + <th>mean</th> + <th>max</th> + <th>Extra 2</th> + </tr> + </thead> + <tbody> + <tr> + <td>-89.2</td> + <td>N/A</td> + <td>19.8</td> + <td>Antarctica</td> + <td>Extra 3</td> + </tr> + <tr> + <td>-89.2</td> + <td>14</td> + <td>56.7</td> + <td>Earth</td> + <td>Extra 4</td> + </tr> + </tbody> +</table> +<table> + <thead> + <tr> + <th>Header 1-1</th> + <th colspan="2" rowspan="2">Header 1-2</th> + </tr> + <tr> + <th>Header 2-1</th> + </tr> + <tr> + <th>Header 3-1</th> + <th>Header 3-2</th> + <th>Header 3-3</th> + </tr> + </thead> + <tbody> + <tr> + <td rowspan="2">Body 1-1</td> + <td colspan="2">Body 1-2</td> + </tr> + <tr> + <td>Body 2-1</td> + <td>Body 2-2</td> + </tr> + </tbody> +</table> +<table> + <thead> + <tr> + <th rowspan="2">Header 1-1</th> + <th>Header 1-2</th> + <th rowspan="2">Header 1-3</th> + </tr> + <tr> + <th>Header 2-1</th> + </tr> + <tr> + <th>Header 3-1</th> + <th>Header 3-2</th> + <th>Header 3-3</th> + </tr> + </thead> + <tbody></tbody> +</table> +^D +[width="63%",cols="49%,17%,17%,17%",options="header",] +|=== +|Location 3+|Temperature 1961-1990 in degree Celsius +| |min |mean |max +|Antarctica |-89.2 |N/A |19.8 +|Earth |-89.2 |14 |56.7 +|=== + +[width="63%",cols="19%,17%,17%,47%",options="header",] +|=== +3+|Temperature 1961-1990 in degree Celsius |Location +|min |mean |max | +|-89.2 |N/A |19.8 |Antarctica +|-89.2 |14 |56.7 |Earth +|=== + +[width="65%",cols="20%,16%,16%,27%,21%",options="header",] +|=== +3+|Temperature 1961-1990 in degree Celsius |Location |Extra +|min |mean |max | |Extra 2 +|-89.2 |N/A |19.8 |Antarctica |Extra 3 +|-89.2 |14 |56.7 |Earth |Extra 4 +|=== + +[cols=",,",options="header",] +|=== +|Header 1-1 2+|Header 1-2 +|Header 2-1 2+| +|Header 3-1 |Header 3-2 |Header 3-3 +.2+|Body 1-1 2+|Body 1-2 +|Body 2-1 |Body 2-2 +|=== + +[cols=",,",options="header",] +|=== +|Header 1-1 |Header 1-2 |Header 1-3 +| |Header 2-1 | +|Header 3-1 |Header 3-2 |Header 3-3 +|=== +``` + +Adjust row span in multiple footer rows. +``` +% pandoc -f html -t asciidoc +<table> + <colgroup> + <col style="width: 40%" /> + <col style="width: 40%" /> + <col style="width: 20%" /> + </colgroup> + <tbody> + <tr> + <td>Body 1-1</td> + <td>Body 1-2</td> + <td>Body 1-3</td> + </tr> + </tbody> + <tfoot> + <tr> + <td colspan="2">Footer 1-1/2</td> + <td>Footer 1-3</td> + </tr> + <tr> + <td>Footer 2-1</td> + <td rowspan="3">Span 3</td> + <td>Footer 2-3</td> + </tr> + <tr> + <td rowspan="2">Span 2</td> + <td>Footer 3-3</td> + </tr> + <tr> + <td>Footer 4-3</td> + </tr> + </tfoot> +</table> +<table> + <tbody> + <tr> + <td>Body 1-1</td> + <td>Body 1-2</td> + <td>Body 1-3</td> + <td>Body 1-4</td> + <td>Body 1-5</td> + </tr> + <tr> + <td>Body 2-1</td> + <td>Body 2-2</td> + <td>Body 2-3</td> + <td>Body 2-4</td> + <td>Body 2-5</td> + </tr> + </tbody> + <tfoot> + <tr> + <td colspan="3">Footer 1-1/2/3</td> + <td>Footer 1-4</td> + <td>Footer 1-5</td> + </tr> + <tr> + <td>Footer 2-1</td> + <td rowspan="3">Span 3</td> + <td>Footer 2-3</td> + <td colspan="2">Footer 2-4/5</td> + </tr> + <tr> + <td rowspan="2">Span 2</td> + <td colspan="2">Footer 3-3/4</td> + <td rowspan="2">Span 2</td> + </tr> + <tr> + <td rowspan="3">Span 3</td> + <td>Footer 4-4</td> + </tr> + <tr> + <td>Footer 5-1</td> + <td>Footer 5-2</td> + <td>Footer 5-4</td> + <td rowspan="2">Span 2</td> + </tr> + <tr> + <td colspan="2">Footer 6-1/2</td> + <td>Footer 6-4</td> + </tr> + </tfoot> +</table> +<table> + <tbody> + <tr> + <td>Body 1</td> + <td>Body 2</td> + <td>Body 3</td> + <td>Body 4</td> + </tr> + </tbody> + <tfoot> + <tr> + <td>Footer 1-1</td> + <td colspan="2" rowspan="3">Span 3</td> + <td rowspan="2">Span 2</td> + </tr> + <tr> + <td>Footer 2-1</td> + </tr> + <tr> + <td>Footer 3-1</td> + <td>Footer 3-4</td> + </tr> + </tfoot> +</table> +<table> + <tbody> + <tr> + <td>Body 1-1</td> + <td>Body 1-2</td> + <td>Body 1-3</td> + <td>Body 1-4</td> + </tr> + </tbody> + <tfoot> + <tr> + <td colspan="2">Footer 1-1/2</td> + <td rowspan="6">Span 6</td> + <td>Footer 1-4</td> + </tr> + <tr> + <td rowspan="3">Span 3</td> + <td>Footer 2-2</td> + <td>Footer 2-4</td> + </tr> + <tr> + <td>Footer 3-2</td> + <td>Footer 3-4</td> + </tr> + <tr> + <td>Footer 4-2</td> + <td>Footer 4-4</td> + </tr> + <tr> + <td>Footer 5-1</td> + <td>Footer 5-2</td> + <td rowspan="2">Span 2</td> + </tr> + <tr> + <td colspan="2">Footer 6-1/2</td> + </tr> + </tfoot> +</table> +^D +[width="100%",cols="40%,40%,20%",options="footer",] +|=== +|Body 1-1 |Body 1-2 |Body 1-3 +2+|Footer 1-1/2 |Footer 1-3 +|Footer 2-1 .2+|Span 3 |Footer 2-3 +|Span 2 |Footer 3-3 +| | |Footer 4-3 +|=== + +[cols=",,,,",options="footer",] +|=== +|Body 1-1 |Body 1-2 |Body 1-3 |Body 1-4 |Body 1-5 +|Body 2-1 |Body 2-2 |Body 2-3 |Body 2-4 |Body 2-5 +3+|Footer 1-1/2/3 |Footer 1-4 |Footer 1-5 +|Footer 2-1 .3+|Span 3 |Footer 2-3 2+|Footer 2-4/5 +.2+|Span 2 2+|Footer 3-3/4 .2+|Span 2 +.2+|Span 3 |Footer 4-4 +|Footer 5-1 |Footer 5-2 |Footer 5-4 |Span 2 +2+|Footer 6-1/2 | |Footer 6-4 | +|=== + +[cols=",,,",options="footer",] +|=== +|Body 1 |Body 2 |Body 3 |Body 4 +|Footer 1-1 2.2+|Span 3 .2+|Span 2 +|Footer 2-1 +|Footer 3-1 2+| |Footer 3-4 +|=== + +[cols=",,,",options="footer",] +|=== +|Body 1-1 |Body 1-2 |Body 1-3 |Body 1-4 +2+|Footer 1-1/2 .5+|Span 6 |Footer 1-4 +.3+|Span 3 |Footer 2-2 |Footer 2-4 +|Footer 3-2 |Footer 3-4 +|Footer 4-2 |Footer 4-4 +|Footer 5-1 |Footer 5-2 |Span 2 +2+|Footer 6-1/2 | | +|=== +``` + +Individual cell alignments +``` +% pandoc -f native -t asciidoc +[ Table + ( "" , [] , [] ) + (Caption Nothing []) + [ ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + ] + (TableHead + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignLeft + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Left" , Space , Str "Header" ] ] + , Cell + ( "" , [] , [] ) + AlignCenter + (RowSpan 2) + (ColSpan 2) + [ Plain [ Str "Center" , Space , Str "Headers" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignRight + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Right" , Space , Str "Header" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignCenter + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Center" , Space , Str "Header" ] ] + , Cell + ( "" , [] , [] ) + AlignRight + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Right" , Space , Str "Header" ] ] + , Cell + ( "" , [] , [] ) + AlignLeft + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Left" , Space , Str "Header" ] ] + ] + ]) + [ TableBody + ( "" , [] , [] ) + (RowHeadColumns 0) + [] + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignRight + (RowSpan 2) + (ColSpan 1) + [ Plain [ Str "Right" , Space , Str "Body" ] ] + , Cell + ( "" , [] , [] ) + AlignLeft + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Left" , Space , Str "Body" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignCenter + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Center" , Space , Str "Body" ] ] + , Cell + ( "" , [] , [] ) + AlignRight + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Right" , Space , Str "Body" ] ] + ] + ] + ] + (TableFoot + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignCenter + (RowSpan 1) + (ColSpan 3) + [ Plain [ Str "Center" , Space , Str "Footer" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignLeft + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Left" , Space , Str "Footer" ] ] + , Cell + ( "" , [] , [] ) + AlignCenter + (RowSpan 3) + (ColSpan 1) + [ Plain [ Str "Center" , Space , Str "Footer" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignRight + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Right" , Space , Str "Footer" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignCenter + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Center" , Space , Str "Footer" ] ] + ] + ]) +] +^D +[cols=",,",options="header,footer",] +|=== +<|Left Header 2+^|Center Headers +>|Right Header 2+| +^|Center Header >|Right Header <|Left Header +.2+>|Right Body 2+<|Left Body +^|Center Body >|Right Body +3+^|Center Footer +2+<|Left Footer .2+^|Center Footer +2+>|Right Footer +2+^|Center Footer | +|=== +``` + +Adjust row span for empty rows and handle empty rows in general +``` +% pandoc -f native -t asciidoc +[ Table + ( "" , [] , [] ) + (Caption Nothing []) + [ ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + ] + (TableHead + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 2) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "1-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 3) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "3" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 2) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "1-3" ] ] + ] + , Row ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "2-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "2-3" ] ] + ] + ]) + [ TableBody + ( "" , [] , [] ) + (RowHeadColumns 0) + [] + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 3) + (ColSpan 2) + [ Plain [ Str "Body" , Space , Str "1-1/2" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 5) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "5" ] ] + ] + , Row ( "" , [] , [] ) [] + , Row ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "2-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "2-2" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "3-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "3-2" ] ] + ] + , Row ( "" , [] , [] ) [] + ] + ] + (TableFoot + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 5) + (ColSpan 1) + [ Plain + [ Str "Span" , Space , Str "5" ] + ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Footer" , Space , Str "1-2" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 2) + (ColSpan 2) + [ Plain + [ Str "Span" , Space , Str "2" ] + ] + ] + , Row ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Footer" , Space , Str "3-2/3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Footer" , Space , Str "4-2/3" ] ] + ] + ]) +, Table + ( "" , [] , [] ) + (Caption Nothing []) + [ ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + ] + (TableHead ( "" , [] , [] ) []) + [ TableBody + ( "" , [] , [] ) + (RowHeadColumns 0) + [] + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "1-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "1-2" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 3) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "4" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 5) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "5" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "2-2" ] ] + ] + , Row + ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "3-2" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "3-3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "4-2" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "4-3" ] ] + ] + , Row + ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "6-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "6-2" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "6-3" ] ] + ] + ] + ] + (TableFoot + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "1-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 8) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "8" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "1-3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 3) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "3" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "2-3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 2) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "2" ] ] + ] + , Row ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "4-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "4-3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "5-1" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 3) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 2) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "2" ] ] + ] + , Row ( "" , [] , [] ) [] + ]) +, Table + ( "" , [] , [] ) + (Caption Nothing []) + [ ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + ] + (TableHead ( "" , [] , [] ) []) + [ TableBody + ( "" , [] , [] ) + (RowHeadColumns 0) + [] + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [ "rowspan-cell" ] , [] ) + AlignDefault + (RowSpan 6) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "6" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "1-2" ] ] + , Cell + ( "" , [ "rowspan-cell" ] , [] ) + AlignDefault + (RowSpan 2) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "2" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [ "rowspan-cell" ] , [] ) + AlignDefault + (RowSpan 3) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "3" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [ "rowspan-cell" ] , [] ) + AlignDefault + (RowSpan 4) + (ColSpan 1) + [ Plain [ Str "Span" , Space , Str "4" ] ] + ] + , Row ( "" , [] , [] ) [] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "3-2" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Body" , Space , Str "4-2" ] ] + ] + , Row ( "" , [] , [] ) [] + , Row ( "" , [] , [] ) [] + ] + ] + (TableFoot ( "" , [] , [] ) []) +] +^D +[cols=",,",options="header,footer",] +|=== +|Header 1-1 |Span 3 |Header 1-3 +|Header 2-1 | |Header 2-3 +2+|Body 1-1/2 .3+|Span 5 +|Body 2-1 |Body 2-2 +|Body 3-1 |Body 3-2 +| | | +.3+|Span 5 2+|Footer 1-2 +2+|Span 2 +2+|Footer 3-2/3 +| 2+|Footer 4-2/3 +|=== + +[cols=",,",options="footer",] +|=== +|Body 1-1 |Body 1-2 .2+|Span 4 +.3+|Span 5 |Body 2-2 +|Body 3-2 |Body 3-3 +|Body 4-2 |Body 4-3 +| | | +|Body 6-1 |Body 6-2 |Span 6-3 +|Footer 1-1 .5+|Span 8 |Footer 1-3 +.2+|Span 3 |Footer 2-3 +|Span 2 +|Footer 4-1 |Footer 4-3 +|Footer 5-1 |Span 3 +|Span 2 | | +|=== + +[cols=",,",] +|=== +.5+|Span 6 |Body 1-2 .2+|Span 2 +.2+|Span 3 +.3+|Span 4 +|Body 3-2 +|Body 4-2 +| | | +| | | +|=== +``` diff --git a/test/command/8665.md b/test/command/8665.md index 562da95cd..7c98a9f32 100644 --- a/test/command/8665.md +++ b/test/command/8665.md @@ -23,7 +23,7 @@ ^D [cols=",",options="header",] |=== -|h1 |h2 -|!@#$%^&++*++()++{++}{vbar}~?{plus}-',."++<>[]\`++ |col 2 +<|h1 <|h2 +<|!@#$%^&++*++()++{++}{vbar}~?{plus}-',."++<>[]\`++ <|col 2 |=== ``` |
