aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs53
-rw-r--r--tests/markdown-reader-more.native5
-rw-r--r--tests/markdown-reader-more.txt5
-rw-r--r--tests/writer.markdown4
-rw-r--r--tests/writer.opml4
-rw-r--r--tests/writer.plain4
6 files changed, 56 insertions, 19 deletions
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index d71f0daf8..5cc1b3444 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -39,6 +39,7 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space)
import Data.Maybe (fromMaybe)
+import Data.Either (isRight)
import Data.List ( group, stripPrefix, find, intersperse, transpose, sortBy )
import Data.Char ( isSpace, isPunctuation )
import Data.Ord ( comparing )
@@ -57,12 +58,14 @@ import qualified Data.Text as T
type Notes = [[Block]]
type Refs = [([Inline], Target)]
-data WriterState = WriterState { stNotes :: Notes
- , stRefs :: Refs
- , stIds :: [String]
- , stPlain :: Bool }
+data WriterState = WriterState { stNotes :: Notes
+ , stRefs :: Refs
+ , stInList :: Bool
+ , stIds :: [String]
+ , stPlain :: Bool }
instance Default WriterState
- where def = WriterState{ stNotes = [], stRefs = [], stIds = [], stPlain = False }
+ where def = WriterState{ stNotes = [], stRefs = [], stInList = False,
+ stIds = [], stPlain = False }
-- | Convert Pandoc to Markdown.
writeMarkdown :: WriterOptions -> Pandoc -> String
@@ -453,7 +456,7 @@ blockToMarkdown opts t@(Table caption aligns widths headers rows) = do
$ Pandoc nullMeta [t]
return $ nst $ tbl $$ blankline $$ caption'' $$ blankline
blockToMarkdown opts (BulletList items) = do
- contents <- mapM (bulletListItemToMarkdown opts) items
+ contents <- inList $ mapM (bulletListItemToMarkdown opts) items
return $ cat contents <> blankline
blockToMarkdown opts (OrderedList (start,sty,delim) items) = do
let start' = if isEnabled Ext_startnum opts then start else 1
@@ -464,13 +467,22 @@ blockToMarkdown opts (OrderedList (start,sty,delim) items) = do
let markers' = map (\m -> if length m < 3
then m ++ replicate (3 - length m) ' '
else m) markers
- contents <- mapM (\(item, num) -> orderedListItemToMarkdown opts item num) $
+ contents <- inList $
+ mapM (\(item, num) -> orderedListItemToMarkdown opts item num) $
zip markers' items
return $ cat contents <> blankline
blockToMarkdown opts (DefinitionList items) = do
- contents <- mapM (definitionListItemToMarkdown opts) items
+ contents <- inList $ mapM (definitionListItemToMarkdown opts) items
return $ cat contents <> blankline
+inList :: State WriterState a -> State WriterState a
+inList p = do
+ oldInList <- gets stInList
+ modify $ \st -> st{ stInList = True }
+ res <- p
+ modify $ \st -> st{ stInList = oldInList }
+ return res
+
addMarkdownAttribute :: String -> String
addMarkdownAttribute s =
case span isTagText $ reverse $ parseTags s of
@@ -677,12 +689,29 @@ getReference label (src, tit) = do
-- | Convert list of Pandoc inline elements to markdown.
inlineListToMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc
-inlineListToMarkdown opts lst =
- mapM (inlineToMarkdown opts) (avoidBadWraps lst) >>= return . cat
+inlineListToMarkdown opts lst = do
+ inlist <- gets stInList
+ mapM (inlineToMarkdown opts)
+ (if inlist then avoidBadWraps lst else lst) >>= return . cat
where avoidBadWraps [] = []
- avoidBadWraps (Space:Str (c:cs):xs)
- | c `elem` ("-*+>" :: String) = Str (' ':c:cs) : avoidBadWraps xs
+ avoidBadWraps (Space:Str ('>':cs):xs) =
+ Str (' ':'>':cs) : avoidBadWraps xs
+ avoidBadWraps (Space:Str [c]:[])
+ | c `elem` "-*+" = Str [' ', c] : []
+ avoidBadWraps (Space:Str [c]:Space:xs)
+ | c `elem` "-*+" = Str [' ', c] : Space : avoidBadWraps xs
+ avoidBadWraps (Space:Str cs:Space:xs)
+ | isOrderedListMarker cs = Str (' ':cs) : Space : avoidBadWraps xs
+ avoidBadWraps (Space:Str cs:[])
+ | isOrderedListMarker cs = Str (' ':cs) : []
avoidBadWraps (x:xs) = x : avoidBadWraps xs
+ isOrderedListMarker xs = endsWithListPunct xs &&
+ isRight (runParserT (anyOrderedListMarker >> eof)
+ defaultParserState "" xs)
+ endsWithListPunct xs = case reverse xs of
+ '.':_ -> True
+ ')':_ -> True
+ _ -> False
escapeSpaces :: Inline -> Inline
escapeSpaces (Str s) = Str $ substitute " " "\\ " s
diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native
index 3f4bb5740..96204898e 100644
--- a/tests/markdown-reader-more.native
+++ b/tests/markdown-reader-more.native
@@ -156,4 +156,7 @@
,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",Space,Str "most",Space,Str "vocal",Space,Str "proponent."]
,Header 2 ("empty-reference-links",[],[]) [Str "Empty",Space,Str "reference",Space,Str "links"]
,Para [Str "bar"]
-,Para [Link [Str "foo2"] ("","")]]
+,Para [Link [Str "foo2"] ("","")]
+,Header 2 ("wrapping-shouldnt-introduce-new-list-items",[],[]) [Str "Wrapping",Space,Str "shouldn\8217t",Space,Str "introduce",Space,Str "new",Space,Str "list",Space,Str "items"]
+,BulletList
+ [[Plain [Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "2015."]]]]
diff --git a/tests/markdown-reader-more.txt b/tests/markdown-reader-more.txt
index d7439f6cb..99e9ec7e8 100644
--- a/tests/markdown-reader-more.txt
+++ b/tests/markdown-reader-more.txt
@@ -276,3 +276,8 @@ most vocal proponent.
bar
[foo2]
+
+## Wrapping shouldn't introduce new list items
+
+- blah blah blah blah blah blah blah blah blah blah blah blah blah blah 2015.
+
diff --git a/tests/writer.markdown b/tests/writer.markdown
index ad97b15ef..7276b31c7 100644
--- a/tests/writer.markdown
+++ b/tests/writer.markdown
@@ -549,8 +549,8 @@ LaTeX
These shouldn’t be math:
- To get the famous equation, write `$e = mc^2$`.
-- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is
- emphasized.)
+- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot”
+ is emphasized.)
- Shoes (\$20) and socks (\$5).
- Escaped `$`: \$73 *this should be emphasized* 23\$.
diff --git a/tests/writer.opml b/tests/writer.opml
index 840c3c6e1..8f79e842c 100644
--- a/tests/writer.opml
+++ b/tests/writer.opml
@@ -33,7 +33,7 @@
<outline text="Lists">
<outline text="Unordered" _note="Asterisks tight:&#10;&#10;- asterisk 1&#10;- asterisk 2&#10;- asterisk 3&#10;&#10;Asterisks loose:&#10;&#10;- asterisk 1&#10;&#10;- asterisk 2&#10;&#10;- asterisk 3&#10;&#10;Pluses tight:&#10;&#10;- Plus 1&#10;- Plus 2&#10;- Plus 3&#10;&#10;Pluses loose:&#10;&#10;- Plus 1&#10;&#10;- Plus 2&#10;&#10;- Plus 3&#10;&#10;Minuses tight:&#10;&#10;- Minus 1&#10;- Minus 2&#10;- Minus 3&#10;&#10;Minuses loose:&#10;&#10;- Minus 1&#10;&#10;- Minus 2&#10;&#10;- Minus 3&#10;&#10;">
</outline>
- <outline text="Ordered" _note="Tight:&#10;&#10;1. First&#10;2. Second&#10;3. Third&#10;&#10;and:&#10;&#10;1. One&#10;2. Two&#10;3. Three&#10;&#10;Loose using tabs:&#10;&#10;1. First&#10;&#10;2. Second&#10;&#10;3. Third&#10;&#10;and using spaces:&#10;&#10;1. One&#10;&#10;2. Two&#10;&#10;3. Three&#10;&#10;Multiple paragraphs:&#10;&#10;1. Item 1, graf one.&#10;&#10; Item 1. graf two. The quick brown fox jumped over the lazy dog’s&#10; back.&#10;&#10;2. Item 2.&#10;&#10;3. Item 3.&#10;&#10;">
+ <outline text="Ordered" _note="Tight:&#10;&#10;1. First&#10;2. Second&#10;3. Third&#10;&#10;and:&#10;&#10;1. One&#10;2. Two&#10;3. Three&#10;&#10;Loose using tabs:&#10;&#10;1. First&#10;&#10;2. Second&#10;&#10;3. Third&#10;&#10;and using spaces:&#10;&#10;1. One&#10;&#10;2. Two&#10;&#10;3. Three&#10;&#10;Multiple paragraphs:&#10;&#10;1. Item 1, graf one.&#10;&#10; Item 1. graf two. The quick brown fox jumped over the lazy&#10; dog’s back.&#10;&#10;2. Item 2.&#10;&#10;3. Item 3.&#10;&#10;">
</outline>
<outline text="Nested" _note="- Tab&#10; - Tab&#10; - Tab&#10;&#10;Here’s another:&#10;&#10;1. First&#10;2. Second:&#10; - Fee&#10; - Fie&#10; - Foe&#10;&#10;3. Third&#10;&#10;Same thing but with paragraphs:&#10;&#10;1. First&#10;&#10;2. Second:&#10;&#10; - Fee&#10; - Fie&#10; - Foe&#10;&#10;3. Third&#10;&#10;">
</outline>
@@ -50,7 +50,7 @@
</outline>
<outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.”&#10;&#10;‘A’, ‘B’, and ‘C’ are letters.&#10;&#10;‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’&#10;&#10;‘He said, “I want to go.”’ Were you alive in the 70’s?&#10;&#10;Here is some quoted ‘`code`’ and a “[quoted&#10;link](http://example.com/?foo=1&amp;bar=2)”.&#10;&#10;Some dashes: one—two — three—four — five.&#10;&#10;Dashes between numbers: 5–7, 255–66, 1987–1999.&#10;&#10;Ellipses…and…and….&#10;&#10;------------------------------------------------------------------------">
</outline>
-<outline text="LaTeX" _note="- \cite[22-23]{smith.1899}&#10;- $2+2=4$&#10;- $x \in y$&#10;- $\alpha \wedge \omega$&#10;- $223$&#10;- $p$-Tree&#10;- Here’s some display math:&#10; $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$&#10;- Here’s one that has a line break in it:&#10; $\alpha + \omega \times x^2$.&#10;&#10;These shouldn’t be math:&#10;&#10;- To get the famous equation, write `$e = mc^2$`.&#10;- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is&#10; emphasized.)&#10;- Shoes (\$20) and socks (\$5).&#10;- Escaped `$`: \$73 *this should be emphasized* 23\$.&#10;&#10;Here’s a LaTeX table:&#10;&#10;\begin{tabular}{|l|l|}\hline&#10;Animal &amp; Number \\ \hline&#10;Dog &amp; 2 \\&#10;Cat &amp; 1 \\ \hline&#10;\end{tabular}&#10;&#10;------------------------------------------------------------------------">
+<outline text="LaTeX" _note="- \cite[22-23]{smith.1899}&#10;- $2+2=4$&#10;- $x \in y$&#10;- $\alpha \wedge \omega$&#10;- $223$&#10;- $p$-Tree&#10;- Here’s some display math:&#10; $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$&#10;- Here’s one that has a line break in it:&#10; $\alpha + \omega \times x^2$.&#10;&#10;These shouldn’t be math:&#10;&#10;- To get the famous equation, write `$e = mc^2$`.&#10;- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot”&#10; is emphasized.)&#10;- Shoes (\$20) and socks (\$5).&#10;- Escaped `$`: \$73 *this should be emphasized* 23\$.&#10;&#10;Here’s a LaTeX table:&#10;&#10;\begin{tabular}{|l|l|}\hline&#10;Animal &amp; Number \\ \hline&#10;Dog &amp; 2 \\&#10;Cat &amp; 1 \\ \hline&#10;\end{tabular}&#10;&#10;------------------------------------------------------------------------">
</outline>
<outline text="Special Characters" _note="Here is some unicode:&#10;&#10;- I hat: Î&#10;- o umlaut: ö&#10;- section: §&#10;- set membership: ∈&#10;- copyright: ©&#10;&#10;AT&amp;T has an ampersand in their name.&#10;&#10;AT&amp;T is another way to write it.&#10;&#10;This &amp; that.&#10;&#10;4 \&lt; 5.&#10;&#10;6 \&gt; 5.&#10;&#10;Backslash: \\&#10;&#10;Backtick: \`&#10;&#10;Asterisk: \*&#10;&#10;Underscore: \_&#10;&#10;Left brace: {&#10;&#10;Right brace: }&#10;&#10;Left bracket: [&#10;&#10;Right bracket: ]&#10;&#10;Left paren: (&#10;&#10;Right paren: )&#10;&#10;Greater-than: \&gt;&#10;&#10;Hash: \#&#10;&#10;Period: .&#10;&#10;Bang: !&#10;&#10;Plus: +&#10;&#10;Minus: -&#10;&#10;------------------------------------------------------------------------">
</outline>
diff --git a/tests/writer.plain b/tests/writer.plain
index fab0489ac..0332a747b 100644
--- a/tests/writer.plain
+++ b/tests/writer.plain
@@ -499,8 +499,8 @@ LATEX
These shouldn’t be math:
- To get the famous equation, write $e = mc^2$.
-- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot” is
- emphasized.)
+- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot”
+ is emphasized.)
- Shoes ($20) and socks ($5).
- Escaped $: $73 _this should be emphasized_ 23$.