diff options
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/FB2.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/TEI.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/XWiki.hs | 2 |
4 files changed, 5 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index ba468cf4f..2f033b19e 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -280,7 +280,7 @@ blockToDocbook opts (Table _ blkCapt specs thead tbody tfoot) = do body' <- (inTagsIndented "tbody" . vcat) <$> mapM (tableRowToDocbook opts) rows return $ inTagsIndented tableType $ captionDoc $$ - inTags True "tgroup" [("cols", tshow (length headers))] ( + inTags True "tgroup" [("cols", tshow (length aligns))] ( coltags $$ head' $$ body') hasLineBreaks :: [Inline] -> Bool diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 83bcf2038..5e6f1861e 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -336,10 +336,10 @@ blockToXml h@Header{} = do blockToXml HorizontalRule = return [ el "empty-line" () ] blockToXml (Table _ blkCapt specs thead tbody tfoot) = do let (caption, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot - hd <- mkrow "th" headers aligns + hd <- if null headers then pure [] else (:[]) <$> 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] + return [el "table" (hd <> bd), el "p" c] where mkrow :: PandocMonad m => String -> [[Block]] -> [Alignment] -> FBM m Content mkrow tag cells aligns' = diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index f7fa19b1b..9ccc137eb 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -196,7 +196,7 @@ blockToTEI _ HorizontalRule = return $ -- table info in the AST is here lossily discard. blockToTEI opts (Table _ blkCapt specs thead tbody tfoot) = do let (_, _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot - headers' <- tableHeadersToTEI opts headers + headers' <- if null headers then pure mempty else tableHeadersToTEI opts headers rows' <- mapM (tableRowToTEI opts) rows return $ inTags True "table" [] $ headers' $$ vcat rows' diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs index bfc61c3b5..486de943f 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -125,7 +125,7 @@ blockToXWiki (DefinitionList items) = do -- TODO: support more features blockToXWiki (Table _ blkCapt specs thead tbody tfoot) = do let (_, _, _, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot - headers' <- mapM (tableCellXWiki True) headers + headers' <- mapM (tableCellXWiki True) $ take (length specs) $ headers ++ repeat [] otherRows <- mapM formRow rows' return $ Text.unlines (Text.unwords headers':otherRows) |