ConTeXt writer: support complex table structures. (#8116)
The following table feature are now supported in ConTeXt: - colspans, - rowspans, - multiple bodies, - row headers, and - multi-row table head and foot. The wrapping `placetable` environment is also given a `reference` option with the table identifier, enabling referencing of the table from within the document.
This commit is contained in:
parent
ab712246f0
commit
f49bee5c31
6 changed files with 303 additions and 116 deletions
|
@ -109,9 +109,10 @@ $endif$
|
|||
\setupfloat[table][default={here,nonumber}]
|
||||
|
||||
\setupxtable[frame=off]
|
||||
\setupxtable[head][topframe=on,bottomframe=on]
|
||||
\setupxtable[head][topframe=on]
|
||||
\setupxtable[body][]
|
||||
\setupxtable[foot][bottomframe=on]
|
||||
\setupxtable[foot][]
|
||||
\setupxtable[lastrow][bottomframe=on]
|
||||
|
||||
$if(csl-refs)$
|
||||
\definemeasure[cslhangindent][1.5em]
|
||||
|
|
|
@ -17,7 +17,8 @@ module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where
|
|||
import Control.Monad.State.Strict
|
||||
import Data.Char (ord, isDigit)
|
||||
import Data.List (intersperse)
|
||||
import Data.Maybe (mapMaybe)
|
||||
import Data.List.NonEmpty (NonEmpty ((:|)))
|
||||
import Data.Maybe (mapMaybe, catMaybes)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Network.URI (unEscapeString)
|
||||
|
@ -34,6 +35,9 @@ import Text.Pandoc.Walk (query)
|
|||
import Text.Pandoc.Writers.Shared
|
||||
import Text.Printf (printf)
|
||||
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
|
||||
|
||||
data WriterState =
|
||||
WriterState { stNextRef :: Int -- number of next URL reference
|
||||
, stOrderedListLevel :: Int -- level of ordered list
|
||||
|
@ -258,81 +262,225 @@ blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
|
|||
-- If this is ever executed, provide a default for the reference identifier.
|
||||
blockToConTeXt (Header level attr lst) =
|
||||
sectionHeader attr level lst NonSectionHeading
|
||||
blockToConTeXt (Table _ blkCapt specs thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
opts <- gets stOptions
|
||||
let tabl = if isEnabled Ext_ntb opts
|
||||
then Ntb
|
||||
else Xtb
|
||||
captionText <- inlineListToConTeXt caption
|
||||
headers <- if all null heads
|
||||
then return empty
|
||||
else tableRowToConTeXt tabl aligns widths heads
|
||||
rows' <- mapM (tableRowToConTeXt tabl aligns widths) rows
|
||||
body <- tableToConTeXt tabl headers rows'
|
||||
return $ "\\startplacetable" <> brackets (
|
||||
if null caption
|
||||
then "location=none"
|
||||
else "title=" <> braces captionText
|
||||
) $$ body $$ "\\stopplacetable" <> blankline
|
||||
blockToConTeXt (Table attr caption colspecs thead tbody tfoot) =
|
||||
tableToConTeXt (Ann.toTable attr caption colspecs thead tbody tfoot)
|
||||
|
||||
tableToConTeXt :: PandocMonad m
|
||||
=> Tabl -> Doc Text -> [Doc Text] -> WM m (Doc Text)
|
||||
tableToConTeXt Xtb heads rows =
|
||||
return $ "\\startxtable" $$
|
||||
(if isEmpty heads
|
||||
then empty
|
||||
else "\\startxtablehead[head]" $$ heads $$ "\\stopxtablehead") $$
|
||||
(if null rows
|
||||
then empty
|
||||
else "\\startxtablebody[body]" $$ vcat (init rows) $$ "\\stopxtablebody" $$
|
||||
"\\startxtablefoot[foot]" $$ last rows $$ "\\stopxtablefoot") $$
|
||||
"\\stopxtable"
|
||||
tableToConTeXt Ntb heads rows =
|
||||
return $ "\\startTABLE" $$
|
||||
(if isEmpty heads
|
||||
then empty
|
||||
else "\\startTABLEhead" $$ heads $$ "\\stopTABLEhead") $$
|
||||
(if null rows
|
||||
then empty
|
||||
else "\\startTABLEbody" $$ vcat (init rows) $$ "\\stopTABLEbody" $$
|
||||
"\\startTABLEfoot" $$ last rows $$ "\\stopTABLEfoot") $$
|
||||
"\\stopTABLE"
|
||||
tableToConTeXt :: PandocMonad m => Ann.Table -> WM m (Doc Text)
|
||||
tableToConTeXt (Ann.Table attr caption colspecs thead tbodies tfoot) = do
|
||||
opts <- gets stOptions
|
||||
let tabl = if isEnabled Ext_ntb opts
|
||||
then Ntb
|
||||
else Xtb
|
||||
captionText <- case caption of
|
||||
Caption _ [] -> return mempty
|
||||
Caption _ longCapt -> blockListToConTeXt longCapt
|
||||
head' <- tableHeadToConTeXt tabl thead
|
||||
bodies <- mapM (tableBodyToConTeXt tabl) tbodies
|
||||
foot' <- tableFootToConTeXt tabl tfoot
|
||||
let body = case tabl of
|
||||
Xtb -> "\\startxtable" $$
|
||||
head' $$
|
||||
"\\startxtablebody[body]" $$
|
||||
vcat bodies $$
|
||||
"\\stopxtablebody" $$
|
||||
foot' $$
|
||||
"\\stopxtable"
|
||||
Ntb -> setupCols colspecs $$
|
||||
"\\bTABLE" $$
|
||||
head' $$
|
||||
"\\bTABLEbody" $$
|
||||
vcat bodies $$
|
||||
"\\eTABLEbody" $$
|
||||
foot' $$
|
||||
"\\eTABLE"
|
||||
let (ident, _classes, _attribs) = attr
|
||||
let tblopts = filter (not . isEmpty)
|
||||
[ if isEmpty captionText
|
||||
then "location=none"
|
||||
else "title=" <> braces captionText
|
||||
, if T.null ident
|
||||
then empty
|
||||
else "reference=" <> braces (literal (toLabel ident))
|
||||
]
|
||||
return $ vcat
|
||||
[ "\\startplacetable" <> brackets (mconcat $ intersperse "," tblopts)
|
||||
, body
|
||||
, "\\stopplacetable" <> blankline
|
||||
]
|
||||
|
||||
tableRowToConTeXt :: PandocMonad m => Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
|
||||
tableRowToConTeXt Xtb aligns widths cols = do
|
||||
cells <- mapM (tableColToConTeXt Xtb) $ zip3 aligns widths cols
|
||||
return $ "\\startxrow" $$ vcat cells $$ "\\stopxrow"
|
||||
tableRowToConTeXt Ntb aligns widths cols = do
|
||||
cells <- mapM (tableColToConTeXt Ntb) $ zip3 aligns widths cols
|
||||
return $ vcat cells $$ "\\NC\\NR"
|
||||
setupCols :: [ColSpec] -> Doc Text
|
||||
setupCols = vcat . map toColSetup . zip [1::Int ..]
|
||||
where
|
||||
toColSetup (i, (align, width)) =
|
||||
let opts = filter (not . isEmpty)
|
||||
[ case align of
|
||||
AlignLeft -> "align=right"
|
||||
AlignRight -> "align=left"
|
||||
AlignCenter -> "align=middle"
|
||||
AlignDefault -> "align=left"
|
||||
, case width of
|
||||
ColWidthDefault -> empty
|
||||
ColWidth w -> ("width=" <>) . braces . text $
|
||||
printf "%.2f\\textwidth" w
|
||||
]
|
||||
in "\\setupTABLE[column]" <> brackets (text $ show i)
|
||||
<> brackets (mconcat $ intersperse "," opts)
|
||||
|
||||
tableColToConTeXt :: PandocMonad m => Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
|
||||
tableColToConTeXt tabl (align, width, blocks) = do
|
||||
cellContents <- blockListToConTeXt blocks
|
||||
let colwidth = if width == 0
|
||||
then empty
|
||||
else "width=" <> braces (text (printf "%.2f\\textwidth" width))
|
||||
let halign = alignToConTeXt align
|
||||
tableBodyToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> Ann.TableBody
|
||||
-> WM m (Doc Text)
|
||||
tableBodyToConTeXt tabl (Ann.TableBody _attr _rowHeadCols inthead rows) = do
|
||||
intermediateHead <-
|
||||
if null inthead
|
||||
then return mempty
|
||||
else headerRowsToConTeXt tabl Thead inthead
|
||||
bodyRows <- bodyRowsToConTeXt tabl rows
|
||||
return $ intermediateHead <> bodyRows
|
||||
|
||||
tableHeadToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> Ann.TableHead
|
||||
-> WM m (Doc Text)
|
||||
tableHeadToConTeXt tabl (Ann.TableHead attr rows) =
|
||||
tablePartToConTeXt tabl Thead attr rows
|
||||
|
||||
tableFootToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> Ann.TableFoot
|
||||
-> WM m (Doc Text)
|
||||
tableFootToConTeXt tbl (Ann.TableFoot attr rows) =
|
||||
tablePartToConTeXt tbl Tfoot attr rows
|
||||
|
||||
tablePartToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> TablePart
|
||||
-> Attr
|
||||
-> [Ann.HeaderRow]
|
||||
-> WM m (Doc Text)
|
||||
tablePartToConTeXt tabl tblpart _attr rows = do
|
||||
let (startCmd, stopCmd) = case (tabl, tblpart) of
|
||||
(Ntb, Thead) -> ("\\bTABLEhead", "\\eTABLEhead")
|
||||
(Ntb, Tfoot) -> ("\\bTABLEfoot", "\\eTABLEfoot")
|
||||
(Xtb, Thead) -> ("\\startxtablehead[head]", "\\stopxtablehead")
|
||||
(Xtb, Tfoot) -> ("\\startxtablefoot[foot]", "\\stopxtablefoot")
|
||||
_ -> ("", "") -- this would be unexpected
|
||||
contents <- headerRowsToConTeXt tabl tblpart rows
|
||||
return $ startCmd $$ contents $$ stopCmd
|
||||
|
||||
-- | The part of a table; header, footer, or body.
|
||||
data TablePart = Thead | Tfoot | Tbody
|
||||
deriving (Eq)
|
||||
|
||||
data CellType = HeaderCell | BodyCell
|
||||
|
||||
data TableRow = TableRow TablePart Attr Ann.RowHead Ann.RowBody
|
||||
|
||||
headerRowsToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> TablePart
|
||||
-> [Ann.HeaderRow]
|
||||
-> WM m (Doc Text)
|
||||
headerRowsToConTeXt tabl tablepart = rowListToConTeXt tabl . map toTableRow
|
||||
where
|
||||
toTableRow (Ann.HeaderRow attr _rownum rowbody) =
|
||||
TableRow tablepart attr [] rowbody
|
||||
|
||||
bodyRowsToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> [Ann.BodyRow]
|
||||
-> WM m (Doc Text)
|
||||
bodyRowsToConTeXt tabl = rowListToConTeXt tabl . map toTableRow
|
||||
where
|
||||
toTableRow (Ann.BodyRow attr _rownum rowhead rowbody) =
|
||||
TableRow Tbody attr rowhead rowbody
|
||||
|
||||
|
||||
rowListToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> [TableRow]
|
||||
-> WM m (Doc Text)
|
||||
rowListToConTeXt = \case
|
||||
Ntb -> fmap vcat . mapM (tableRowToConTeXt Ntb)
|
||||
Xtb -> \rows -> do
|
||||
(butlast, lastrow) <-
|
||||
case reverse rows of
|
||||
[] -> pure ( []
|
||||
, empty
|
||||
)
|
||||
r:rs -> (,) <$> (mapM (tableRowToConTeXt Xtb) (reverse rs))
|
||||
<*> tableRowToConTeXt Xtb r
|
||||
return $
|
||||
vcat butlast $$
|
||||
if isEmpty lastrow
|
||||
then empty
|
||||
else "\\startxrowgroup[lastrow]" $$ lastrow $$ "\\stopxrowgroup"
|
||||
|
||||
tableRowToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> TableRow
|
||||
-> WM m (Doc Text)
|
||||
tableRowToConTeXt tabl (TableRow tblpart _attr rowhead rowbody) = do
|
||||
let celltype = case tblpart of
|
||||
Thead -> HeaderCell
|
||||
_ -> BodyCell
|
||||
headcells <- mapM (tableCellToConTeXt tabl HeaderCell) rowhead
|
||||
bodycells <- mapM (tableCellToConTeXt tabl celltype) rowbody
|
||||
let cells = vcat headcells $$ vcat bodycells
|
||||
return $ case tabl of
|
||||
Xtb -> "\\startxrow" $$ cells $$ "\\stopxrow"
|
||||
Ntb -> "\\bTR" $$ cells $$ "\\eTR"
|
||||
|
||||
tableCellToConTeXt :: PandocMonad m
|
||||
=> Tabl
|
||||
-> CellType
|
||||
-> Ann.Cell -> WM m (Doc Text)
|
||||
tableCellToConTeXt tabl celltype (Ann.Cell colspecs _colnum cell) = do
|
||||
let Cell _attr cellalign rowspan colspan blocks = cell
|
||||
let (colalign, _) :| _ = colspecs
|
||||
let halign = alignToConTeXt $
|
||||
case (cellalign, tabl) of
|
||||
(AlignDefault, Xtb) -> colalign
|
||||
_ -> cellalign
|
||||
let nx = case colspan of
|
||||
ColSpan 1 -> empty
|
||||
ColSpan n -> "nc=" <> literal (tshow n)
|
||||
let ny = case rowspan of
|
||||
RowSpan 1 -> empty
|
||||
RowSpan n -> "nr=" <> literal (tshow n)
|
||||
let widths = map snd (NonEmpty.toList colspecs)
|
||||
let mbcolwidth = flip map widths $ \case
|
||||
ColWidthDefault -> Nothing
|
||||
ColWidth w -> Just w
|
||||
let colwidth = case catMaybes mbcolwidth of
|
||||
[] -> empty
|
||||
ws -> ("width=" <>) . braces . text $
|
||||
printf "%.2f\\textwidth" (sum ws)
|
||||
let keys = hcat . intersperse "," $ filter (not . isEmpty) $
|
||||
case tabl of
|
||||
Xtb -> [halign, colwidth, nx, ny]
|
||||
Ntb -> [halign, nx, ny] -- no need for a column width
|
||||
let options = (if isEmpty keys
|
||||
then empty
|
||||
else brackets keys) <> space
|
||||
where keys = hcat $ intersperse "," $ filter (not . isEmpty) [halign, colwidth]
|
||||
tableCellToConTeXt tabl options cellContents
|
||||
|
||||
tableCellToConTeXt :: PandocMonad m
|
||||
=> Tabl -> Doc Text -> Doc Text -> WM m (Doc Text)
|
||||
tableCellToConTeXt Xtb options cellContents =
|
||||
return $ "\\startxcell" <> options <> cellContents <> " \\stopxcell"
|
||||
tableCellToConTeXt Ntb options cellContents =
|
||||
return $ "\\NC" <> options <> cellContents
|
||||
cellContents <- blockListToConTeXt blocks
|
||||
return $ case tabl of
|
||||
Xtb -> "\\startxcell" <> options <> cellContents <> " \\stopxcell"
|
||||
Ntb -> case celltype of
|
||||
BodyCell -> "\\bTD" <> options <> cellContents <> "\\eTD"
|
||||
HeaderCell -> "\\bTH" <> options <> cellContents <> "\\eTH"
|
||||
|
||||
alignToConTeXt :: Alignment -> Doc Text
|
||||
alignToConTeXt align = case align of
|
||||
AlignLeft -> "align=right"
|
||||
AlignRight -> "align=left"
|
||||
AlignCenter -> "align=middle"
|
||||
AlignDefault -> empty
|
||||
alignToConTeXt = \case
|
||||
AlignLeft -> "align=right"
|
||||
AlignRight -> "align=left"
|
||||
AlignCenter -> "align=middle"
|
||||
AlignDefault -> empty
|
||||
|
||||
|
||||
---
|
||||
--- Lists
|
||||
--
|
||||
|
||||
listItemToConTeXt :: PandocMonad m => [Block] -> WM m (Doc Text)
|
||||
listItemToConTeXt list = ("\\item" $$) . nest 2 <$> blockListToConTeXt list
|
||||
|
|
|
@ -135,34 +135,42 @@ tests =
|
|||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
=?> unlines [ "\\startplacetable[title={Table 1}]"
|
||||
, "\\startTABLE"
|
||||
, "\\startTABLEhead"
|
||||
, "\\NC[align=left] Right"
|
||||
, "\\NC[align=right] Left"
|
||||
, "\\NC[align=middle] Center"
|
||||
, "\\NC Default"
|
||||
, "\\NC\\NR"
|
||||
, "\\stopTABLEhead"
|
||||
, "\\startTABLEbody"
|
||||
, "\\NC[align=left] 1.1"
|
||||
, "\\NC[align=right] 1.2"
|
||||
, "\\NC[align=middle] 1.3"
|
||||
, "\\NC 1.4"
|
||||
, "\\NC\\NR"
|
||||
, "\\NC[align=left] 2.1"
|
||||
, "\\NC[align=right] 2.2"
|
||||
, "\\NC[align=middle] 2.3"
|
||||
, "\\NC 2.4"
|
||||
, "\\NC\\NR"
|
||||
, "\\stopTABLEbody"
|
||||
, "\\startTABLEfoot"
|
||||
, "\\NC[align=left] 3.1"
|
||||
, "\\NC[align=right] 3.2"
|
||||
, "\\NC[align=middle] 3.3"
|
||||
, "\\NC 3.4"
|
||||
, "\\NC\\NR"
|
||||
, "\\stopTABLEfoot"
|
||||
, "\\stopTABLE"
|
||||
, "\\setupTABLE[column][1][align=left]"
|
||||
, "\\setupTABLE[column][2][align=right]"
|
||||
, "\\setupTABLE[column][3][align=middle]"
|
||||
, "\\setupTABLE[column][4][align=left]"
|
||||
, "\\bTABLE"
|
||||
, "\\bTABLEhead"
|
||||
, "\\bTR"
|
||||
, "\\bTH Right\\eTH"
|
||||
, "\\bTH Left\\eTH"
|
||||
, "\\bTH Center\\eTH"
|
||||
, "\\bTH Default\\eTH"
|
||||
, "\\eTR"
|
||||
, "\\eTABLEhead"
|
||||
, "\\bTABLEbody"
|
||||
, "\\bTR"
|
||||
, "\\bTD 1.1\\eTD"
|
||||
, "\\bTD 1.2\\eTD"
|
||||
, "\\bTD 1.3\\eTD"
|
||||
, "\\bTD 1.4\\eTD"
|
||||
, "\\eTR"
|
||||
, "\\bTR"
|
||||
, "\\bTD 2.1\\eTD"
|
||||
, "\\bTD 2.2\\eTD"
|
||||
, "\\bTD 2.3\\eTD"
|
||||
, "\\bTD 2.4\\eTD"
|
||||
, "\\eTR"
|
||||
, "\\bTR"
|
||||
, "\\bTD 3.1\\eTD"
|
||||
, "\\bTD 3.2\\eTD"
|
||||
, "\\bTD 3.3\\eTD"
|
||||
, "\\bTD 3.4\\eTD"
|
||||
, "\\eTR"
|
||||
, "\\eTABLEbody"
|
||||
, "\\bTABLEfoot"
|
||||
, "\\eTABLEfoot"
|
||||
, "\\eTABLE"
|
||||
, "\\stopplacetable" ]
|
||||
]
|
||||
]
|
||||
|
|
|
@ -3,12 +3,14 @@ Simple table with caption:
|
|||
\startplacetable[title={Demonstration of simple table syntax.}]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] Right \stopxcell
|
||||
\startxcell[align=right] Left \stopxcell
|
||||
\startxcell[align=middle] Center \stopxcell
|
||||
\startxcell Default \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
|
@ -23,14 +25,16 @@ Simple table with caption:
|
|||
\startxcell[align=middle] 123 \stopxcell
|
||||
\startxcell 123 \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] 1 \stopxcell
|
||||
\startxcell[align=right] 1 \stopxcell
|
||||
\startxcell[align=middle] 1 \stopxcell
|
||||
\startxcell 1 \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
@ -40,12 +44,14 @@ Simple table without caption:
|
|||
\startplacetable[location=none]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] Right \stopxcell
|
||||
\startxcell[align=right] Left \stopxcell
|
||||
\startxcell[align=middle] Center \stopxcell
|
||||
\startxcell Default \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
|
@ -60,14 +66,16 @@ Simple table without caption:
|
|||
\startxcell[align=middle] 123 \stopxcell
|
||||
\startxcell 123 \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] 1 \stopxcell
|
||||
\startxcell[align=right] 1 \stopxcell
|
||||
\startxcell[align=middle] 1 \stopxcell
|
||||
\startxcell 1 \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
@ -77,12 +85,14 @@ Simple table indented two spaces:
|
|||
\startplacetable[title={Demonstration of simple table syntax.}]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] Right \stopxcell
|
||||
\startxcell[align=right] Left \stopxcell
|
||||
\startxcell[align=middle] Center \stopxcell
|
||||
\startxcell Default \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
|
@ -97,14 +107,16 @@ Simple table indented two spaces:
|
|||
\startxcell[align=middle] 123 \stopxcell
|
||||
\startxcell 123 \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] 1 \stopxcell
|
||||
\startxcell[align=right] 1 \stopxcell
|
||||
\startxcell[align=middle] 1 \stopxcell
|
||||
\startxcell 1 \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
@ -114,12 +126,14 @@ Multiline table with caption:
|
|||
\startplacetable[title={Here's the caption. It may span multiple lines.}]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=middle,width={0.15\textwidth}] Centered Header \stopxcell
|
||||
\startxcell[align=right,width={0.14\textwidth}] Left Aligned \stopxcell
|
||||
\startxcell[align=left,width={0.16\textwidth}] Right Aligned \stopxcell
|
||||
\startxcell[align=right,width={0.35\textwidth}] Default aligned \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
|
@ -129,8 +143,7 @@ Multiline table with caption:
|
|||
\startxcell[align=right,width={0.35\textwidth}] Example of a row that spans
|
||||
multiple lines. \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell
|
||||
\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
|
||||
|
@ -138,6 +151,9 @@ multiple lines. \stopxcell
|
|||
\startxcell[align=right,width={0.35\textwidth}] Here's another one. Note the
|
||||
blank line between rows. \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
@ -147,12 +163,14 @@ Multiline table without caption:
|
|||
\startplacetable[location=none]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=middle,width={0.15\textwidth}] Centered Header \stopxcell
|
||||
\startxcell[align=right,width={0.14\textwidth}] Left Aligned \stopxcell
|
||||
\startxcell[align=left,width={0.16\textwidth}] Right Aligned \stopxcell
|
||||
\startxcell[align=right,width={0.35\textwidth}] Default aligned \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
|
@ -162,8 +180,7 @@ Multiline table without caption:
|
|||
\startxcell[align=right,width={0.35\textwidth}] Example of a row that spans
|
||||
multiple lines. \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell
|
||||
\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
|
||||
|
@ -171,6 +188,9 @@ multiple lines. \stopxcell
|
|||
\startxcell[align=right,width={0.35\textwidth}] Here's another one. Note the
|
||||
blank line between rows. \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
@ -179,6 +199,8 @@ Table without column headers:
|
|||
|
||||
\startplacetable[location=none]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
\startxcell[align=left] 12 \stopxcell
|
||||
|
@ -192,14 +214,16 @@ Table without column headers:
|
|||
\startxcell[align=middle] 123 \stopxcell
|
||||
\startxcell[align=left] 123 \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=left] 1 \stopxcell
|
||||
\startxcell[align=right] 1 \stopxcell
|
||||
\startxcell[align=middle] 1 \stopxcell
|
||||
\startxcell[align=left] 1 \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
@ -208,6 +232,8 @@ Multiline table without column headers:
|
|||
|
||||
\startplacetable[location=none]
|
||||
\startxtable
|
||||
\startxtablehead[head]
|
||||
\stopxtablehead
|
||||
\startxtablebody[body]
|
||||
\startxrow
|
||||
\startxcell[align=middle,width={0.15\textwidth}] First \stopxcell
|
||||
|
@ -216,8 +242,7 @@ Multiline table without column headers:
|
|||
\startxcell[width={0.35\textwidth}] Example of a row that spans multiple
|
||||
lines. \stopxcell
|
||||
\stopxrow
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\startxrowgroup[lastrow]
|
||||
\startxrow
|
||||
\startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell
|
||||
\startxcell[align=right,width={0.14\textwidth}] row \stopxcell
|
||||
|
@ -225,6 +250,9 @@ lines. \stopxcell
|
|||
\startxcell[width={0.35\textwidth}] Here's another one. Note the blank line
|
||||
between rows. \stopxcell
|
||||
\stopxrow
|
||||
\stopxrowgroup
|
||||
\stopxtablebody
|
||||
\startxtablefoot[foot]
|
||||
\stopxtablefoot
|
||||
\stopxtable
|
||||
\stopplacetable
|
||||
|
|
|
@ -60,9 +60,10 @@
|
|||
\setupfloat[table][default={here,nonumber}]
|
||||
|
||||
\setupxtable[frame=off]
|
||||
\setupxtable[head][topframe=on,bottomframe=on]
|
||||
\setupxtable[head][topframe=on]
|
||||
\setupxtable[body][]
|
||||
\setupxtable[foot][bottomframe=on]
|
||||
\setupxtable[foot][]
|
||||
\setupxtable[lastrow][bottomframe=on]
|
||||
|
||||
|
||||
\starttext
|
||||
|
|
|
@ -58,9 +58,10 @@
|
|||
\setupfloat[table][default={here,nonumber}]
|
||||
|
||||
\setupxtable[frame=off]
|
||||
\setupxtable[head][topframe=on,bottomframe=on]
|
||||
\setupxtable[head][topframe=on]
|
||||
\setupxtable[body][]
|
||||
\setupxtable[foot][bottomframe=on]
|
||||
\setupxtable[foot][]
|
||||
\setupxtable[lastrow][bottomframe=on]
|
||||
|
||||
|
||||
\starttext
|
||||
|
|
Loading…
Reference in a new issue