diff --git a/src/Text/Pandoc/Readers/Mdoc.hs b/src/Text/Pandoc/Readers/Mdoc.hs index d4874faf2743..db094ad3bda5 100644 --- a/src/Text/Pandoc/Readers/Mdoc.hs +++ b/src/Text/Pandoc/Readers/Mdoc.hs @@ -95,6 +95,7 @@ data MdocState = MdocState , tableCellsPlain :: Bool , spacingMode :: Bool , authorNameSplit :: Bool + , inLineEnclosure :: Bool , progName :: Maybe T.Text , currentSection :: MdocSection , currentReference :: MdocReference @@ -110,6 +111,7 @@ instance Default MdocState where , tableCellsPlain = True , spacingMode = True , authorNameSplit = False + , inLineEnclosure = False , currentSection = ShOther , currentReference = M.empty , progName = Nothing @@ -268,7 +270,6 @@ parseHeader :: PandocMonad m => MdocParser m Blocks parseHeader = do (Macro m _) <- lookAhead $ macro "Sh" <|> macro "Ss" txt <- lineEnclosure m id - eol let lvl = if m == "Sh" then 1 else 2 when (lvl == 1) $ modifyState $ \s -> s{currentSection = (shToSectionMode . stringify) txt} return $ B.header lvl txt @@ -403,14 +404,19 @@ spanLikeInline nm = simpleInline nm (eliminateEmpty (B.spanWith (cls nm))) lineEnclosure :: PandocMonad m => T.Text -> (Inlines -> Inlines) -> MdocParser m Inlines lineEnclosure nm xform = do macro nm + amNested <- inLineEnclosure <$> getState + modifyState $ \s -> s{inLineEnclosure = True} --- XXX wtf - (first, further, finally) <- delimitedArgs + first <- openingDelimiters + further <- (manyTill (parseInlineMacro <|> (try (litsAndDelimsToInlines <* notFollowedBy eol)) <|> litsToInlines) (try (lookAhead (many (macro "Ns" <|> delim Close) *> eol)))) further' <- spacify further + finally <- if amNested then mempty else closingDelimiters <* optional eol + modifyState $ \s -> s{inLineEnclosure = amNested} return $ first <> xform further' <> finally noSpace :: Inlines @@ -469,12 +475,15 @@ but pandoc inlines inside of these multiline enclosures. -} multilineEnclosure :: PandocMonad m => T.Text -> T.Text -> (Inlines -> Inlines) -> MdocParser m Inlines multilineEnclosure op cl xform = do macro op + amNested <- inLineEnclosure <$> getState openDelim <- mconcat <$> many (parseDelim Open) optional eol contents <- many parseInline (macro cl show cl) - closeDelim <- mconcat <$> many (parseDelim Close) - optional eol + closeDelim <- + if amNested + then mempty + else mconcat <$> many (parseDelim Close) <* optional eol contents' <- spacify contents return $ openDelim <> xform contents' <> closeDelim @@ -654,13 +663,11 @@ parseAo = multilineEnclosure "Ao" "Ac" $ \x -> "⟨" <> x <> "⟩" parseDl :: PandocMonad m => MdocParser m Blocks parseDl = do inner <- lineEnclosure "Dl" id - eol return $ B.codeBlock (stringify inner) parseD1 :: PandocMonad m => MdocParser m Blocks parseD1 = do inner <- lineEnclosure "D1" id - eol return $ B.divWith (cls "display") $ B.plain inner parseNm :: PandocMonad m => MdocParser m Inlines diff --git a/test/Tests/Readers/Mdoc.hs b/test/Tests/Readers/Mdoc.hs index 381830454425..ec854654ea5c 100644 --- a/test/Tests/Readers/Mdoc.hs +++ b/test/Tests/Readers/Mdoc.hs @@ -48,6 +48,12 @@ tests = [ , "nested" =: ".Dq Pq hello world" =?> para (doubleQuoted "(hello world)") + , "nested with closing delimiters" =: + ".Dq Pq hi mom !" =?> + para (doubleQuoted "(hi mom)" <> "!") + , "nested multiline enclosure" =: + ".Dq Po a \\&; b \\&; c Pc ." =?> + para (doubleQuoted "(a ; b ; c)" <> ".") , "with inlines" =: ".Dq hello Sy world ." =?> para (doubleQuoted ("hello" <> space <> strong "world" <> ".")) @@ -65,6 +71,9 @@ tests = [ , "nested on one line" =: ".Bo Po hi Pc Bc" =?> para ("[(hi)]") + , "with wacky delimiters" =: + ".Bo ( | hi ! Bc ?" =?> + para ("([| hi!]?") ] , testGroup "simple inlines" [ "Sy" =: