aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2024-08-29 10:39:46 -0700
committerJohn MacFarlane <[email protected]>2024-08-29 10:41:52 -0700
commita0bc3a574e7e6bcdbba043316c2f5816b11b7d46 (patch)
tree406a539a2211e2a8ff3858cce4c0e9b88564ec27 /src/Text
parent54452e71fd6a3a5beda354207685b41ebeba52fc (diff)
RST reader: improve simple table support.
Multiline rows occur only when the *first* cell is empty; we were previously treating lines with *any* empty cell as row continuations. Closes #10093. In addition, we no longer wrap multiline cells in Para if they can be represented as Plain. This is consistent with docutils behavior.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/RST.hs30
1 files changed, 18 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 76ead049f..ce8a83628 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -884,12 +884,6 @@ csvTableDirective top fields rawcsv = do
Left e ->
throwError $ fromParsecError (toSources rawcsv') e
Right rawrows -> do
- let singleParaToPlain bs =
- case B.toList bs of
- [Para ils] -> B.fromList [Plain ils]
- _ -> bs
- let parseCell t = singleParaToPlain
- <$> parseFromString' parseBlocks (t <> "\n\n")
let parseRow = mapM parseCell
rows <- mapM parseRow rawrows
let (headerRow,bodyRows,numOfCols) =
@@ -918,6 +912,17 @@ csvTableDirective top fields rawcsv = do
[TableBody nullAttr 0 [] $ map toRow bodyRows]
(TableFoot nullAttr [])
+singleParaToPlain :: Blocks -> Blocks
+singleParaToPlain bs =
+ case B.toList bs of
+ [Para ils] -> B.fromList [Plain ils]
+ _ -> bs
+
+parseCell :: PandocMonad m => Text -> RSTParser m Blocks
+parseCell t = singleParaToPlain
+ <$> parseFromString' parseBlocks (t <> "\n\n")
+
+
-- TODO:
-- - Only supports :format: fields with a single format for :raw: roles,
-- change Text.Pandoc.Definition.Format to fix
@@ -1285,23 +1290,24 @@ simpleTableFooter = try $ simpleTableSep '=' >> blanklines
simpleTableRawLine :: Monad m => [Int] -> RSTParser m [Text]
simpleTableRawLine indices = simpleTableSplitLine indices <$> anyLine
-simpleTableRawLineWithEmptyCell :: Monad m => [Int] -> RSTParser m [Text]
-simpleTableRawLineWithEmptyCell indices = try $ do
+simpleTableRawLineWithInitialEmptyCell :: Monad m => [Int] -> RSTParser m [Text]
+simpleTableRawLineWithInitialEmptyCell indices = try $ do
cs <- simpleTableRawLine indices
let isEmptyCell = T.all (\c -> c == ' ' || c == '\t')
- guard $ any isEmptyCell cs
- return cs
+ case cs of
+ c:_ | isEmptyCell c -> return cs
+ _ -> mzero
-- Parse a table row and return a list of blocks (columns).
simpleTableRow :: PandocMonad m => [Int] -> RSTParser m [Blocks]
simpleTableRow indices = do
notFollowedBy' simpleTableFooter
firstLine <- simpleTableRawLine indices
- conLines <- many $ simpleTableRawLineWithEmptyCell indices
+ conLines <- many $ simpleTableRawLineWithInitialEmptyCell indices
let cols = map T.unlines . transpose $ firstLine : conLines ++
[replicate (length indices) ""
| not (null conLines)]
- mapM (parseFromString' parseBlocks) cols
+ mapM parseCell cols
simpleTableSplitLine :: [Int] -> Text -> [Text]
simpleTableSplitLine indices line =