diff options
| -rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 87 | ||||
| -rw-r--r-- | test/command/10127.md | 345 |
2 files changed, 412 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 8f4e7783e..cfae285ba 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -343,7 +343,7 @@ blockToRST (Table _attrs blkCapt specs thead tbody tfoot) = do renderGrid = gridTable opts blocksToDoc specs' thead tbody tfoot isSimple = all (== 0) widths && length widths > 1 renderSimple = do - tbl' <- simpleTable opts blocksToDoc headers rows + tbl' <- simpleTable opts blocksToDoc thead tbody tfoot if offset tbl' > writerColumns opts then renderGrid else return tbl' @@ -918,25 +918,76 @@ imageDimsToRST attr = do simpleTable :: PandocMonad m => WriterOptions -> (WriterOptions -> [Block] -> m (Doc Text)) - -> [[Block]] - -> [[[Block]]] + -> TableHead + -> [TableBody] + -> TableFoot -> m (Doc Text) -simpleTable opts blocksToDoc headers rows = do - -- can't have empty cells in first column: - let fixEmpties (d:ds) = if isEmpty d - then literal "\\ " : ds - else d : ds - fixEmpties [] = [] - headerDocs <- if all null headers +simpleTable opts blocksToDoc (TableHead _ headers) tbody (TableFoot _ footers) = do + headerDocs <- if all isEmptyRow headers then return [] - else fixEmpties <$> mapM (blocksToDoc opts) headers - rowDocs <- mapM (fmap fixEmpties . mapM (blocksToDoc opts)) rows - let numChars = maybe 0 maximum . NE.nonEmpty . map offset - let colWidths = map numChars $ transpose (headerDocs : rowDocs) - let toRow = mconcat . intersperse (lblock 1 " ") . zipWith lblock colWidths + else fixEmpties <$> mapM rowToDoc headers + rowDocs <- fixEmpties <$> mapM rowToDoc ((concatMap tableBodyToRows tbody) ++ footers) + let numChars = maybe 0 maximum . NE.nonEmpty . map (offset . fst) + let colWidths = map numChars $ transpose (headerDocs ++ rowDocs) let hline = nowrap $ hsep (map (\n -> literal (T.replicate n "=")) colWidths) - let hdr = if all null headers + let hdr = if all isEmptyRow headers then mempty - else hline $$ toRow headerDocs - let bdy = vcat $ map toRow rowDocs + else hline $$ mapToRow colWidths headerDocs + let bdy = mapToRow colWidths rowDocs return $ hdr $$ hline $$ bdy $$ hline + where + isEmptyRow (Row _ cells) = all isEmptyCell cells + + isEmptyCell (Cell _ _ _ _ blocks) = null blocks + + -- can't have empty cells in first column: + fixEmpties (d:ds) = fixEmpties' d : ds + fixEmpties [] = [] + + fixEmpties' ((d, colSpan):ds) = if isEmpty d + then (literal "\\ ", colSpan) : ds + else (d, colSpan) : ds + fixEmpties' [] = [] + + rowToDoc (Row _ cells) = concat <$> mapM cellToDocs cells + + cellToDocs (Cell _ _ _ colSpan blocks) = applyColSpan colSpan <$> (blocksToDoc opts) blocks + + tableBodyToRows (TableBody _ _ headerRows bodyRows) = headerRows ++ bodyRows + + applyColSpan col@(ColSpan colSpan) doc + | colSpan > 1 = + -- Fill up columns for the col spans by adding empty docs without a ColSpan. + let emptyDoc = (literal "", Nothing) + in (doc, Just col) : replicate (colSpan - 1) emptyDoc + | otherwise = [(doc, Just col)] + + mapToRow colWidths = vcat . concatMap (toRow colWidths) + + toRow colWidths rowDocsWithColSpans = + let (rowDocs, colSpans) = unzip rowDocsWithColSpans + row = intersperseDivider $ zipWith lblock colWidths rowDocs + colSpanRow = intersperseDivider $ writeColSpans colSpans colWidths + in if any (maybe False (> 1)) colSpans + then [row, colSpanRow] + else [row] -- Don't write out col spans if they are all just 1. + + intersperseDivider = mconcat . intersperse (lblock 1 " ") + + -- Write col span dashes to match the length of the col widths. + writeColSpans [] _ = [] + writeColSpans _ [] = [] + writeColSpans (Nothing : remainingColSpans) colWidths = writeColSpans remainingColSpans colWidths + writeColSpans (Just (ColSpan colSpan) : remainingColSpans) colWidths = + let (colWidths', remainingColWidths) = splitAt colSpan colWidths + in writeColSpanDashes colWidths' : writeColSpans remainingColSpans remainingColWidths + + writeColSpanDashes colWidths = + let colWidthsLength = length colWidths + colWidthsSum = sum colWidths + dashLength = if colWidthsLength > 1 + -- Offset by 1 for the white spaces between columns so that the col + -- span dashes align with the end of the columns correctly. + then colWidthsSum + colWidthsLength - 1 + else colWidthsSum + in literal $ T.replicate dashLength "-" diff --git a/test/command/10127.md b/test/command/10127.md index 486ef6120..cb7d4639e 100644 --- a/test/command/10127.md +++ b/test/command/10127.md @@ -1,3 +1,5 @@ +RST Reader + ``` % pandoc -f rst -t native ===== ===== ====== @@ -24,7 +26,7 @@ Full column row ---------------------------------------------------- Row with Col spans For visual separation --------------- ------------ --------------------- -Row with col span 1 On the left +Row with col span 2 On the left ----------------------------- --------------------- Final row =============== ============ ===================== @@ -335,7 +337,7 @@ Final row , Space , Str "span" , Space - , Str "1" + , Str "2" ] ] , Cell @@ -370,3 +372,342 @@ Final row (TableFoot ( "" , [] , [] ) []) ] ``` + +RST Writer +``` +% pandoc -f native -t rst +[ Table + ( "" , [] , [] ) + (Caption Nothing []) + [ ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + ] + (TableHead + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 2) + [ Plain [ Str "Inputs" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Output" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "A" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "B" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "A" , Space , Str "or" , Space , Str "B" ] + ] + ] + ]) + [ TableBody + ( "" , [] , [] ) + (RowHeadColumns 0) + [] + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "False" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "False" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "False" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "False" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "False" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "True" ] ] + ] + ] + ] + (TableFoot ( "" , [] , [] ) []) +, Table + ( "" , [] , [] ) + (Caption Nothing []) + [ ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + , ( AlignDefault , ColWidthDefault ) + ] + (TableHead + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 3) + [ Plain + [ Str "Full" + , Space + , Str "column" + , Space + , Str "header" + ] + ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "One" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "Two" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Header" , Space , Str "3" ] ] + ] + ]) + [ TableBody + ( "" , [] , [] ) + (RowHeadColumns 0) + [] + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Row" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 2) + [ Plain + [ Str "With" + , Space + , Str "col" + , Space + , Str "span" + , Space + , Str "2" + , Space + , Str "on" + , Space + , Str "the" + , Space + , Str "right" + ] + ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 3) + [ Plain + [ Str "Full" + , Space + , Str "column" + , Space + , Str "row" + ] + ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 2) + [ Plain + [ Str "Row" + , Space + , Str "with" + , Space + , Str "col" + , Space + , Str "span" + , Space + , Str "2" + ] + ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain + [ Str "On" + , Space + , Str "the" + , Space + , Str "left" + ] + ] + ] + , Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Final" , Space , Str "row" ] ] + , Cell + ( "" , [] , [] ) AlignDefault (RowSpan 1) (ColSpan 1) [] + , Cell + ( "" , [] , [] ) AlignDefault (RowSpan 1) (ColSpan 1) [] + ] + ] + ] + (TableFoot + ( "" , [] , [] ) + [ Row + ( "" , [] , [] ) + [ Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "Footer" , Space , Str "Row" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "at" , Space , Str "the" ] ] + , Cell + ( "" , [] , [] ) + AlignDefault + (RowSpan 1) + (ColSpan 1) + [ Plain [ Str "bottom" ] ] + ] + ]) +] +^D +====== ===== ====== +Inputs Output +------------ ------ +A B A or B +====== ===== ====== +False False False +True False True +False True True +True True True +====== ===== ====== + +=================== ============================ =========== +Full column header +------------------------------------------------------------ +Header One Header Two Header 3 +=================== ============================ =========== +Row With col span 2 on the right +------------------- ---------------------------------------- +Full column row +------------------------------------------------------------ +Row with col span 2 On the left +------------------------------------------------ ----------- +Final row +Footer Row at the bottom +=================== ============================ =========== +``` |
