aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Parsing.hs45
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs18
-rw-r--r--src/Text/Pandoc/Readers/RST.hs19
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs22
-rw-r--r--test/Tests/Readers/Markdown.hs2
-rw-r--r--test/command/7216.md19
-rw-r--r--test/command/pandoc-citeproc-320a.md12
7 files changed, 67 insertions, 70 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
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index 0930deae6..6e38da21a 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -358,7 +358,7 @@ tests = [ testGroup "inline code"
para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
, test markdownSmart "unclosed double quote"
("**this should \"be bold**"
- =?> para (strong "this should \"be bold"))
+ =?> para (strong "this should \8220be bold"))
]
, testGroup "footnotes"
[ "indent followed by newline and flush-left text" =:
diff --git a/test/command/7216.md b/test/command/7216.md
new file mode 100644
index 000000000..cab3b9689
--- /dev/null
+++ b/test/command/7216.md
@@ -0,0 +1,19 @@
+```
+pandoc -t latex
+"This is some text in quotes. Another paragraph by the same speaker follows. The first paragraph should have no close quote.
+
+"The second paragraph should have open and close quotes."
+
+| "Open quote on this line,
+| Close quote on the next line."
+| "Quotes on the same line."
+^D
+``This is some text in quotes. Another paragraph by the same speaker
+follows. The first paragraph should have no close quote.
+
+``The second paragraph should have open and close quotes.''
+
+``Open quote on this line,\\
+Close quote on the next line.''\\
+``Quotes on the same line.''
+```
diff --git a/test/command/pandoc-citeproc-320a.md b/test/command/pandoc-citeproc-320a.md
index 79dacfa10..e894a2250 100644
--- a/test/command/pandoc-citeproc-320a.md
+++ b/test/command/pandoc-citeproc-320a.md
@@ -49,17 +49,13 @@ references:
Foo [@item1; @item2; @item3; @item4; @item5; @item6; @item7; @item8].
^D
Foo (al-ʾUdhrī, n.d.; al-ʿUdhrī, n.d.; al-\'Udhrī, n.d.; al-'Udhrī,
-n.d.; al-'Udhrī, n.d.; Uch, n.d.; Uebel, n.d.; Zzz, n.d.).
+n.d.a, n.d.b; Uch, n.d.; Uebel, n.d.; Zzz, n.d.).
::: {#refs .references .csl-bib-body .hanging-indent}
::: {#ref-item6 .csl-entry}
Uch, Ann. n.d.
:::
-::: {#ref-item4 .csl-entry}
-'Udhrī, Jamīl al-. n.d.
-:::
-
::: {#ref-item1 .csl-entry}
ʾUdhrī, Jamīl al-. n.d.
:::
@@ -72,8 +68,12 @@ Uch, Ann. n.d.
\'Udhrī, Jamīl al-. n.d.
:::
+::: {#ref-item4 .csl-entry}
+'Udhrī, Jamīl al-. n.d.a.
+:::
+
::: {#ref-item5 .csl-entry}
-'Udhrī, Jamīl al-. n.d.
+---------. n.d.b.
:::
::: {#ref-item7 .csl-entry}