diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 45 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 18 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 19 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TWiki.hs | 22 |
4 files changed, 41 insertions, 63 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 847fd2e05..2f6189104 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -105,8 +105,9 @@ module Text.Pandoc.Parsing ( take1WhileP, singleQuoteEnd, doubleQuoteStart, doubleQuoteEnd, - ellipses, apostrophe, + doubleCloseQuote, + ellipses, dash, nested, citeKey, @@ -1398,10 +1399,7 @@ smartPunctuation :: (HasReaderOptions st, HasLastStrPosition st, HasQuoteContext -> ParserT s st m Inlines smartPunctuation inlineParser = do guardEnabled Ext_smart - choice [ quoted inlineParser, apostrophe, dash, ellipses ] - -apostrophe :: Stream s m Char => ParserT s st m Inlines -apostrophe = (char '\'' <|> char '\8217') >> return (B.str "\x2019") + choice [ quoted inlineParser, apostrophe, doubleCloseQuote, dash, ellipses ] quoted :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) => ParserT s st m Inlines @@ -1411,16 +1409,22 @@ quoted inlineParser = doubleQuoted inlineParser <|> singleQuoted inlineParser singleQuoted :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) => ParserT s st m Inlines -> ParserT s st m Inlines -singleQuoted inlineParser = try $ B.singleQuoted . mconcat - <$ singleQuoteStart - <*> withQuoteContext InSingleQuote (many1Till inlineParser singleQuoteEnd) - -doubleQuoted :: (HasQuoteContext st m, Stream s m Char) +singleQuoted inlineParser = do + singleQuoteStart + (B.singleQuoted . mconcat <$> + try + (withQuoteContext InSingleQuote (many1Till inlineParser singleQuoteEnd))) + <|> pure "\8217" + +doubleQuoted :: (HasQuoteContext st m, HasLastStrPosition st, Stream s m Char) => ParserT s st m Inlines -> ParserT s st m Inlines -doubleQuoted inlineParser = try $ B.doubleQuoted . mconcat - <$ doubleQuoteStart - <*> withQuoteContext InDoubleQuote (manyTill inlineParser doubleQuoteEnd) +doubleQuoted inlineParser = do + doubleQuoteStart + (B.doubleQuoted . mconcat <$> + try + (withQuoteContext InDoubleQuote (manyTill inlineParser doubleQuoteEnd))) + <|> pure (B.str "\8220") failIfInQuoteContext :: (HasQuoteContext st m, Stream s m t) => QuoteContext @@ -1443,7 +1447,7 @@ singleQuoteStart = do guard =<< notAfterString try $ do charOrRef "'\8216\145" - notFollowedBy (oneOf [' ', '\t', '\n']) + notFollowedBy (satisfy isSpaceChar) singleQuoteEnd :: Stream s m Char => ParserT s st m () @@ -1451,17 +1455,26 @@ singleQuoteEnd = try $ do charOrRef "'\8217\146" notFollowedBy alphaNum -doubleQuoteStart :: (HasQuoteContext st m, Stream s m Char) +doubleQuoteStart :: (HasLastStrPosition st, + HasQuoteContext st m, + Stream s m Char) => ParserT s st m () doubleQuoteStart = do failIfInQuoteContext InDoubleQuote + guard =<< notAfterString try $ do charOrRef "\"\8220\147" - notFollowedBy (oneOf [' ', '\t', '\n']) + notFollowedBy (satisfy isSpaceChar) doubleQuoteEnd :: Stream s m Char => ParserT s st m () doubleQuoteEnd = void (charOrRef "\"\8221\148") +apostrophe :: Stream s m Char => ParserT s st m Inlines +apostrophe = (char '\'' <|> char '\8217') >> return (B.str "\8217") + +doubleCloseQuote :: Stream s m Char => ParserT s st m Inlines +doubleCloseQuote = B.str "\8221" <$ char '"' + ellipses :: Stream s m Char => ParserT s st m Inlines ellipses = try (string "..." >> return (B.str "\8230")) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 4b20e3a8b..ba8ed147e 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -2199,25 +2199,27 @@ citation = try $ do smart :: PandocMonad m => MarkdownParser m (F Inlines) smart = do guardEnabled Ext_smart - doubleQuoted <|> singleQuoted <|> - choice (map (return <$>) [apostrophe, dash, ellipses]) + doubleQuoted <|> singleQuoted <|> (return <$> doubleCloseQuote) <|> + (return <$> apostrophe) <|> (return <$> dash) <|> (return <$> ellipses) singleQuoted :: PandocMonad m => MarkdownParser m (F Inlines) -singleQuoted = try $ do +singleQuoted = do singleQuoteStart - withQuoteContext InSingleQuote $ + (try (withQuoteContext InSingleQuote $ fmap B.singleQuoted . trimInlinesF . mconcat <$> - many1Till inline singleQuoteEnd + many1Till inline singleQuoteEnd)) + <|> (return (return (B.str "\8217"))) -- doubleQuoted will handle regular double-quoted sections, as well -- as dialogues with an open double-quote without a close double-quote -- in the same paragraph. doubleQuoted :: PandocMonad m => MarkdownParser m (F Inlines) -doubleQuoted = try $ do +doubleQuoted = do doubleQuoteStart - withQuoteContext InDoubleQuote $ + (try (withQuoteContext InDoubleQuote $ fmap B.doubleQuoted . trimInlinesF . mconcat <$> - many1Till inline doubleQuoteEnd + many1Till inline doubleQuoteEnd)) + <|> (return (return (B.str "\8220"))) toRow :: [Blocks] -> Row toRow = Row nullAttr . map B.simpleCell diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 514e3b88d..ac4c0b6cb 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -1658,21 +1658,4 @@ note = try $ do return $ B.note contents smart :: PandocMonad m => RSTParser m Inlines -smart = do - guardEnabled Ext_smart - doubleQuoted <|> singleQuoted <|> - choice [apostrophe, dash, ellipses] - -singleQuoted :: PandocMonad m => RSTParser m Inlines -singleQuoted = try $ do - singleQuoteStart - withQuoteContext InSingleQuote $ - B.singleQuoted . trimInlines . mconcat <$> - many1Till inline singleQuoteEnd - -doubleQuoted :: PandocMonad m => RSTParser m Inlines -doubleQuoted = try $ do - doubleQuoteStart - withQuoteContext InDoubleQuote $ - B.doubleQuoted . trimInlines . mconcat <$> - many1Till inline doubleQuoteEnd +smart = smartPunctuation inline diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index 484a6c923..c4d7bcc93 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -469,27 +469,7 @@ symbol :: PandocMonad m => TWParser m B.Inlines symbol = B.str <$> countChar 1 nonspaceChar smart :: PandocMonad m => TWParser m B.Inlines -smart = do - guardEnabled Ext_smart - doubleQuoted <|> singleQuoted <|> - choice [ apostrophe - , dash - , ellipses - ] - -singleQuoted :: PandocMonad m => TWParser m B.Inlines -singleQuoted = try $ do - singleQuoteStart - withQuoteContext InSingleQuote - (B.singleQuoted . B.trimInlines . mconcat <$> many1Till inline singleQuoteEnd) - -doubleQuoted :: PandocMonad m => TWParser m B.Inlines -doubleQuoted = try $ do - doubleQuoteStart - contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline) - withQuoteContext InDoubleQuote (doubleQuoteEnd >> - return (B.doubleQuoted $ B.trimInlines contents)) - <|> return (B.str "\8220" B.<> contents) +smart = smartPunctuation inline link :: PandocMonad m => TWParser m B.Inlines link = try $ do |