From e96bb43ceb561628d28a87965d539b0aae2c097b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 27 Oct 2018 23:37:18 -0700 Subject: Man reader: allow block-level content in table cells. Closes #5028. --- src/Text/Pandoc/Readers/Man.hs | 33 +++++++++++++++++++++++++-------- test/man-reader.man | 17 +++++++++++++++++ test/man-reader.native | 10 +++++++++- 3 files changed, 51 insertions(+), 9 deletions(-) diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs index 3644050c7..f2fd4b0e1 100644 --- a/src/Text/Pandoc/Readers/Man.hs +++ b/src/Text/Pandoc/Readers/Man.hs @@ -55,13 +55,15 @@ import qualified Text.Parsec as Parsec import Text.Parsec.Pos (updatePosString, initialPos) import qualified Data.Foldable as Foldable -data ManState = ManState { readerOptions :: ReaderOptions - , metadata :: Meta +data ManState = ManState { readerOptions :: ReaderOptions + , metadata :: Meta + , tableCellsPlain :: Bool } deriving Show instance Default ManState where - def = ManState { readerOptions = def - , metadata = nullMeta } + def = ManState { readerOptions = def + , metadata = nullMeta + , tableCellsPlain = True } type ManParser m = ParserT [RoffToken] ManState m @@ -111,6 +113,7 @@ parseBlock = choice [ parseList parseTable :: PandocMonad m => ManParser m Blocks parseTable = do + modifyState $ \st -> st { tableCellsPlain = True } let isMTable (MTable{}) = True isMTable _ = False MTable _opts rows pos <- msatisfy isMTable @@ -126,7 +129,12 @@ parseTable = do _ -> (([],[]), rows) headerRow <- mapM parseTableCell $ snd headerRow' bodyRows <- mapM (mapM parseTableCell . snd) bodyRows' - return $ B.table mempty (zip alignments (repeat 0.0)) + isPlainTable <- tableCellsPlain <$> getState + let widths = if isPlainTable + then repeat 0.0 + else repeat ((1.0 / fromIntegral (length alignments)) + :: Double) + return $ B.table mempty (zip alignments widths) headerRow bodyRows) <|> fallback pos [] -> fallback pos @@ -135,14 +143,23 @@ parseTable = do parseTableCell ts = do st <- getState let ts' = Foldable.toList $ unRoffTokens ts - let tcell = try $ do + let plaintcell = try $ do skipMany memptyLine plain . trimInlines <$> (parseInlines <* eof) + let blockstcell = try $ do + skipMany memptyLine + mconcat <$> many parseBlock <* eof res <- if null ts' then return $ Right mempty - else lift $ readWithMTokens tcell st ts' + else lift $ readWithMTokens plaintcell st ts' case res of - Left _ -> fail "Could not parse table cell" + Left _ -> do + res' <- lift $ readWithMTokens blockstcell st ts' + case res' of + Left _ -> fail "Could not parse table cell" + Right x -> do + modifyState $ \s -> s{ tableCellsPlain = False } + return x Right x -> return x isHrule :: TableRow -> Bool diff --git a/test/man-reader.man b/test/man-reader.man index 6f2e763ab..95d1a9d71 100644 --- a/test/man-reader.man +++ b/test/man-reader.man @@ -372,3 +372,20 @@ T}@T{ 1 T} .TE +.TS +tab(@); +rl. +a@b +T{ +.PP +one +.PP +two +T}@T{ +.nf +some + code +.fi +T} +.TE + diff --git a/test/man-reader.native b/test/man-reader.native index 4dc1f4c77..99c7405f8 100644 --- a/test/man-reader.native +++ b/test/man-reader.native @@ -169,4 +169,12 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "Oct",Space,Str "17,", ,[[Plain [Str "1"]] ,[Plain [Str "1"]] ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]]] + ,[Plain [Str "1"]]]] +,Table [] [AlignRight,AlignLeft] [0.5,0.5] + [[] + ,[]] + [[[Plain [Str "a"]] + ,[Plain [Str "b"]]] + ,[[Para [Str "one"] + ,Para [Str "two"]] + ,[CodeBlock ("",[],[]) "some\n code"]]]] -- cgit v1.2.3