diff options
author | despresc <christian.j.j.despres@gmail.com> | 2020-03-28 18:22:48 -0400 |
---|---|---|
committer | despresc <christian.j.j.despres@gmail.com> | 2020-04-15 23:03:22 -0400 |
commit | 7254a2ae0ba40b29c04b8924f27739614229432b (patch) | |
tree | 114e3143953451e3212511e7bf2e178548d3e1bd /src/Text/Pandoc/Writers | |
parent | 83c1ce1d77d3ef058e4e5c645a8eb0379fab780f (diff) | |
download | pandoc-7254a2ae0ba40b29c04b8924f27739614229432b.tar.gz |
Implement the new Table type
Diffstat (limited to 'src/Text/Pandoc/Writers')
32 files changed, 239 insertions, 181 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 08af578a7..b9d93188a 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -191,7 +191,8 @@ blockToAsciiDoc opts (BlockQuote blocks) = do else contents let bar = text "____" return $ bar $$ chomp contents' $$ bar <> blankline -blockToAsciiDoc opts (Table caption aligns widths headers rows) = do +blockToAsciiDoc opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot caption' <- inlineListToAsciiDoc opts caption let caption'' = if null caption then empty diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 48a6934eb..585f7137e 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -27,7 +27,7 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Shared (capitalize, isTightList, - linesToPara, onlySimpleTableCells, taskListItemToAscii, tshow) + linesToPara, onlySimpleTableCells, taskListItemToAscii, tshow, toLegacyTable) import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Walk (walk, walkM) import Text.Pandoc.Writers.HTML (writeHtml5String, tagWithAttributes) @@ -154,71 +154,72 @@ blockToNodes opts (DefinitionList items) ns = Plain (term ++ [LineBreak] ++ xs) : ys ++ concat zs dlToBullet (term, xs) = Para term : concat xs -blockToNodes opts t@(Table capt aligns _widths headers rows) ns = - if isEnabled Ext_pipe_tables opts && onlySimpleTableCells (headers:rows) - then do - -- We construct a table manually as a CUSTOM_BLOCK, for - -- two reasons: (1) cmark-gfm currently doesn't support - -- rendering TABLE nodes; (2) we can align the column sides; - -- (3) we can render the caption as a regular paragraph. - let capt' = node PARAGRAPH (inlinesToNodes opts capt) - -- backslash | in code and raw: - let fixPipe (Code attr xs) = - Code attr (T.replace "|" "\\|" xs) - fixPipe (RawInline format xs) = - RawInline format (T.replace "|" "\\|" xs) - fixPipe x = x - let toCell [Plain ils] = T.strip - $ nodeToCommonmark [] Nothing - $ node (CUSTOM_INLINE mempty mempty) - $ inlinesToNodes opts - $ walk (fixPipe . softBreakToSpace) ils - toCell [Para ils] = T.strip - $ nodeToCommonmark [] Nothing - $ node (CUSTOM_INLINE mempty mempty) - $ inlinesToNodes opts - $ walk (fixPipe . softBreakToSpace) ils - toCell [] = "" - toCell xs = error $ "toCell encountered " ++ show xs - let separator = " | " - let starter = "| " - let ender = " |" - let rawheaders = map toCell headers - let rawrows = map (map toCell) rows - let maximum' [] = 0 - maximum' xs = maximum xs - let colwidths = map (maximum' . map T.length) $ - transpose (rawheaders:rawrows) - let toHeaderLine len AlignDefault = T.replicate len "-" - toHeaderLine len AlignLeft = ":" <> - T.replicate (max (len - 1) 1) "-" - toHeaderLine len AlignRight = - T.replicate (max (len - 1) 1) "-" <> ":" - toHeaderLine len AlignCenter = ":" <> - T.replicate (max (len - 2) 1) (T.pack "-") <> ":" - let rawheaderlines = zipWith toHeaderLine colwidths aligns - let headerlines = starter <> T.intercalate separator rawheaderlines <> - ender - let padContent (align, w) t' = - let padding = w - T.length t' - halfpadding = padding `div` 2 - in case align of - AlignRight -> T.replicate padding " " <> t' - AlignCenter -> T.replicate halfpadding " " <> t' <> - T.replicate (padding - halfpadding) " " - _ -> t' <> T.replicate padding " " - let toRow xs = starter <> T.intercalate separator - (zipWith padContent (zip aligns colwidths) xs) <> - ender - let table' = toRow rawheaders <> "\n" <> headerlines <> "\n" <> - T.intercalate "\n" (map toRow rawrows) - return (node (CUSTOM_BLOCK table' mempty) [] : - if null capt - then ns - else capt' : ns) - else do -- fall back to raw HTML - s <- writeHtml5String def $! Pandoc nullMeta [t] - return (node (HTML_BLOCK s) [] : ns) +blockToNodes opts t@(Table _ blkCapt specs _ thead tbody tfoot) ns = + let (capt, aligns, _widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + in if isEnabled Ext_pipe_tables opts && onlySimpleTableCells (thead <> tbody <> tfoot) + then do + -- We construct a table manually as a CUSTOM_BLOCK, for + -- two reasons: (1) cmark-gfm currently doesn't support + -- rendering TABLE nodes; (2) we can align the column sides; + -- (3) we can render the caption as a regular paragraph. + let capt' = node PARAGRAPH (inlinesToNodes opts capt) + -- backslash | in code and raw: + let fixPipe (Code attr xs) = + Code attr (T.replace "|" "\\|" xs) + fixPipe (RawInline format xs) = + RawInline format (T.replace "|" "\\|" xs) + fixPipe x = x + let toCell [Plain ils] = T.strip + $ nodeToCommonmark [] Nothing + $ node (CUSTOM_INLINE mempty mempty) + $ inlinesToNodes opts + $ walk (fixPipe . softBreakToSpace) ils + toCell [Para ils] = T.strip + $ nodeToCommonmark [] Nothing + $ node (CUSTOM_INLINE mempty mempty) + $ inlinesToNodes opts + $ walk (fixPipe . softBreakToSpace) ils + toCell [] = "" + toCell xs = error $ "toCell encountered " ++ show xs + let separator = " | " + let starter = "| " + let ender = " |" + let rawheaders = map toCell headers + let rawrows = map (map toCell) rows + let maximum' [] = 0 + maximum' xs = maximum xs + let colwidths = map (maximum' . map T.length) $ + transpose (rawheaders:rawrows) + let toHeaderLine len AlignDefault = T.replicate len "-" + toHeaderLine len AlignLeft = ":" <> + T.replicate (max (len - 1) 1) "-" + toHeaderLine len AlignRight = + T.replicate (max (len - 1) 1) "-" <> ":" + toHeaderLine len AlignCenter = ":" <> + T.replicate (max (len - 2) 1) (T.pack "-") <> ":" + let rawheaderlines = zipWith toHeaderLine colwidths aligns + let headerlines = starter <> T.intercalate separator rawheaderlines <> + ender + let padContent (align, w) t' = + let padding = w - T.length t' + halfpadding = padding `div` 2 + in case align of + AlignRight -> T.replicate padding " " <> t' + AlignCenter -> T.replicate halfpadding " " <> t' <> + T.replicate (padding - halfpadding) " " + _ -> t' <> T.replicate padding " " + let toRow xs = starter <> T.intercalate separator + (zipWith padContent (zip aligns colwidths) xs) <> + ender + let table' = toRow rawheaders <> "\n" <> headerlines <> "\n" <> + T.intercalate "\n" (map toRow rawrows) + return (node (CUSTOM_BLOCK table' mempty) [] : + if null capt + then ns + else capt' : ns) + else do -- fall back to raw HTML + s <- writeHtml5String def $! Pandoc nullMeta [t] + return (node (HTML_BLOCK s) [] : ns) blockToNodes _ Null ns = return ns inlinesToNodes :: WriterOptions -> [Inline] -> [Node] diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index fb97e4fb4..f3d7219d1 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -255,7 +255,8 @@ blockToConTeXt (DefinitionList lst) = 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 -blockToConTeXt (Table caption aligns widths heads rows) = do +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 diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index bc520d520..beb2301c9 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -29,6 +29,7 @@ import Text.Pandoc.Lua (Global (..), LuaException (LuaException), runLua, setGlobals) import Text.Pandoc.Lua.Util (addField, dofileWithTraceback) import Text.Pandoc.Options +import Text.Pandoc.Shared (toLegacyTable) import Text.Pandoc.Templates (renderTemplate) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.Writers.Shared @@ -149,8 +150,9 @@ blockToCustom (CodeBlock attr str) = blockToCustom (BlockQuote blocks) = Lua.callFunc "BlockQuote" (Stringify blocks) -blockToCustom (Table capt aligns widths headers rows) = - let aligns' = map show aligns +blockToCustom (Table _ blkCapt specs _ thead tbody tfoot) = + let (capt, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + aligns' = map show aligns capt' = Stringify capt headers' = map Stringify headers rows' = map (map Stringify) rows diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index f05a29157..7af357fb0 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -263,7 +263,8 @@ blockToDocbook _ b@(RawBlock f str) report $ BlockNotRendered b return empty blockToDocbook _ HorizontalRule = return empty -- not semantic -blockToDocbook opts (Table caption aligns widths headers rows) = do +blockToDocbook opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot captionDoc <- if null caption then return empty else inTagsIndented "title" <$> diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 2a2747826..f9e173bb2 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -970,7 +970,8 @@ blockToOpenXML' _ HorizontalRule = do $ mknode "v:rect" [("style","width:0;height:1.5pt"), ("o:hralign","center"), ("o:hrstd","t"),("o:hr","t")] () ] -blockToOpenXML' opts (Table caption aligns widths headers rows) = do +blockToOpenXML' opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot setFirstPara modify $ \s -> s { stInTable = True } let captionStr = stringify caption @@ -993,11 +994,11 @@ blockToOpenXML' opts (Table caption aligns widths headers rows) = do $ mknode "w:bottom" [("w:val","single")] () , mknode "w:vAlign" [("w:val","bottom")] () ] compactStyle <- pStyleM "Compact" - let emptyCell = [mknode "w:p" [] [mknode "w:pPr" [] [compactStyle]]] + let emptyCell' = [mknode "w:p" [] [mknode "w:pPr" [] [compactStyle]]] let mkcell border contents = mknode "w:tc" [] $ [ borderProps | border ] ++ if null contents - then emptyCell + then emptyCell' else contents let mkrow border cells = mknode "w:tr" [] $ [mknode "w:trPr" [] [ diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 5cc5d19fe..ce99aaa9d 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -35,7 +35,7 @@ import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, isURI, linesToPara, - removeFormatting, trimr, tshow) + removeFormatting, trimr, tshow, toLegacyTable) import Text.Pandoc.Templates (renderTemplate) import Text.DocLayout (render, literal) import Text.Pandoc.Writers.Shared (defField, metaToContext) @@ -166,7 +166,8 @@ blockToDokuWiki opts (BlockQuote blocks) = do then return $ T.unlines $ map ("> " <>) $ T.lines contents else return $ "<HTML><blockquote>\n" <> contents <> "</blockquote></HTML>" -blockToDokuWiki opts (Table capt aligns _ headers rows) = do +blockToDokuWiki opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (capt, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot captionDoc <- if null capt then return "" else do diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index b6f76235c..5b62119a3 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -40,7 +40,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Logging import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..), def) import Text.Pandoc.Shared (capitalize, isURI, orderedListMarkers, - makeSections, tshow) + makeSections, tshow, toLegacyTable) import Text.Pandoc.Writers.Shared (lookupMetaString) -- | Data to be written at the end of the document: @@ -334,17 +334,18 @@ blockToXml h@Header{} = do report $ BlockNotRendered h return [] blockToXml HorizontalRule = return [ el "empty-line" () ] -blockToXml (Table caption aligns _ headers rows) = do +blockToXml (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot hd <- mkrow "th" headers aligns bd <- mapM (\r -> mkrow "td" r aligns) rows c <- el "emphasis" <$> cMapM toXml caption return [el "table" (hd : bd), el "p" c] where - mkrow :: PandocMonad m => String -> [TableCell] -> [Alignment] -> FBM m Content + mkrow :: PandocMonad m => String -> [[Block]] -> [Alignment] -> FBM m Content mkrow tag cells aligns' = el "tr" <$> mapM (mkcell tag) (zip cells aligns') -- - mkcell :: PandocMonad m => String -> (TableCell, Alignment) -> FBM m Content + mkcell :: PandocMonad m => String -> ([Block], Alignment) -> FBM m Content mkcell tag (cell, align) = do cblocks <- cMapM blockToXml cell return $ el tag ([align_attr align], cblocks) diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 7cee2868c..070631f0d 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -885,7 +885,8 @@ blockToHtml opts (DefinitionList lst) = do return $ mconcat $ nl opts : term' : nl opts : intersperse (nl opts) defs') lst defList opts contents -blockToHtml opts (Table capt aligns widths headers rows') = do +blockToHtml opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (capt, aligns, widths, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot captionDoc <- if null capt then return mempty else do diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 5a29f6246..57e2f0ea7 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -115,7 +115,8 @@ blockToHaddock _ (CodeBlock (_,_,_) str) = -- Nothing in haddock corresponds to block quotes: blockToHaddock opts (BlockQuote blocks) = blockListToHaddock opts blocks -blockToHaddock opts (Table caption aligns widths headers rows) = do +blockToHaddock opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot caption' <- inlineListToHaddock opts caption let caption'' = if null caption then empty diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 997961f37..5575ab2bb 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -321,8 +321,9 @@ blockToICML opts style (Header lvl (_, cls, _) lst) = else "" in parStyle opts stl lst blockToICML _ _ HorizontalRule = return empty -- we could insert a page break instead -blockToICML opts style (Table caption aligns widths headers rows) = - let style' = tableName : style +blockToICML opts style (Table _ blkCapt specs _ thead tbody tfoot) = + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + style' = tableName : style noHeader = all null headers nrHeaders = if noHeader then "0" diff --git a/src/Text/Pandoc/Writers/Ipynb.hs b/src/Text/Pandoc/Writers/Ipynb.hs index 9355cc22f..d01d5a7e5 100644 --- a/src/Text/Pandoc/Writers/Ipynb.hs +++ b/src/Text/Pandoc/Writers/Ipynb.hs @@ -97,7 +97,7 @@ addAttachment (Image attr lab (src,tit)) return $ Image attr lab ("attachment:" <> src, tit) addAttachment x = return x -extractCells :: PandocMonad m => WriterOptions -> [Block] -> m [Cell a] +extractCells :: PandocMonad m => WriterOptions -> [Block] -> m [Ipynb.Cell a] extractCells _ [] = return [] extractCells opts (Div (_id,classes,kvs) xs : bs) | "cell" `elem` classes @@ -106,7 +106,7 @@ extractCells opts (Div (_id,classes,kvs) xs : bs) (newdoc, attachments) <- runStateT (walkM addAttachment (Pandoc nullMeta xs)) mempty source <- writeMarkdown opts{ writerTemplate = Nothing } newdoc - (Cell{ + (Ipynb.Cell{ cellType = Markdown , cellSource = Source $ breakLines $ T.stripEnd source , cellMetadata = meta @@ -123,7 +123,7 @@ extractCells opts (Div (_id,classes,kvs) xs : bs) let meta = pairsToJSONMeta kvs outputs <- catMaybes <$> mapM blockToOutput rest let exeCount = lookup "execution_count" kvs >>= safeRead - (Cell{ + (Ipynb.Cell{ cellType = Ipynb.Code { codeExecutionCount = exeCount , codeOutputs = outputs @@ -143,7 +143,7 @@ extractCells opts (Div (_id,classes,kvs) xs : bs) "markdown" -> "text/markdown" "rst" -> "text/x-rst" _ -> f - (Cell{ + (Ipynb.Cell{ cellType = Raw , cellSource = Source $ breakLines raw , cellMetadata = if format' == "ipynb" -- means no format given @@ -156,7 +156,7 @@ extractCells opts (CodeBlock (_id,classes,kvs) raw : bs) | "code" `elem` classes = do let meta = pairsToJSONMeta kvs let exeCount = lookup "execution_count" kvs >>= safeRead - (Cell{ + (Ipynb.Cell{ cellType = Ipynb.Code { codeExecutionCount = exeCount , codeOutputs = [] diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 4b731469e..f739613b6 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -356,21 +356,25 @@ blockToJATS _ b@(RawBlock f str) report $ BlockNotRendered b return empty blockToJATS _ HorizontalRule = return empty -- not semantic -blockToJATS opts (Table [] aligns widths headers rows) = do - let percent w = tshow (truncate (100*w) :: Integer) <> "*" - let coltags = vcat $ zipWith (\w al -> selfClosingTag "col" - ([("width", percent w) | w > 0] ++ - [("align", alignmentToText al)])) widths aligns - thead <- if all null headers - then return empty - else inTagsIndented "thead" <$> tableRowToJATS opts True headers - tbody <- (inTagsIndented "tbody" . vcat) <$> - mapM (tableRowToJATS opts False) rows - return $ inTags True "table" [] $ coltags $$ thead $$ tbody -blockToJATS opts (Table caption aligns widths headers rows) = do - captionDoc <- inTagsIndented "caption" <$> blockToJATS opts (Para caption) - tbl <- blockToJATS opts (Table [] aligns widths headers rows) - return $ inTags True "table-wrap" [] $ captionDoc $$ tbl +blockToJATS opts (Table _ blkCapt specs _ th tb tf) = + case toLegacyTable blkCapt specs th tb tf of + ([], aligns, widths, headers, rows) -> captionlessTable aligns widths headers rows + (caption, aligns, widths, headers, rows) -> do + captionDoc <- inTagsIndented "caption" <$> blockToJATS opts (Para caption) + tbl <- captionlessTable aligns widths headers rows + return $ inTags True "table-wrap" [] $ captionDoc $$ tbl + where + captionlessTable aligns widths headers rows = do + let percent w = tshow (truncate (100*w) :: Integer) <> "*" + let coltags = vcat $ zipWith (\w al -> selfClosingTag "col" + ([("width", percent w) | w > 0] ++ + [("align", alignmentToText al)])) widths aligns + thead <- if all null headers + then return empty + else inTagsIndented "thead" <$> tableRowToJATS opts True headers + tbody <- (inTagsIndented "tbody" . vcat) <$> + mapM (tableRowToJATS opts False) rows + return $ inTags True "table" [] $ coltags $$ thead $$ tbody alignmentToText :: Alignment -> Text alignmentToText alignment = case alignment of diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs index 19db34137..bd22c161f 100644 --- a/src/Text/Pandoc/Writers/Jira.hs +++ b/src/Text/Pandoc/Writers/Jira.hs @@ -26,7 +26,7 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Options (WriterOptions (writerTemplate, writerWrapText), WrapOption (..)) -import Text.Pandoc.Shared (linesToPara, stringify) +import Text.Pandoc.Shared (linesToPara, stringify, toLegacyTable) import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Math (texMathToInlines) import Text.Pandoc.Writers.Shared (defField, metaToContext) @@ -98,7 +98,8 @@ toJiraBlocks blocks = do Plain xs -> singleton . Jira.Para <$> toJiraInlines xs RawBlock fmt cs -> rawBlockToJira fmt cs Null -> return mempty - Table _ _ _ hd body -> singleton <$> do + Table _ blkCapt specs _ thead tbody tfoot -> singleton <$> do + let (_, _, _, hd, body) = toLegacyTable blkCapt specs thead tbody tfoot headerRow <- if all null hd then pure Nothing else Just <$> toRow Jira.HeaderCell hd @@ -112,7 +113,7 @@ toJiraBlocks blocks = do toRow :: PandocMonad m => ([Jira.Block] -> Jira.Cell) - -> [TableCell] + -> [[Block]] -> JiraConverter m Jira.Row toRow mkCell cells = Jira.Row <$> mapM (fmap mkCell . toJiraBlocks) cells diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 1670f8380..274f5108a 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -759,7 +759,8 @@ blockToLaTeX (Header level (id',classes,_) lst) = do hdr <- sectionHeader classes id' level lst modify $ \s -> s{stInHeading = False} return hdr -blockToLaTeX (Table caption aligns widths heads rows) = do +blockToLaTeX (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot (captionText, captForLof, captNotes) <- getCaption False caption let toHeaders hs = do contents <- tableRowToLaTeX True aligns widths hs return ("\\toprule" $$ contents $$ "\\midrule") diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 2f4175d19..dda1e1cf1 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -139,8 +139,9 @@ blockToMan opts (CodeBlock _ str) = return $ blockToMan opts (BlockQuote blocks) = do contents <- blockListToMan opts blocks return $ literal ".RS" $$ contents $$ literal ".RE" -blockToMan opts (Table caption alignments widths headers rows) = - let aligncode AlignLeft = "l" +blockToMan opts (Table _ blkCapt specs _ thead tbody tfoot) = + let (caption, alignments, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + aligncode AlignLeft = "l" aligncode AlignRight = "r" aligncode AlignCenter = "c" aligncode AlignDefault = "l" diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 58299f5ea..5501b49ee 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -574,14 +574,15 @@ blockToMarkdown' opts (BlockQuote blocks) = do else if plain then " " else "> " contents <- blockListToMarkdown opts blocks return $ (prefixed leader contents) <> blankline -blockToMarkdown' opts t@(Table caption aligns widths headers rows) = do +blockToMarkdown' opts t@(Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot let numcols = maximum (length aligns : length widths : map length (headers:rows)) caption' <- inlineListToMarkdown opts caption let caption'' = if null caption || not (isEnabled Ext_table_captions opts) then blankline else blankline $$ (": " <> caption') $$ blankline - let hasSimpleCells = onlySimpleTableCells $ headers:rows + let hasSimpleCells = onlySimpleTableCells $ thead <> tbody <> tfoot let isSimple = hasSimpleCells && all (==0) widths let isPlainBlock (Plain _) = True isPlainBlock _ = False diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 8b8eb7561..fbfb7acb4 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -150,7 +150,8 @@ blockToMediaWiki (BlockQuote blocks) = do contents <- blockListToMediaWiki blocks return $ "<blockquote>" <> contents <> "</blockquote>" -blockToMediaWiki (Table capt aligns widths headers rows') = do +blockToMediaWiki (Table _ blkCapt specs _ thead tbody tfoot) = do + let (capt, aligns, widths, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot caption <- if null capt then return "" else do diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 78c70c561..ad2a7a3fd 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -215,8 +215,9 @@ blockToMs opts (BlockQuote blocks) = do contents <- blockListToMs opts blocks setFirstPara return $ literal ".QS" $$ contents $$ literal ".QE" -blockToMs opts (Table caption alignments widths headers rows) = - let aligncode AlignLeft = "l" +blockToMs opts (Table _ blkCapt specs _ thead tbody tfoot) = + let (caption, alignments, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + aligncode AlignLeft = "l" aligncode AlignRight = "r" aligncode AlignCenter = "c" aligncode AlignDefault = "l" diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 60d200007..8f672a8bd 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -150,8 +150,8 @@ flatBlockListToMuse [] = return mempty simpleTable :: PandocMonad m => [Inline] - -> [TableCell] - -> [[TableCell]] + -> [[Block]] + -> [[[Block]]] -> Muse m (Doc Text) simpleTable caption headers rows = do topLevel <- asks envTopLevel @@ -259,17 +259,18 @@ blockToMuse (Header level (ident,_,_) inlines) = do return $ blankline <> attr' $$ nowrap (header' <> contents) <> blankline -- https://www.gnu.org/software/emacs-muse/manual/muse.html#Horizontal-Rules-and-Anchors blockToMuse HorizontalRule = return $ blankline $$ "----" $$ blankline -blockToMuse (Table caption aligns widths headers rows) = +blockToMuse (Table _ blkCapt specs _ thead tbody tfoot) = if isSimple && numcols > 1 then simpleTable caption headers rows else do opts <- asks envOptions gridTable opts blocksToDoc True (map (const AlignDefault) aligns) widths headers rows where + (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot blocksToDoc opts blocks = local (\env -> env { envOptions = opts }) $ blockListToMuse blocks numcols = maximum (length aligns : length widths : map length (headers:rows)) - isSimple = onlySimpleTableCells (headers:rows) && all (== 0) widths + isSimple = onlySimpleTableCells (thead <> tbody <> tfoot) && all (== 0) widths blockToMuse (Div _ bs) = flatBlockListToMuse bs blockToMuse Null = return empty diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index 1c4719fe9..a533496c1 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -40,12 +40,33 @@ prettyBlock (DefinitionList items) = "DefinitionList" $$ prettyList (map deflistitem items) where deflistitem (term, defs) = "(" <> text (show term) <> "," <> cr <> nest 1 (prettyList $ map (prettyList . map prettyBlock) defs) <> ")" -prettyBlock (Table caption aligns widths header rows) = - "Table " <> text (show caption) <> " " <> text (show aligns) <> " " <> - text (show widths) $$ - prettyRow header $$ - prettyList (map prettyRow rows) - where prettyRow cols = prettyList (map (prettyList . map prettyBlock) cols) +prettyBlock (Table attr blkCapt specs rhs thead tbody tfoot) = + mconcat [ "Table " + , text (show attr) + , " " + , prettyCaption blkCapt + , " " + , text (show specs) + , " " + , text (show rhs) ] $$ + prettyRows thead $$ + prettyRows tbody $$ + prettyRows tfoot + where prettyRows = prettyList . map prettyRow + prettyRow (Row a body) = + text ("Row " <> show a) $$ prettyList (map prettyCell body) + prettyCell (Cell a ma h w b) = + mconcat [ "Cell " + , text (show a) + , " " + , text (showsPrec 11 ma "") + , " " + , text (show h) + , " " + , text (show w) ] $$ + prettyList (map prettyBlock b) + prettyCaption (Caption mshort body) = + "(Caption " <> text (showsPrec 11 mshort "") $$ prettyList (map prettyBlock body) <> ")" prettyBlock (Div attr blocks) = text ("Div " <> show attr) $$ prettyList (map prettyBlock blocks) prettyBlock block = text $ show block diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index b7243484b..12599772f 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -31,7 +31,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Logging import Text.Pandoc.Options import Text.DocLayout -import Text.Pandoc.Shared (linesToPara, tshow) +import Text.Pandoc.Shared (linesToPara, tshow, toLegacyTable) import Text.Pandoc.Templates (renderTemplate) import qualified Text.Pandoc.Translations as Term (Term(Figure, Table)) import Text.Pandoc.Writers.Math @@ -359,7 +359,9 @@ blockToOpenDocument o bs | BulletList b <- bs = setFirstPara >> bulletListToOpenDocument o b | OrderedList a b <- bs = setFirstPara >> orderedList a b | CodeBlock _ s <- bs = setFirstPara >> preformatted s - | Table c a w h r <- bs = setFirstPara >> table c a w h r + | Table _ bc s _ th tb tf + <- bs = let (c, a, w, h, r) = toLegacyTable bc s th tb tf + in setFirstPara >> table c a w h r | HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p" [ ("text:style-name", "Horizontal_20_Line") ]) | RawBlock f s <- bs = if f == Format "opendocument" diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 632ad5d34..d8d89d2eb 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -183,7 +183,8 @@ blockToOrg (BlockQuote blocks) = do contents <- blockListToOrg blocks return $ blankline $$ "#+BEGIN_QUOTE" $$ nest 2 contents $$ "#+END_QUOTE" $$ blankline -blockToOrg (Table caption' _ _ headers rows) = do +blockToOrg (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption', _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot caption'' <- inlineListToOrg caption' let caption = if null caption' then empty diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index b98eee1f5..12467048b 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -977,10 +977,10 @@ graphicToElement tableWidth (Tbl tblPr hdrCells rows) = do headers' <- mapM cellToOpenXML hdrCells rows' <- mapM (mapM cellToOpenXML) rows let borderProps = mknode "a:tcPr" [] () - let emptyCell = [mknode "a:p" [] [mknode "a:pPr" [] ()]] + let emptyCell' = [mknode "a:p" [] [mknode "a:pPr" [] ()]] let mkcell border contents = mknode "a:tc" [] $ (if null contents - then emptyCell + then emptyCell' else contents) <> [ borderProps | border ] let mkrow border cells = mknode "a:tr" [("h", "0")] $ map (mkcell border) cells diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 84e7423ac..dbacbb3cf 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -54,7 +54,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Walk import Data.Time (UTCTime) import qualified Text.Pandoc.Shared as Shared -- so we don't overlap "Element" -import Text.Pandoc.Shared (tshow) +import Text.Pandoc.Shared (tshow, toLegacyTable) import Text.Pandoc.Writers.Shared (lookupMetaInlines, lookupMetaBlocks , lookupMetaString, toTableOfContents) import qualified Data.Map as M @@ -201,13 +201,17 @@ data Shape = Pic PicProps FilePath [ParaElem] | RawOOXMLShape T.Text deriving (Show, Eq) -type Cell = [Paragraph] +type TableCell = [Paragraph] + +-- TODO: remove when better handling of new +-- tables is implemented +type SimpleCell = [Block] data TableProps = TableProps { tblPrFirstRow :: Bool , tblPrBandRow :: Bool } deriving (Show, Eq) -data Graphic = Tbl TableProps [Cell] [[Cell]] +data Graphic = Tbl TableProps [TableCell] [[TableCell]] deriving (Show, Eq) @@ -503,7 +507,7 @@ multiParBullet (b:bs) = do concatMapM blockToParagraphs bs return $ p ++ ps -cellToParagraphs :: Alignment -> TableCell -> Pres [Paragraph] +cellToParagraphs :: Alignment -> SimpleCell -> Pres [Paragraph] cellToParagraphs algn tblCell = do paras <- mapM blockToParagraphs tblCell let alignment = case algn of @@ -514,7 +518,7 @@ cellToParagraphs algn tblCell = do paras' = map (map (\p -> p{paraProps = (paraProps p){pPropAlign = alignment}})) paras return $ concat paras' -rowToParagraphs :: [Alignment] -> [TableCell] -> Pres [[Paragraph]] +rowToParagraphs :: [Alignment] -> [SimpleCell] -> Pres [[Paragraph]] rowToParagraphs algns tblCells = do -- We have to make sure we have the right number of alignments let pairs = zip (algns ++ repeat AlignDefault) tblCells @@ -537,7 +541,8 @@ blockToShape (Para (il:_)) | Link _ (il':_) target <- il , Image attr ils (url, _) <- il' = (withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url)) <$> inlinesToParElems ils -blockToShape (Table caption algn _ hdrCells rows) = do +blockToShape (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, algn, _, hdrCells, rows) = toLegacyTable blkCapt specs thead tbody tfoot caption' <- inlinesToParElems caption hdrCells' <- rowToParagraphs algn hdrCells rows' <- mapM (rowToParagraphs algn) rows diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 9a6e41e3c..85354d93f 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -284,7 +284,8 @@ blockToRST (CodeBlock (_,classes,kvs) str) = do blockToRST (BlockQuote blocks) = do contents <- blockListToRST blocks return $ nest 3 contents <> blankline -blockToRST (Table caption aligns widths headers rows) = do +blockToRST (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot caption' <- inlineListToRST caption let blocksToDoc opts bs = do oldOpts <- gets stOptions diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 41cfc416b..e45a73f79 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -254,7 +254,8 @@ blockToRTF indent alignment (Header level _ lst) = do contents <- inlinesToRTF lst return $ rtfPar indent 0 alignment $ "\\b \\fs" <> tshow (40 - (level * 4)) <> " " <> contents -blockToRTF indent alignment (Table caption aligns sizes headers rows) = do +blockToRTF indent alignment (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, sizes, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot caption' <- inlinesToRTF caption header' <- if all null headers then return "" diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index d2689935e..d1bc514c1 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -194,7 +194,8 @@ blockToTEI _ HorizontalRule = return $ -- | TEI Tables -- TEI Simple's tables are composed of cells and rows; other -- table info in the AST is here lossily discard. -blockToTEI opts (Table _ _ _ headers rows) = do +blockToTEI opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (_, _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot headers' <- tableHeadersToTEI opts headers rows' <- mapM (tableRowToTEI opts) rows return $ inTags True "table" [] $ headers' $$ vcat rows' diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index de78b705e..a4b1d3a57 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -228,7 +228,8 @@ blockToTexinfo (Header level (ident,_,_) lst) seccmd 4 = return "@subsubsection " seccmd _ = throwError $ PandocSomeError "illegal seccmd level" -blockToTexinfo (Table caption aligns widths heads rows) = do +blockToTexinfo (Table _ blkCapt specs _ thead tbody tfoot) = do + let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot headers <- if all null heads then return empty else tableHeadToTexinfo aligns heads diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index d2cb74c84..2e02448e3 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -168,44 +168,44 @@ blockToTextile opts (BlockQuote blocks) = do contents <- blockListToTextile opts blocks return $ "<blockquote>\n\n" <> contents <> "\n</blockquote>\n" -blockToTextile opts (Table [] aligns widths headers rows') | - all (==0) widths = do - hs <- mapM (liftM (("_. " <>) . stripTrailingNewlines) . blockListToTextile opts) headers - let cellsToRow cells = "|" <> T.intercalate "|" cells <> "|" - let header = if all null headers then "" else cellsToRow hs <> "\n" - let blocksToCell (align, bs) = do - contents <- stripTrailingNewlines <$> blockListToTextile opts bs - let alignMarker = case align of - AlignLeft -> "<. " - AlignRight -> ">. " - AlignCenter -> "=. " - AlignDefault -> "" - return $ alignMarker <> contents - let rowToCells = mapM blocksToCell . zip aligns - bs <- mapM rowToCells rows' - let body = T.unlines $ map cellsToRow bs - return $ header <> body - -blockToTextile opts (Table capt aligns widths headers rows') = do - let alignStrings = map alignmentToText aligns - captionDoc <- if null capt - then return "" - else do - c <- inlineListToTextile opts capt - return $ "<caption>" <> c <> "</caption>\n" - let percent w = tshow (truncate (100*w) :: Integer) <> "%" - let coltags = if all (== 0.0) widths - then "" - else T.unlines $ map - (\w -> "<col width=\"" <> percent w <> "\" />") widths - head' <- if all null headers - then return "" - else do - hs <- tableRowToTextile opts alignStrings 0 headers - return $ "<thead>\n" <> hs <> "\n</thead>\n" - body' <- zipWithM (tableRowToTextile opts alignStrings) [1..] rows' - return $ "<table>\n" <> captionDoc <> coltags <> head' <> - "<tbody>\n" <> T.unlines body' <> "</tbody>\n</table>\n" +blockToTextile opts (Table _ blkCapt specs _ thead tbody tfoot) + = case toLegacyTable blkCapt specs thead tbody tfoot of + ([], aligns, widths, headers, rows') | all (==0) widths -> do + hs <- mapM (liftM (("_. " <>) . stripTrailingNewlines) . blockListToTextile opts) headers + let cellsToRow cells = "|" <> T.intercalate "|" cells <> "|" + let header = if all null headers then "" else cellsToRow hs <> "\n" + let blocksToCell (align, bs) = do + contents <- stripTrailingNewlines <$> blockListToTextile opts bs + let alignMarker = case align of + AlignLeft -> "<. " + AlignRight -> ">. " + AlignCenter -> "=. " + AlignDefault -> "" + return $ alignMarker <> contents + let rowToCells = mapM blocksToCell . zip aligns + bs <- mapM rowToCells rows' + let body = T.unlines $ map cellsToRow bs + return $ header <> body + (capt, aligns, widths, headers, rows') -> do + let alignStrings = map alignmentToText aligns + captionDoc <- if null capt + then return "" + else do + c <- inlineListToTextile opts capt + return $ "<caption>" <> c <> "</caption>\n" + let percent w = tshow (truncate (100*w) :: Integer) <> "%" + let coltags = if all (== 0.0) widths + then "" + else T.unlines $ map + (\w -> "<col width=\"" <> percent w <> "\" />") widths + head' <- if all null headers + then return "" + else do + hs <- tableRowToTextile opts alignStrings 0 headers + return $ "<thead>\n" <> hs <> "\n</thead>\n" + body' <- zipWithM (tableRowToTextile opts alignStrings) [1..] rows' + return $ "<table>\n" <> captionDoc <> coltags <> head' <> + "<tbody>\n" <> T.unlines body' <> "</tbody>\n</table>\n" blockToTextile opts x@(BulletList items) = do oldUseTags <- gets stUseTags diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs index 71bb8b2e4..43729d0b0 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -122,7 +122,8 @@ blockToXWiki (DefinitionList items) = do return $ vcat contents <> if Text.null lev then "\n" else "" -- TODO: support more features -blockToXWiki (Table _ _ _ headers rows') = do +blockToXWiki (Table _ blkCapt specs _ thead tbody tfoot) = do + let (_, _, _, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot headers' <- mapM (tableCellXWiki True) headers otherRows <- mapM formRow rows' return $ Text.unlines (Text.unwords headers':otherRows) diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 9644b9695..0709744d5 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -32,7 +32,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (escapeURI, isURI, linesToPara, removeFormatting, trimr) +import Text.Pandoc.Shared (escapeURI, isURI, linesToPara, removeFormatting, trimr, toLegacyTable) import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared (defField, metaToContext) @@ -132,7 +132,8 @@ blockToZimWiki opts (BlockQuote blocks) = do contents <- blockListToZimWiki opts blocks return $ T.unlines $ map ("> " <>) $ T.lines contents -blockToZimWiki opts (Table capt aligns _ headers rows) = do +blockToZimWiki opts (Table _ blkCapt specs _ thead tbody tfoot) = do + let (capt, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot captionDoc <- if null capt then return "" else do |