diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/CSV.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/DocBook.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx.hs | 19 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/DokuWiki.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Haddock.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/JATS.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Jira.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Man.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/MediaWiki.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Muse.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TWiki.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Txt2Tags.hs | 8 |
18 files changed, 154 insertions, 60 deletions
diff --git a/src/Text/Pandoc/Readers/CSV.hs b/src/Text/Pandoc/Readers/CSV.hs index a1272d47f..384687a6a 100644 --- a/src/Text/Pandoc/Readers/CSV.hs +++ b/src/Text/Pandoc/Readers/CSV.hs @@ -30,12 +30,18 @@ readCSV :: PandocMonad m -> m Pandoc readCSV _opts s = case parseCSV defaultCSVOptions (crFilter s) of - Right (r:rs) -> return $ B.doc $ B.table capt (zip aligns widths) hdrs rows - where capt = mempty + Right (r:rs) -> return $ B.doc $ B.table capt + (zip aligns widths) + (TableHead nullAttr hdrs) + [TableBody nullAttr 0 [] rows] + (TableFoot nullAttr []) + where capt = B.emptyCaption numcols = length r - toplain = B.plain . B.text . T.strip - hdrs = map toplain r - rows = map (map toplain) rs + toplain = B.simpleCell . B.plain . B.text . T.strip + toRow = Row nullAttr . map toplain + toHeaderRow l = if null l then [] else [toRow l] + hdrs = toHeaderRow r + rows = map toRow rs aligns = replicate numcols AlignDefault widths = replicate numcols ColWidthDefault Right [] -> return $ B.doc mempty diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 4001d647e..9757b8914 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -887,11 +887,13 @@ parseBlock (Elem e) = Just ws' -> let tot = sum ws' in ColWidth . (/ tot) <$> ws' Nothing -> replicate numrows ColWidthDefault - let headrows' = if null headrows - then replicate numrows mempty - else headrows - return $ table capt (zip aligns widths) - headrows' bodyrows + let toRow = Row nullAttr . map simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ table (simpleCaption $ plain capt) + (zip aligns widths) + (TableHead nullAttr $ toHeaderRow headrows) + [TableBody nullAttr 0 [] $ map toRow bodyrows] + (TableFoot nullAttr []) isEntry x = named "entry" x || named "td" x || named "th" x parseRow = mapM (parseMixed plain . elContent) . filterChildren isEntry sect n = do isbook <- gets dbBook diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 69aa18f73..bb86c91b0 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -72,7 +72,7 @@ import Data.Maybe (isJust, fromMaybe) import Data.Sequence (ViewL (..), viewl) import qualified Data.Sequence as Seq import qualified Data.Set as Set -import Text.Pandoc.Builder +import Text.Pandoc.Builder as Pandoc import Text.Pandoc.MediaBag (MediaBag) import Text.Pandoc.Options import Text.Pandoc.Readers.Docx.Combine @@ -645,7 +645,7 @@ bodyPartToBlocks (ListItem pPr _ _ _ parparts) = bodyPartToBlocks (Tbl _ _ _ []) = return $ para mempty bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do - let cap' = text cap + let cap' = simpleCaption $ plain $ text cap (hdr, rows) = case firstRowFormatting look of True | null rs -> (Nothing, [r]) | otherwise -> (Just r, rs) @@ -662,13 +662,16 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do rowLength :: Docx.Row -> Int rowLength (Docx.Row c) = length c + let toRow = Pandoc.Row nullAttr . map simpleCell + toHeaderRow l = if null l then [] else [toRow l] + -- pad cells. New Text.Pandoc.Builder will do that for us, -- so this is for compatibility while we switch over. - let cells' = map (\row -> take width (row ++ repeat mempty)) cells + let cells' = map (\row -> toRow $ take width (row ++ repeat mempty)) cells hdrCells <- case hdr of - Just r' -> rowToBlocksList r' - Nothing -> return $ replicate width mempty + Just r' -> toHeaderRow <$> rowToBlocksList r' + Nothing -> return [] -- The two following variables (horizontal column alignment and -- relative column widths) go to the default at the @@ -678,7 +681,11 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do let alignments = replicate width AlignDefault widths = replicate width ColWidthDefault - return $ table cap' (zip alignments widths) hdrCells cells' + return $ table cap' + (zip alignments widths) + (TableHead nullAttr hdrCells) + [TableBody nullAttr 0 [] cells'] + (TableFoot nullAttr []) bodyPartToBlocks (OMathPara e) = return $ para $ displayMath (writeTeX e) diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs index ee26eed84..8b48789b3 100644 --- a/src/Text/Pandoc/Readers/DokuWiki.hs +++ b/src/Text/Pandoc/Readers/DokuWiki.hs @@ -471,7 +471,13 @@ table = do then (head rows, tail rows) else ([], rows) let attrs = (AlignDefault, ColWidthDefault) <$ transpose rows - pure $ B.table mempty attrs headerRow body + let toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + pure $ B.table B.emptyCaption + attrs + (TableHead nullAttr $ toHeaderRow headerRow) + [TableBody nullAttr 0 [] $ map toRow body] + (TableFoot nullAttr []) tableRows :: PandocMonad m => DWParser m [[B.Blocks]] tableRows = many1 tableRow diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 30b812913..a48836446 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -516,7 +516,13 @@ pTable = try $ do then replicate cols ColWidthDefault else replicate cols (ColWidth (1.0 / fromIntegral cols)) else widths' - return $ B.table caption (zip aligns widths) head' rows + let toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ B.table (B.simpleCaption $ B.plain caption) + (zip aligns widths) + (TableHead nullAttr $ toHeaderRow head') + [TableBody nullAttr 0 [] $ map toRow rows] + (TableFoot nullAttr []) pCol :: PandocMonad m => TagParser m ColWidth pCol = try $ do diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 5bef6f9fd..8fe5e062c 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -85,6 +85,8 @@ docHToBlocks d' = , tableBodyRows = bodyRows } -> let toCells = map (docHToBlocks . tableCellContents) . tableRowCells + toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] (header, body) = if null headerRows then ([], map toCells bodyRows) @@ -92,7 +94,11 @@ docHToBlocks d' = map toCells (tail headerRows ++ bodyRows)) colspecs = replicate (maximum (map length body)) (AlignDefault, ColWidthDefault) - in B.table mempty colspecs header body + in B.table B.emptyCaption + colspecs + (TableHead nullAttr $ toHeaderRow header) + [TableBody nullAttr 0 [] $ map toRow body] + (TableFoot nullAttr []) where inlineFallback = B.plain $ docHToInlines False d' consolidatePlains = B.fromList . consolidatePlains' . B.toList diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs index 24d2ef4a1..f78630ec0 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -280,11 +280,13 @@ parseBlock (Elem e) = Just ws' -> let tot = sum ws' in ColWidth . (/ tot) <$> ws' Nothing -> replicate numrows ColWidthDefault - let headrows' = if null headrows - then replicate numrows mempty - else headrows - return $ table capt (zip aligns widths) - headrows' bodyrows + let toRow = Row nullAttr . map simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ table (simpleCaption $ plain capt) + (zip aligns widths) + (TableHead nullAttr $ toHeaderRow headrows) + [TableBody nullAttr 0 [] $ map toRow bodyrows] + (TableFoot nullAttr []) isEntry x = named "entry" x || named "td" x || named "th" x parseRow = mapM (parseMixed plain . elContent) . filterChildren isEntry sect n = do isbook <- gets jatsBook diff --git a/src/Text/Pandoc/Readers/Jira.hs b/src/Text/Pandoc/Readers/Jira.hs index d0900fd08..fd96cbc4d 100644 --- a/src/Text/Pandoc/Readers/Jira.hs +++ b/src/Text/Pandoc/Readers/Jira.hs @@ -16,7 +16,7 @@ import Data.Text (Text, append, pack, singleton, unpack) import Text.HTML.TagSoup.Entity (lookupEntity) import Text.Jira.Parser (parse) import Text.Pandoc.Class.PandocMonad (PandocMonad (..)) -import Text.Pandoc.Builder +import Text.Pandoc.Builder hiding (cell) import Text.Pandoc.Error (PandocError (PandocParseError)) import Text.Pandoc.Options (ReaderOptions) import Text.Pandoc.Shared (stringify) diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index ea5549543..cdd2c1362 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -2372,7 +2372,6 @@ simpTable envname hasWidthParameter = try $ do skipopts colspecs <- parseAligns let (aligns, widths, prefsufs) = unzip3 colspecs - let cols = length colspecs optional $ controlSeq "caption" *> setCaption spaces optional label @@ -2393,11 +2392,14 @@ simpTable envname hasWidthParameter = try $ do spaces optional lbreak spaces - let header'' = if null header' - then replicate cols mempty - else header' lookAhead $ controlSeq "end" -- make sure we're at end - return $ table mempty (zip aligns widths) header'' rows + let toRow = Row nullAttr . map simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ table emptyCaption + (zip aligns widths) + (TableHead nullAttr $ toHeaderRow header') + [TableBody nullAttr 0 [] $ map toRow rows] + (TableFoot nullAttr []) addTableCaption :: PandocMonad m => Blocks -> LP m Blocks addTableCaption = walkM go diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs index e175135da..12001b534 100644 --- a/src/Text/Pandoc/Readers/Man.hs +++ b/src/Text/Pandoc/Readers/Man.hs @@ -109,8 +109,10 @@ parseTable = do let widths = if isPlainTable then repeat ColWidthDefault else repeat $ ColWidth (1.0 / fromIntegral (length alignments)) - return $ B.table mempty (zip alignments widths) - headerRow bodyRows) <|> fallback pos + return $ B.table B.emptyCaption (zip alignments widths) + (TableHead nullAttr $ toHeaderRow headerRow) + [TableBody nullAttr 0 [] $ map toRow bodyRows] + (TableFoot nullAttr [])) <|> fallback pos [] -> fallback pos where @@ -159,6 +161,9 @@ parseTable = do 'r' -> Just AlignRight _ -> Nothing + toRow = Row nullAttr . map simpleCell + toHeaderRow l = if null l then [] else [toRow l] + parseNewParagraph :: PandocMonad m => ManParser m Blocks parseNewParagraph = do mmacro "P" <|> mmacro "PP" <|> mmacro "LP" <|> memptyLine diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 222c227e2..bfa43c228 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -32,7 +32,7 @@ import Text.HTML.TagSoup import Text.Pandoc.Builder (Blocks, Inlines) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class.PandocMonad (PandocMonad (..), report) -import Text.Pandoc.Definition +import Text.Pandoc.Definition as Pandoc import Text.Pandoc.Emoji (emojiToInline) import Text.Pandoc.Error import Text.Pandoc.Logging @@ -1163,7 +1163,7 @@ simpleTableHeader headless = try $ do else return rawContent let aligns = zipWith alignType (map (: []) rawHeads) lengths let rawHeads' = if headless - then replicate (length dashes) "" + then [] else rawHeads heads <- fmap sequence $ @@ -1235,7 +1235,7 @@ tableCaption = try $ do -- Parse a simple table with '---' header and one line per row. simpleTable :: PandocMonad m => Bool -- ^ Headerless table - -> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]]) + -> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row]) simpleTable headless = do (aligns, _widths, heads', lines') <- tableWith (simpleTableHeader headless) tableLine @@ -1250,7 +1250,7 @@ simpleTable headless = do -- ending with a footer (dashed line followed by blank line). multilineTable :: PandocMonad m => Bool -- ^ Headerless table - -> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]]) + -> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row]) multilineTable headless = tableWith (multilineTableHeader headless) multilineRow blanklines tableFooter @@ -1281,7 +1281,7 @@ multilineTableHeader headless = try $ do rawContent let aligns = zipWith alignType rawHeadsList lengths let rawHeads = if headless - then replicate (length dashes) "" + then [] else map (T.unlines . map trim) rawHeadsList heads <- fmap sequence $ mapM (parseFromString' (mconcat <$> many plain).trim) rawHeads @@ -1292,7 +1292,7 @@ multilineTableHeader headless = try $ do -- which may be grid, separated by blank lines, and -- ending with a footer (dashed line followed by blank line). gridTable :: PandocMonad m => Bool -- ^ Headerless table - -> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]]) + -> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row]) gridTable headless = gridTableWith' parseBlocks headless pipeBreak :: PandocMonad m => MarkdownParser m ([Alignment], [Int]) @@ -1307,7 +1307,7 @@ pipeBreak = try $ do blankline return $ unzip (first:rest) -pipeTable :: PandocMonad m => MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]]) +pipeTable :: PandocMonad m => MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row]) pipeTable = try $ do nonindentSpaces lookAhead nonspaceChar @@ -1323,7 +1323,7 @@ pipeTable = try $ do fromIntegral len / fromIntegral (sum seplengths)) seplengths else replicate (length aligns) 0.0 - return (aligns, widths, heads', sequence lines'') + return (aligns, widths, toHeaderRow <$> heads', map toRow <$> sequence lines'') sepPipe :: PandocMonad m => MarkdownParser m () sepPipe = try $ do @@ -1384,7 +1384,7 @@ tableWith :: PandocMonad m -> ([Int] -> MarkdownParser m (F [Blocks])) -> MarkdownParser m sep -> MarkdownParser m end - -> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]]) + -> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row]) tableWith headerParser rowParser lineParser footerParser = try $ do (heads, aligns, indices) <- headerParser lines' <- fmap sequence $ rowParser indices `sepEndBy1` lineParser @@ -1393,7 +1393,7 @@ tableWith headerParser rowParser lineParser footerParser = try $ do let widths = if null indices then replicate (length aligns) 0.0 else widthsFromIndices numColumns indices - return (aligns, widths, heads, lines') + return (aligns, widths, toHeaderRow <$> heads, map toRow <$> lines') table :: PandocMonad m => MarkdownParser m (F Blocks) table = try $ do @@ -1424,7 +1424,11 @@ table = try $ do caption' <- caption heads' <- heads lns' <- lns - return $ B.table caption' (zip aligns (strictPos <$> widths')) heads' lns' + return $ B.table (B.simpleCaption $ B.plain caption') + (zip aligns (strictPos <$> widths')) + (TableHead nullAttr heads') + [TableBody nullAttr 0 [] lns'] + (TableFoot nullAttr []) -- -- inline @@ -2113,3 +2117,9 @@ doubleQuoted = try $ do withQuoteContext InDoubleQuote $ fmap B.doubleQuoted . trimInlinesF . mconcat <$> many1Till inline doubleQuoteEnd + +toRow :: [Blocks] -> Pandoc.Row +toRow = Row nullAttr . map B.simpleCell + +toHeaderRow :: [Blocks] -> [Pandoc.Row] +toHeaderRow l = if null l then [] else [toRow l] diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 0396c95de..6bcc4735e 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -232,7 +232,13 @@ table = do let (headers,rows) = if hasheader then (hdr, rows') else (replicate cols mempty, hdr:rows') - return $ B.table caption cellspecs headers rows + let toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ B.table (B.simpleCaption $ B.plain caption) + cellspecs + (TableHead nullAttr $ toHeaderRow headers) + [TableBody nullAttr 0 [] $ map toRow rows] + (TableFoot nullAttr []) parseAttrs :: PandocMonad m => MWParser m [(Text,Text)] parseAttrs = many1 parseAttr diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 34a9a7367..987028910 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -645,9 +645,15 @@ data MuseTableElement = MuseHeaderRow [Blocks] museToPandocTable :: MuseTable -> Blocks museToPandocTable (MuseTable caption headers body footers) = - B.table caption attrs headRow (rows ++ body ++ footers) + B.table (B.simpleCaption $ B.plain caption) + attrs + (TableHead nullAttr $ toHeaderRow headRow) + [TableBody nullAttr 0 [] $ map toRow $ rows ++ body ++ footers] + (TableFoot nullAttr []) where attrs = (AlignDefault, ColWidthDefault) <$ transpose (headers ++ body ++ footers) (headRow, rows) = fromMaybe ([], []) $ uncons headers + toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] museAppendElement :: MuseTableElement -> MuseTable @@ -693,8 +699,13 @@ museGridTable = try $ do indent <- getIndent indices <- museGridTableHeader fmap rowsToTable . sequence <$> many1 (museGridTableRow indent indices) - where rowsToTable rows = B.table mempty attrs [] rows + where rowsToTable rows = B.table B.emptyCaption + attrs + (TableHead nullAttr []) + [TableBody nullAttr 0 [] $ map toRow rows] + (TableFoot nullAttr []) where attrs = (AlignDefault, ColWidthDefault) <$ transpose rows + toRow = Row nullAttr . map B.simpleCell -- | Parse a table. table :: PandocMonad m => MuseParser m (F Blocks) diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 5dbaa2a17..b2cf3b3ec 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -627,8 +627,14 @@ orgToPandocTable (OrgTable colProps heads lns) caption = let totalWidth = if any (isJust . columnRelWidth) colProps then Just . sum $ map (fromMaybe 1 . columnRelWidth) colProps else Nothing - in B.table caption (map (convertColProp totalWidth) colProps) heads lns + in B.table (B.simpleCaption $ B.plain caption) + (map (convertColProp totalWidth) colProps) + (TableHead nullAttr $ toHeaderRow heads) + [TableBody nullAttr 0 [] $ map toRow lns] + (TableFoot nullAttr []) where + toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, ColWidth) convertColProp totalWidth colProp = let diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 0460c43f4..4acdc10c2 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -822,10 +822,13 @@ listTableDirective top fields body = do Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $ splitTextBy (`elem` (" ," :: String)) specs _ -> replicate numOfCols ColWidthDefault - return $ B.table title + toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ B.table (B.simpleCaption $ B.plain title) (zip (replicate numOfCols AlignDefault) widths) - headerRow - bodyRows + (TableHead nullAttr $ toHeaderRow headerRow) + [TableBody nullAttr 0 [] $ map toRow bodyRows] + (TableFoot nullAttr []) where takeRows [BulletList rows] = map takeCells rows takeRows _ = [] takeCells [BulletList cells] = map B.fromList cells @@ -897,10 +900,13 @@ csvTableDirective top fields rawcsv = do $ map (fromMaybe (0 :: Double) . safeRead) $ splitTextBy (`elem` (" ," :: String)) specs _ -> replicate numOfCols ColWidthDefault - return $ B.table title - (zip (replicate numOfCols AlignDefault) widths) - headerRow - bodyRows + let toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ B.table (B.simpleCaption $ B.plain title) + (zip (replicate numOfCols AlignDefault) widths) + (TableHead nullAttr $ toHeaderRow headerRow) + [TableBody nullAttr 0 [] $ map toRow bodyRows] + (TableFoot nullAttr []) -- TODO: -- - Only supports :format: fields with a single format for :raw: roles, diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index b39e3303e..4df1de045 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -228,10 +228,16 @@ table = try $ do return $ buildTable mempty rows $ fromMaybe (align rows, columns rows) tableHead where buildTable caption rows (aligns, heads) - = B.table caption aligns heads rows + = B.table (B.simpleCaption $ B.plain caption) + aligns + (TableHead nullAttr $ toHeaderRow heads) + [TableBody nullAttr 0 [] $ map toRow rows] + (TableFoot nullAttr []) align rows = replicate (columCount rows) (AlignDefault, ColWidthDefault) columns rows = replicate (columCount rows) mempty columCount rows = length $ head rows + toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] tableParseHeader :: PandocMonad m => TWParser m ((Alignment, ColWidth), B.Blocks) tableParseHeader = try $ do diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index a0680ac81..fef192fd3 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -377,10 +377,13 @@ table = try $ do _ -> (mempty, rawrows) let nbOfCols = maximum $ map length (headers:rows) let aligns = map minimum $ transpose $ map (map (snd . fst)) (headers:rows) - return $ B.table caption + let toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ B.table (B.simpleCaption $ B.plain caption) (zip aligns (replicate nbOfCols ColWidthDefault)) - (map snd headers) - (map (map snd) rows) + (TableHead nullAttr $ toHeaderRow $ map snd headers) + [TableBody nullAttr 0 [] $ map (toRow . map snd) rows] + (TableFoot nullAttr []) -- | Ignore markers for cols, thead, tfoot. ignorableRow :: PandocMonad m => ParserT Text ParserState m () diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index fc1c8c5cf..c5c87e471 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -267,9 +267,13 @@ table = try $ do let size = maximum (map length rows') let rowsPadded = map (pad size) rows' let headerPadded = if null tableHeader then mempty else pad size tableHeader - return $ B.table mempty + let toRow = Row nullAttr . map B.simpleCell + toHeaderRow l = if null l then [] else [toRow l] + return $ B.table B.emptyCaption (zip aligns (replicate ncolumns ColWidthDefault)) - headerPadded rowsPadded + (TableHead nullAttr $ toHeaderRow headerPadded) + [TableBody nullAttr 0 [] $ map toRow rowsPadded] + (TableFoot nullAttr []) pad :: (Monoid a) => Int -> [a] -> [a] pad n xs = xs ++ replicate (n - length xs) mempty |