parent
22babd5382
commit
a400d0dc62
6 changed files with 224 additions and 29 deletions
|
@ -288,6 +288,9 @@ extra-source-files:
|
||||||
test/tables.muse
|
test/tables.muse
|
||||||
test/tables.custom
|
test/tables.custom
|
||||||
test/tables.xwiki
|
test/tables.xwiki
|
||||||
|
test/tables/*.html4
|
||||||
|
test/tables/*.html5
|
||||||
|
test/tables/*.native
|
||||||
test/testsuite.txt
|
test/testsuite.txt
|
||||||
test/writer.latex
|
test/writer.latex
|
||||||
test/writer.context
|
test/writer.context
|
||||||
|
|
|
@ -910,7 +910,7 @@ tableToHtml :: PandocMonad m
|
||||||
=> WriterOptions
|
=> WriterOptions
|
||||||
-> Ann.Table
|
-> Ann.Table
|
||||||
-> StateT WriterState m Html
|
-> StateT WriterState m Html
|
||||||
tableToHtml opts (Ann.Table attr caption colspecs thead tbodies _tfoot) = do
|
tableToHtml opts (Ann.Table attr caption colspecs thead tbodies tfoot) = do
|
||||||
captionDoc <- case caption of
|
captionDoc <- case caption of
|
||||||
Caption _ [] -> return mempty
|
Caption _ [] -> return mempty
|
||||||
Caption _ longCapt -> do
|
Caption _ longCapt -> do
|
||||||
|
@ -921,11 +921,11 @@ tableToHtml opts (Ann.Table attr caption colspecs thead tbodies _tfoot) = do
|
||||||
coltags <- colSpecListToHtml opts colspecs
|
coltags <- colSpecListToHtml opts colspecs
|
||||||
head' <- tableHeadToHtml opts thead
|
head' <- tableHeadToHtml opts thead
|
||||||
body' <- mconcat <$> mapM (tableBodyToHtml opts) tbodies
|
body' <- mconcat <$> mapM (tableBodyToHtml opts) tbodies
|
||||||
|
foot' <- tableFootToHtml opts tfoot
|
||||||
let (ident,classes,kvs) = attr
|
let (ident,classes,kvs) = attr
|
||||||
-- When widths of columns are < 100%, we need to set width for the whole
|
-- When widths of columns are < 100%, we need to set width for the whole
|
||||||
-- table, or some browsers give us skinny columns with lots of space
|
-- table, or some browsers give us skinny columns with lots of space
|
||||||
-- between:
|
-- between:
|
||||||
-- let totalWidth = sum widths
|
|
||||||
let colWidth = \case
|
let colWidth = \case
|
||||||
ColWidth d -> d
|
ColWidth d -> d
|
||||||
ColWidthDefault -> 0
|
ColWidthDefault -> 0
|
||||||
|
@ -936,8 +936,14 @@ tableToHtml opts (Ann.Table attr caption colspecs thead tbodies _tfoot) = do
|
||||||
T.pack (show (round (totalWidth * 100) :: Int))
|
T.pack (show (round (totalWidth * 100) :: Int))
|
||||||
<> "%;"):kvs)
|
<> "%;"):kvs)
|
||||||
_ -> attr
|
_ -> attr
|
||||||
addAttrs opts attr' $ H.table $
|
addAttrs opts attr' $ H.table $ do
|
||||||
nl opts *> captionDoc *> coltags *> head' *> body' *> nl opts
|
nl opts
|
||||||
|
captionDoc
|
||||||
|
coltags
|
||||||
|
head'
|
||||||
|
body'
|
||||||
|
foot'
|
||||||
|
nl opts
|
||||||
|
|
||||||
tableBodyToHtml :: PandocMonad m
|
tableBodyToHtml :: PandocMonad m
|
||||||
=> WriterOptions
|
=> WriterOptions
|
||||||
|
@ -951,36 +957,57 @@ tableHeadToHtml :: PandocMonad m
|
||||||
-> Ann.TableHead
|
-> Ann.TableHead
|
||||||
-> StateT WriterState m Html
|
-> StateT WriterState m Html
|
||||||
tableHeadToHtml opts (Ann.TableHead attr rows) =
|
tableHeadToHtml opts (Ann.TableHead attr rows) =
|
||||||
|
tablePartToHtml opts Thead attr rows
|
||||||
|
|
||||||
|
tableFootToHtml :: PandocMonad m
|
||||||
|
=> WriterOptions
|
||||||
|
-> Ann.TableFoot
|
||||||
|
-> StateT WriterState m Html
|
||||||
|
tableFootToHtml opts (Ann.TableFoot attr rows) =
|
||||||
|
tablePartToHtml opts Tfoot attr rows
|
||||||
|
|
||||||
|
tablePartToHtml :: PandocMonad m
|
||||||
|
=> WriterOptions
|
||||||
|
-> TablePart
|
||||||
|
-> Attr
|
||||||
|
-> [Ann.HeaderRow]
|
||||||
|
-> StateT WriterState m Html
|
||||||
|
tablePartToHtml opts tblpart attr rows =
|
||||||
if null rows || all isEmptyRow rows
|
if null rows || all isEmptyRow rows
|
||||||
then return mempty
|
then return mempty
|
||||||
else do
|
else do
|
||||||
contents <- headerRowsToHtml opts rows
|
let tag' = case tblpart of
|
||||||
headElement <- addAttrs opts attr $ H.thead contents
|
Thead -> H.thead
|
||||||
|
Tfoot -> H.tfoot
|
||||||
|
Tbody -> H.tbody -- this would be unexpected
|
||||||
|
contents <- headerRowsToHtml opts tblpart rows
|
||||||
|
tablePartElement <- addAttrs opts attr $ tag' contents
|
||||||
return $ do
|
return $ do
|
||||||
headElement
|
tablePartElement
|
||||||
nl opts
|
nl opts
|
||||||
where
|
where
|
||||||
isEmptyRow (Ann.HeaderRow _attr _rownum cells) = all isEmptyCell cells
|
isEmptyRow (Ann.HeaderRow _attr _rownum cells) = all isEmptyCell cells
|
||||||
isEmptyCell (Ann.Cell _colspecs _colnum cell) =
|
isEmptyCell (Ann.Cell _colspecs _colnum cell) =
|
||||||
cell == Cell nullAttr AlignDefault (RowSpan 1) (ColSpan 1) []
|
cell == Cell nullAttr AlignDefault (RowSpan 1) (ColSpan 1) []
|
||||||
|
|
||||||
|
-- | The part of a table; header, footer, or body.
|
||||||
data RowType = HeaderRow | FooterRow | BodyRow
|
data TablePart = Thead | Tfoot | Tbody
|
||||||
deriving (Eq)
|
deriving (Eq)
|
||||||
|
|
||||||
data CellType = HeaderCell | BodyCell
|
data CellType = HeaderCell | BodyCell
|
||||||
|
|
||||||
data TableRow = TableRow RowType Attr Ann.RowNumber Ann.RowHead Ann.RowBody
|
data TableRow = TableRow TablePart Attr Ann.RowNumber Ann.RowHead Ann.RowBody
|
||||||
|
|
||||||
headerRowsToHtml :: PandocMonad m
|
headerRowsToHtml :: PandocMonad m
|
||||||
=> WriterOptions
|
=> WriterOptions
|
||||||
-> [Ann.HeaderRow]
|
-> TablePart
|
||||||
-> StateT WriterState m Html
|
-> [Ann.HeaderRow]
|
||||||
headerRowsToHtml opts =
|
-> StateT WriterState m Html
|
||||||
|
headerRowsToHtml opts tablepart =
|
||||||
rowListToHtml opts . map toTableRow
|
rowListToHtml opts . map toTableRow
|
||||||
where
|
where
|
||||||
toTableRow (Ann.HeaderRow attr rownum rowbody) =
|
toTableRow (Ann.HeaderRow attr rownum rowbody) =
|
||||||
TableRow HeaderRow attr rownum [] rowbody
|
TableRow tablepart attr rownum [] rowbody
|
||||||
|
|
||||||
bodyRowsToHtml :: PandocMonad m
|
bodyRowsToHtml :: PandocMonad m
|
||||||
=> WriterOptions
|
=> WriterOptions
|
||||||
|
@ -990,7 +1017,7 @@ bodyRowsToHtml opts =
|
||||||
rowListToHtml opts . zipWith toTableRow [1..]
|
rowListToHtml opts . zipWith toTableRow [1..]
|
||||||
where
|
where
|
||||||
toTableRow rownum (Ann.BodyRow attr _rownum rowhead rowbody) =
|
toTableRow rownum (Ann.BodyRow attr _rownum rowhead rowbody) =
|
||||||
TableRow BodyRow attr rownum rowhead rowbody
|
TableRow Tbody attr rownum rowhead rowbody
|
||||||
|
|
||||||
|
|
||||||
rowListToHtml :: PandocMonad m
|
rowListToHtml :: PandocMonad m
|
||||||
|
@ -1034,14 +1061,14 @@ tableRowToHtml :: PandocMonad m
|
||||||
=> WriterOptions
|
=> WriterOptions
|
||||||
-> TableRow
|
-> TableRow
|
||||||
-> StateT WriterState m Html
|
-> StateT WriterState m Html
|
||||||
tableRowToHtml opts (TableRow rowtype _attr rownum rowhead rowbody) = do
|
tableRowToHtml opts (TableRow tblpart _attr rownum rowhead rowbody) = do
|
||||||
let rowclass = A.class_ $ case rownum of
|
let rowclass = A.class_ $ case rownum of
|
||||||
Ann.RowNumber x | x `rem` 2 == 1 -> "odd"
|
Ann.RowNumber x | x `rem` 2 == 1 -> "odd"
|
||||||
_ | rowtype /= HeaderRow -> "even"
|
_ | tblpart /= Thead -> "even"
|
||||||
_ -> "header"
|
_ -> "header"
|
||||||
let celltype = case rowtype of
|
let celltype = case tblpart of
|
||||||
HeaderRow -> HeaderCell
|
Thead -> HeaderCell
|
||||||
_ -> BodyCell
|
_ -> BodyCell
|
||||||
head' <- mapM (cellToHtml opts HeaderCell) rowhead
|
head' <- mapM (cellToHtml opts HeaderCell) rowhead
|
||||||
body <- mapM (cellToHtml opts celltype) rowbody
|
body <- mapM (cellToHtml opts celltype) rowbody
|
||||||
return $ do
|
return $ do
|
||||||
|
|
|
@ -267,12 +267,13 @@ writerTests pandocPath format
|
||||||
extendedWriterTests :: FilePath -> String -> [TestTree]
|
extendedWriterTests :: FilePath -> String -> [TestTree]
|
||||||
extendedWriterTests pandocPath format
|
extendedWriterTests pandocPath format
|
||||||
= writerTests pandocPath format ++
|
= writerTests pandocPath format ++
|
||||||
[ test pandocPath
|
let testForTable name =
|
||||||
"tables"
|
test pandocPath
|
||||||
opts
|
(name ++ " table")
|
||||||
("tables" </> "planets.native")
|
opts
|
||||||
("tables" </> "planets" <.> format)
|
("tables" </> name <.> "native")
|
||||||
]
|
("tables" </> name <.> format)
|
||||||
|
in map testForTable ["planets", "nordics"]
|
||||||
where
|
where
|
||||||
opts = ["-r", "native", "-w", format, "--columns=78",
|
opts = ["-r", "native", "-w", format, "--columns=78",
|
||||||
"--variable", "pandoc-version="]
|
"--variable", "pandoc-version="]
|
||||||
|
|
59
test/tables/nordics.html4
Normal file
59
test/tables/nordics.html4
Normal file
|
@ -0,0 +1,59 @@
|
||||||
|
<table>
|
||||||
|
<caption><p>States belonging to the <em>Nordics.</em></p></caption>
|
||||||
|
<colgroup>
|
||||||
|
<col width="30%" />
|
||||||
|
<col width="30%" />
|
||||||
|
<col width="20%" />
|
||||||
|
<col width="20%" />
|
||||||
|
</colgroup>
|
||||||
|
<thead>
|
||||||
|
<tr class="header">
|
||||||
|
<th align="center">Name</th>
|
||||||
|
<th align="center">Capital</th>
|
||||||
|
<th align="center">Population<br />
|
||||||
|
(in 2018)</th>
|
||||||
|
<th align="center">Area<br />
|
||||||
|
(in km<sup>2</sup>)</th>
|
||||||
|
</tr>
|
||||||
|
</thead>
|
||||||
|
<tbody>
|
||||||
|
<tr class="odd">
|
||||||
|
<th align="center">Denmark</th>
|
||||||
|
<td align="left">Copenhagen</td>
|
||||||
|
<td align="left">5,809,502</td>
|
||||||
|
<td align="left">43,094</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="even">
|
||||||
|
<th align="center">Finland</th>
|
||||||
|
<td align="left">Helsinki</td>
|
||||||
|
<td align="left">5,537,364</td>
|
||||||
|
<td align="left">338,145</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="odd">
|
||||||
|
<th align="center">Iceland</th>
|
||||||
|
<td align="left">Reykjavik</td>
|
||||||
|
<td align="left">343,518</td>
|
||||||
|
<td align="left">103,000</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="even">
|
||||||
|
<th align="center">Norway</th>
|
||||||
|
<td align="left">Oslo</td>
|
||||||
|
<td align="left">5,372,191</td>
|
||||||
|
<td align="left">323,802</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="odd">
|
||||||
|
<th align="center">Sweden</th>
|
||||||
|
<td align="left">Stockholm</td>
|
||||||
|
<td align="left">10,313,447</td>
|
||||||
|
<td align="left">450,295</td>
|
||||||
|
</tr>
|
||||||
|
</tbody><tfoot>
|
||||||
|
<tr class="even">
|
||||||
|
<td align="center">Total</td>
|
||||||
|
<td align="left"></td>
|
||||||
|
<td align="left">27,376,022</td>
|
||||||
|
<td align="left">1,258,336</td>
|
||||||
|
</tr>
|
||||||
|
</tfoot>
|
||||||
|
|
||||||
|
</table>
|
59
test/tables/nordics.html5
Normal file
59
test/tables/nordics.html5
Normal file
|
@ -0,0 +1,59 @@
|
||||||
|
<table>
|
||||||
|
<caption><p>States belonging to the <em>Nordics.</em></p></caption>
|
||||||
|
<colgroup>
|
||||||
|
<col style="width: 30%" />
|
||||||
|
<col style="width: 30%" />
|
||||||
|
<col style="width: 20%" />
|
||||||
|
<col style="width: 20%" />
|
||||||
|
</colgroup>
|
||||||
|
<thead>
|
||||||
|
<tr class="header">
|
||||||
|
<th style="text-align: center;">Name</th>
|
||||||
|
<th style="text-align: center;">Capital</th>
|
||||||
|
<th style="text-align: center;">Population<br />
|
||||||
|
(in 2018)</th>
|
||||||
|
<th style="text-align: center;">Area<br />
|
||||||
|
(in km<sup>2</sup>)</th>
|
||||||
|
</tr>
|
||||||
|
</thead>
|
||||||
|
<tbody>
|
||||||
|
<tr class="odd">
|
||||||
|
<th style="text-align: center;">Denmark</th>
|
||||||
|
<td style="text-align: left;">Copenhagen</td>
|
||||||
|
<td style="text-align: left;">5,809,502</td>
|
||||||
|
<td style="text-align: left;">43,094</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="even">
|
||||||
|
<th style="text-align: center;">Finland</th>
|
||||||
|
<td style="text-align: left;">Helsinki</td>
|
||||||
|
<td style="text-align: left;">5,537,364</td>
|
||||||
|
<td style="text-align: left;">338,145</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="odd">
|
||||||
|
<th style="text-align: center;">Iceland</th>
|
||||||
|
<td style="text-align: left;">Reykjavik</td>
|
||||||
|
<td style="text-align: left;">343,518</td>
|
||||||
|
<td style="text-align: left;">103,000</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="even">
|
||||||
|
<th style="text-align: center;">Norway</th>
|
||||||
|
<td style="text-align: left;">Oslo</td>
|
||||||
|
<td style="text-align: left;">5,372,191</td>
|
||||||
|
<td style="text-align: left;">323,802</td>
|
||||||
|
</tr>
|
||||||
|
<tr class="odd">
|
||||||
|
<th style="text-align: center;">Sweden</th>
|
||||||
|
<td style="text-align: left;">Stockholm</td>
|
||||||
|
<td style="text-align: left;">10,313,447</td>
|
||||||
|
<td style="text-align: left;">450,295</td>
|
||||||
|
</tr>
|
||||||
|
</tbody><tfoot>
|
||||||
|
<tr class="even">
|
||||||
|
<td style="text-align: center;">Total</td>
|
||||||
|
<td style="text-align: left;"></td>
|
||||||
|
<td style="text-align: left;">27,376,022</td>
|
||||||
|
<td style="text-align: left;">1,258,336</td>
|
||||||
|
</tr>
|
||||||
|
</tfoot>
|
||||||
|
|
||||||
|
</table>
|
46
test/tables/nordics.native
Normal file
46
test/tables/nordics.native
Normal file
|
@ -0,0 +1,46 @@
|
||||||
|
[Table ("",[],[]) (Caption (Just [Str "Nordic countries"])
|
||||||
|
[Para [Str "States", Space, Str "belonging", Space, Str "to", Space, Str "the", Space, Emph [Str "Nordics."]]])
|
||||||
|
[(AlignCenter,ColWidth 0.3)
|
||||||
|
,(AlignLeft,ColWidth 0.3)
|
||||||
|
,(AlignLeft,ColWidth 0.2)
|
||||||
|
,(AlignLeft,ColWidth 0.2)]
|
||||||
|
(TableHead ("",[],[])
|
||||||
|
[Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1) [Plain [Str "Name"]]
|
||||||
|
,Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1) [Plain [Str "Capital"]]
|
||||||
|
,Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1) [Plain [Str "Population", LineBreak, Str "(in", Space, Str "2018)"]]
|
||||||
|
,Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1) [Plain [Str "Area", LineBreak, Str "(in", Space, Str "km", Superscript [Str "2"], Str ")"]]]])
|
||||||
|
[(TableBody ("",[],[]) (RowHeadColumns 1)
|
||||||
|
[]
|
||||||
|
[Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Denmark"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Copenhagen"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "5,809,502"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "43,094"]]]
|
||||||
|
,Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Finland"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Helsinki"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "5,537,364"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "338,145"]]]
|
||||||
|
,Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Iceland"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Reykjavik"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "343,518"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "103,000"]]]
|
||||||
|
,Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Norway"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Oslo"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "5,372,191"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "323,802"]]]
|
||||||
|
,Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Sweden"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Stockholm"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "10,313,447"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "450,295"]]]])]
|
||||||
|
(TableFoot ("",[],[])
|
||||||
|
[Row ("",[],[])
|
||||||
|
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "Total"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) []
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "27,376,022"]]
|
||||||
|
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "1,258,336"]]]])
|
||||||
|
]
|
Loading…
Add table
Reference in a new issue