diff options
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 43 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Shared.hs | 46 | ||||
-rw-r--r-- | test/command/3516.md | 15 | ||||
-rw-r--r-- | test/tables-rstsubset.native | 12 | ||||
-rw-r--r-- | test/tables.rst | 60 |
5 files changed, 91 insertions, 85 deletions
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index d4a537d72..24898d62e 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -33,7 +33,7 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html> module Text.Pandoc.Writers.RST ( writeRST ) where import Control.Monad.State import Data.Char (isSpace, toLower) -import Data.List (intersperse, isPrefixOf, stripPrefix, transpose) +import Data.List (isPrefixOf, stripPrefix) import Data.Maybe (fromMaybe) import Network.URI (isURI) import qualified Text.Pandoc.Builder as B @@ -269,39 +269,18 @@ blockToRST (BlockQuote blocks) = do tabstop <- gets $ writerTabStop . stOptions contents <- blockListToRST blocks return $ (nest tabstop contents) <> blankline -blockToRST (Table caption _ widths headers rows) = do +blockToRST (Table caption aligns widths headers rows) = do caption' <- inlineListToRST caption - headers' <- mapM blockListToRST headers - rawRows <- mapM (mapM blockListToRST) rows - -- let isSimpleCell [Plain _] = True - -- isSimpleCell [Para _] = True - -- isSimpleCell [] = True - -- isSimpleCell _ = False - -- let isSimple = all (==0) widths && all (all isSimpleCell) rows - let numChars = maximum . map offset + let blocksToDoc opts bs = do + oldOpts <- gets stOptions + modify $ \st -> st{ stOptions = opts } + result <- blockListToRST bs + modify $ \st -> st{ stOptions = oldOpts } + return result opts <- gets stOptions - let widthsInChars = - if all (== 0) widths - then map ((+2) . numChars) $ transpose (headers' : rawRows) - else map (floor . (fromIntegral (writerColumns opts) *)) widths - let hpipeBlocks blocks = hcat [beg, middle, end] - where h = height (hcat blocks) - sep' = lblock 3 $ vcat (map text $ replicate h " | ") - beg = lblock 2 $ vcat (map text $ replicate h "| ") - end = lblock 2 $ vcat (map text $ replicate h " |") - middle = hcat $ intersperse sep' blocks - let makeRow = hpipeBlocks . zipWith lblock widthsInChars - let head' = makeRow headers' - let rows' = map makeRow rawRows - let border ch = char '+' <> char ch <> - (hcat $ intersperse (char ch <> char '+' <> char ch) $ - map (\l -> text $ replicate l ch) widthsInChars) <> - char ch <> char '+' - let body = vcat $ intersperse (border '-') rows' - let head'' = if all null headers - then empty - else head' $$ border '=' - let tbl = border '-' $$ head'' $$ body $$ border '-' + tbl <- gridTable opts blocksToDoc (all null headers) + (map (const AlignDefault) aligns) widths + headers rows return $ if null caption then tbl $$ blankline else (".. table:: " <> caption') $$ blankline $$ nest 3 tbl $$ diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index 520df1037..3b28c58c8 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -46,7 +46,7 @@ import Control.Monad (liftM, zipWithM) import Data.Aeson (FromJSON (..), Result (..), ToJSON (..), Value (Object), encode, fromJSON) import qualified Data.HashMap.Strict as H -import Data.List (groupBy, intersperse) +import Data.List (groupBy, intersperse, transpose) import qualified Data.Map as M import Data.Maybe (isJust) import qualified Data.Text as T @@ -229,22 +229,34 @@ gridTable :: Monad m gridTable opts blocksToDoc headless aligns widths headers rows = do let numcols = maximum (length aligns : length widths : map length (headers:rows)) - let widths' = if all (==0) widths - then replicate numcols - (1.0 / fromIntegral numcols) - else widths - let widthsInChars = map ((\x -> x - 3) . floor . - (fromIntegral (writerColumns opts) *)) widths' - rawHeaders <- zipWithM blocksToDoc - (map (\w -> opts{writerColumns = - min (w - 2) (writerColumns opts)}) widthsInChars) - headers - rawRows <- mapM - (\cs -> zipWithM blocksToDoc - (map (\w -> opts{writerColumns = - min (w - 2) (writerColumns opts)}) widthsInChars) - cs) - rows + let handleGivenWidths widths' = do + let widthsInChars' = map ((\x -> x - 3) . floor . + (fromIntegral (writerColumns opts) *)) widths' + rawHeaders' <- zipWithM blocksToDoc + (map (\w -> opts{writerColumns = + min (w - 2) (writerColumns opts)}) widthsInChars') + headers + rawRows' <- mapM + (\cs -> zipWithM blocksToDoc + (map (\w -> opts{writerColumns = + min (w - 2) (writerColumns opts)}) widthsInChars') + cs) + rows + return (widthsInChars', rawHeaders', rawRows') + let handleZeroWidths = do + rawHeaders' <- mapM (blocksToDoc opts) headers + rawRows' <- mapM (mapM (blocksToDoc opts)) rows + let numChars = maximum . map offset + let widthsInChars' = + map ((+2) . numChars) $ transpose (rawHeaders' : rawRows') + if sum widthsInChars' > writerColumns opts + then -- use even widths + handleGivenWidths + (replicate numcols (1.0 / fromIntegral numcols) :: [Double]) + else return (widthsInChars', rawHeaders', rawRows') + (widthsInChars, rawHeaders, rawRows) <- if all (== 0) widths + then handleZeroWidths + else handleGivenWidths widths let hpipeBlocks blocks = hcat [beg, middle, end] where h = maximum (1 : map height blocks) sep' = lblock 3 $ vcat (map text $ replicate h " | ") diff --git a/test/command/3516.md b/test/command/3516.md new file mode 100644 index 000000000..d547ddbb1 --- /dev/null +++ b/test/command/3516.md @@ -0,0 +1,15 @@ +Correctly handle empty row: +``` +% pandoc -f markdown -t rst ++---+---+ +| 1 | 2 | ++---+---+ +| | | ++---+---+ +^D ++---+---+ +| 1 | 2 | ++---+---+ +| | | ++---+---+ +``` diff --git a/test/tables-rstsubset.native b/test/tables-rstsubset.native index 65ced24af..4f095c798 100644 --- a/test/tables-rstsubset.native +++ b/test/tables-rstsubset.native @@ -53,7 +53,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625] +,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] [[Plain [Str "Centered",Space,Str "Header"]] ,[Plain [Str "Left",Space,Str "Aligned"]] ,[Plain [Str "Right",Space,Str "Aligned"]] @@ -65,9 +65,9 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625] +,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] [[Plain [Str "Centered",Space,Str "Header"]] ,[Plain [Str "Left",Space,Str "Aligned"]] ,[Plain [Str "Right",Space,Str "Aligned"]] @@ -79,7 +79,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,0.1,0.1,0.1] [[] @@ -99,7 +99,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625] +,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] [[] ,[] ,[] @@ -111,4 +111,4 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]]] diff --git a/test/tables.rst b/test/tables.rst index 184d9894a..eaef50d28 100644 --- a/test/tables.rst +++ b/test/tables.rst @@ -42,31 +42,31 @@ Multiline table with caption: .. table:: Here’s the caption. It may span multiple lines. - +-------------+------------+--------------+----------------------------+ - | Centered | Left | Right | Default aligned | - | Header | Aligned | Aligned | | - +=============+============+==============+============================+ - | First | row | 12.0 | Example of a row that | - | | | | spans multiple lines. | - +-------------+------------+--------------+----------------------------+ - | Second | row | 5.0 | Here’s another one. Note | - | | | | the blank line between | - | | | | rows. | - +-------------+------------+--------------+----------------------------+ + +----------+---------+-----------+-------------------------+ + | Centered | Left | Right | Default aligned | + | Header | Aligned | Aligned | | + +==========+=========+===========+=========================+ + | First | row | 12.0 | Example of a row that | + | | | | spans multiple lines. | + +----------+---------+-----------+-------------------------+ + | Second | row | 5.0 | Here’s another one. | + | | | | Note the blank line | + | | | | between rows. | + +----------+---------+-----------+-------------------------+ Multiline table without caption: -+-------------+------------+--------------+----------------------------+ -| Centered | Left | Right | Default aligned | -| Header | Aligned | Aligned | | -+=============+============+==============+============================+ -| First | row | 12.0 | Example of a row that | -| | | | spans multiple lines. | -+-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here’s another one. Note | -| | | | the blank line between | -| | | | rows. | -+-------------+------------+--------------+----------------------------+ ++----------+---------+-----------+-------------------------+ +| Centered | Left | Right | Default aligned | +| Header | Aligned | Aligned | | ++==========+=========+===========+=========================+ +| First | row | 12.0 | Example of a row that | +| | | | spans multiple lines. | ++----------+---------+-----------+-------------------------+ +| Second | row | 5.0 | Here’s another one. | +| | | | Note the blank line | +| | | | between rows. | ++----------+---------+-----------+-------------------------+ Table without column headers: @@ -80,11 +80,11 @@ Table without column headers: Multiline table without column headers: -+-------------+------------+--------------+----------------------------+ -| First | row | 12.0 | Example of a row that | -| | | | spans multiple lines. | -+-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here’s another one. Note | -| | | | the blank line between | -| | | | rows. | -+-------------+------------+--------------+----------------------------+ ++----------+---------+-----------+-------------------------+ +| First | row | 12.0 | Example of a row that | +| | | | spans multiple lines. | ++----------+---------+-----------+-------------------------+ +| Second | row | 5.0 | Here’s another one. | +| | | | Note the blank line | +| | | | between rows. | ++----------+---------+-----------+-------------------------+ |