Smarter smart quotes.
Treat a leading " with no closing " as a left curly quote. This supports the practice, in fiction, of continuing paragraphs quoting the same speaker without an end quote. It also helps with quotes that break over lines in line blocks. Closes #7216.
This commit is contained in:
parent
8fe7e8dd5c
commit
80e2e88287
7 changed files with 66 additions and 69 deletions
|
@ -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)
|
||||
singleQuoted inlineParser = do
|
||||
singleQuoteStart
|
||||
(B.singleQuoted . mconcat <$>
|
||||
try
|
||||
(withQuoteContext InSingleQuote (many1Till inlineParser singleQuoteEnd)))
|
||||
<|> pure "\8217"
|
||||
|
||||
doubleQuoted :: (HasQuoteContext st m, Stream s m Char)
|
||||
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"))
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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" =:
|
||||
|
|
19
test/command/7216.md
Normal file
19
test/command/7216.md
Normal file
|
@ -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.''
|
||||
```
|
|
@ -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}
|
||||
|
|
Loading…
Reference in a new issue