aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Text/Pandoc/Readers/Markdown.hs17
-rw-r--r--changelog3
-rw-r--r--tests/markdown-reader-more.native5
-rw-r--r--tests/markdown-reader-more.txt13
4 files changed, 25 insertions, 13 deletions
diff --git a/Text/Pandoc/Readers/Markdown.hs b/Text/Pandoc/Readers/Markdown.hs
index 08e78d525..205472d29 100644
--- a/Text/Pandoc/Readers/Markdown.hs
+++ b/Text/Pandoc/Readers/Markdown.hs
@@ -32,7 +32,6 @@ module Text.Pandoc.Readers.Markdown (
readMarkdown
) where
-import Control.Applicative ( (<$>) )
import Data.List ( transpose, isPrefixOf, isSuffixOf, lookup, sortBy, findIndex, intercalate )
import Data.Ord ( comparing )
import Data.Char ( isAlphaNum, isAlpha, isLower, isDigit, isUpper )
@@ -189,15 +188,13 @@ referenceKey = try $ do
lab <- reference
char ':'
skipSpaces >> optional newline >> skipSpaces >> notFollowedBy (char '[')
- let sourceURL excludes = concat <$>
- (many $ do optional (char '\\')
- count 1 (noneOf $ ' ':excludes)
- <|> (notFollowedBy' referenceTitle >> char ' ' >> return "%20"))
+ let sourceURL excludes = many $
+ optional (char '\\') >> (noneOf (' ':excludes) <|> (notFollowedBy' referenceTitle >> char ' '))
src <- try (char '<' >> sourceURL ">\t\n" >>~ char '>') <|> sourceURL "\t\n"
tit <- option "" referenceTitle
blanklines
endPos <- getPosition
- let newkey = (lab, (removeTrailingSpace src, tit))
+ let newkey = (lab, (intercalate "%20" $ words $ removeTrailingSpace src, tit))
st <- getState
let oldkeys = stateKeys st
updateState $ \s -> s { stateKeys = newkey : oldkeys }
@@ -1066,15 +1063,13 @@ source =
source' :: GenParser Char st (String, [Char])
source' = do
skipSpaces
- let sourceURL excludes = concat <$>
- (many $ do optional (char '\\')
- count 1 (noneOf $ ' ':excludes)
- <|> (notFollowedBy' linkTitle >> char ' ' >> return "%20"))
+ let sourceURL excludes = many $
+ optional (char '\\') >> (noneOf (' ':excludes) <|> (notFollowedBy' linkTitle >> char ' '))
src <- try (char '<' >> sourceURL ">\t\n" >>~ char '>') <|> sourceURL "\t\n"
tit <- option "" linkTitle
skipSpaces
eof
- return (removeTrailingSpace src, tit)
+ return (intercalate "%20" $ words $ removeTrailingSpace src, tit)
linkTitle :: GenParser Char st String
linkTitle = try $ do
diff --git a/changelog b/changelog
index 23f71ba3a..d448f1c17 100644
--- a/changelog
+++ b/changelog
@@ -49,7 +49,8 @@ pandoc (1.1)
a blank line before the haskell code, and we don't want spurious
blank lines in the output.
- + Allow URLs with spaces in them in links and references.
+ + Allow URLs with spaces in them in links and references, but escape
+ them as "%20".
* HTML writer:
diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native
index 5fea0f02d..3d38e7a9a 100644
--- a/tests/markdown-reader-more.native
+++ b/tests/markdown-reader-more.native
@@ -4,5 +4,8 @@ Pandoc (Meta [] [] "")
, Para [Link [Str "foo"] ("/url",""),Space,Str "and",Space,Link [Str "bar"] ("/url","title")]
, Header 2 [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]
, Para [TeX "\\placeformula",Space,TeX "\\startformula\n L_{1} = L_{2}\n \\stopformula"]
-, Para [TeX "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"] ]
+, Para [TeX "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"]
+, Header 2 [Str "URLs",Space,Str "with",Space,Str "spaces"]
+, Para [Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("bar%20baz","title")]
+, Para [Link [Str "baz"] ("/foo%20foo",""),Space,Link [Str "bam"] ("/foo%20fee",""),Space,Link [Str "bork"] ("/foo/zee%20zob","title")] ]
diff --git a/tests/markdown-reader-more.txt b/tests/markdown-reader-more.txt
index 6c6191fad..d26274d6a 100644
--- a/tests/markdown-reader-more.txt
+++ b/tests/markdown-reader-more.txt
@@ -22,3 +22,16 @@
\stop[a2]
\stop[a2]
+## URLs with spaces
+
+[foo](/bar and baz)
+[foo](/bar and baz )
+[foo]( /bar and baz )
+[foo](bar baz "title" )
+
+[baz][] [bam][] [bork][]
+
+[baz]: /foo foo
+[bam]: /foo fee
+[bork]: /foo/zee zob (title)
+