aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Shared.hs
diff options
context:
space:
mode:
authordespresc <christian.j.j.despres@gmail.com>2020-04-04 16:35:42 -0400
committerdespresc <christian.j.j.despres@gmail.com>2020-04-15 23:03:22 -0400
commit4e34d366df31937cdc69b6b366355f10a84c16b2 (patch)
tree844503b0f59439acaec5d2f8e2f016e2eb1d214c /src/Text/Pandoc/Shared.hs
parentf8ce38975b547fe7fc8c12ccee3a940b35d8b9cf (diff)
downloadpandoc-4e34d366df31937cdc69b6b366355f10a84c16b2.tar.gz
Adapt to the newest Table type, fix some previous adaptation issues
- Writers.Native is now adapted to the new Table type. - Inline captions should now be conditionally wrapped in a Plain, not a Para block. - The toLegacyTable function now lives in Writers.Shared.
Diffstat (limited to 'src/Text/Pandoc/Shared.hs')
-rw-r--r--src/Text/Pandoc/Shared.hs31
1 files changed, 4 insertions, 27 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 0418aa6e2..4a60866af 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -77,7 +77,6 @@ module Text.Pandoc.Shared (
htmlSpanLikeElements,
splitSentences,
filterIpynbOutput,
- toLegacyTable,
-- * TagSoup HTML handling
renderTags',
-- * File handling
@@ -993,12 +992,14 @@ blockToInlines (DefinitionList pairslst) =
mconcat (map blocksToInlines' blkslst)
blockToInlines (Header _ _ ils) = B.fromList ils
blockToInlines HorizontalRule = mempty
-blockToInlines (Table _ _ _ _ headers rows feet) =
+blockToInlines (Table _ _ _ (TableHead _ hbd) bodies (TableFoot _ fbd)) =
mconcat $ intersperse B.linebreak $
- map (mconcat . map blocksToInlines') (plainRowBody <$> headers <> rows <> feet)
+ map (mconcat . map blocksToInlines') (plainRowBody <$> hbd <> unTableBodies bodies <> fbd)
where
plainRowBody (Row _ body) = cellBody <$> body
cellBody (Cell _ _ _ _ body) = body
+ unTableBody (TableBody _ _ hd bd) = hd <> bd
+ unTableBodies = concatMap unTableBody
blockToInlines (Div _ blks) = blocksToInlines' blks
blockToInlines Null = mempty
@@ -1012,30 +1013,6 @@ blocksToInlines' = blocksToInlinesWithSep defaultBlocksSeparator
blocksToInlines :: [Block] -> [Inline]
blocksToInlines = B.toList . blocksToInlines'
--- | Convert the relevant components of a new-style table (with block
--- caption, row headers, row and column spans, and so on) to those of
--- an old-style table (inline caption, table head with one row, no
--- foot, and so on).
-toLegacyTable :: Caption
- -> [ColSpec]
- -> TableHead
- -> TableBody
- -> TableFoot
- -> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
-toLegacyTable (Caption _ cbody) specs th tb tf = (cbody', aligns, widths, th', tb')
- where
- numcols = length specs
- (aligns, mwidths) = unzip specs
- widths = map (fromMaybe 0) mwidths
- unRow (Row _ x) = map unCell x
- unCell (Cell _ _ _ _ x) = x
- cbody' = blocksToInlines cbody
- sanitise = pad mempty numcols . unRow
- pad element upTo list = take upTo (list ++ repeat element)
- (th', tb') = case th of
- (r:rs) -> (sanitise r, map sanitise $ rs <> tb <> tf)
- [] -> ([], map sanitise $ tb <> tf)
-
-- | Inline elements used to separate blocks when squashing blocks into
-- inlines.
defaultBlocksSeparator :: Inlines