Markdown reader: Allow linebreaks in URLs (treat as spaces).

Also, a string of consecutive spaces or tabs is now parsed
as a single space. If you have multiple spaces in your URL,
use %20%20.
This commit is contained in:
John MacFarlane 2010-12-10 12:14:51 -08:00
parent ee0a0953de
commit 17d48cf4af
3 changed files with 24 additions and 8 deletions

View file

@ -202,9 +202,17 @@ referenceKey = try $ do
lab <- reference
char ':'
skipSpaces >> optional newline >> skipSpaces >> notFollowedBy (char '[')
let sourceURL excludes = many $
optional (char '\\') >> (noneOf (' ':excludes) <|> (notFollowedBy' referenceTitle >> char ' '))
src <- try (char '<' >> sourceURL ">\t\n" >>~ char '>') <|> sourceURL "\t\n"
let nl = char '\n' >> notFollowedBy blankline >> return ' '
let sourceURL = liftM unwords $ many $ try $ do
notFollowedBy' referenceTitle
skipMany (oneOf " \t")
optional nl
notFollowedBy' reference
skipMany (oneOf " \t")
many1 (noneOf " \t\n")
let betweenAngles = try $ char '<' >>
manyTill (noneOf ">\n" <|> nl) (char '>')
src <- try betweenAngles <|> sourceURL
tit <- option "" referenceTitle
blanklines
endPos <- getPosition
@ -1116,9 +1124,16 @@ source =
source' :: GenParser Char st (String, [Char])
source' = do
skipSpaces
let sourceURL excludes = many $
optional (char '\\') >> (noneOf (' ':excludes) <|> (notFollowedBy' linkTitle >> char ' '))
src <- try (char '<' >> sourceURL ">\t\n" >>~ char '>') <|> sourceURL "\t\n"
let nl = char '\n' >>~ notFollowedBy blankline
let sourceURL = liftM unwords $ many $ try $ do
notFollowedBy' linkTitle
skipMany (oneOf " \t")
optional nl
skipMany (oneOf " \t")
many1 (noneOf " \t\n")
let betweenAngles = try $ char '<' >>
manyTill (noneOf ">\n" <|> nl) (char '>')
src <- try betweenAngles <|> sourceURL
tit <- option "" linkTitle
skipSpaces
eof

View file

@ -6,7 +6,7 @@ Pandoc (Meta {docTitle = [Str "Title",Space,Str "spanning",Space,Str "multiple",
, 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]"]
, 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%20%20and%20%20baz",""),Space,Link [Str "foo"] ("bar%20baz","title")]
, 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")]
, Header 2 [Str "Horizontal",Space,Str "rules",Space,Str "with",Space,Str "spaces",Space,Str "at",Space,Str "end"]
, HorizontalRule

View file

@ -31,7 +31,8 @@
## URLs with spaces
[foo](/bar and baz)
[foo](/bar and baz )
[foo](/bar
and baz )
[foo]( /bar and baz )
[foo](bar baz "title" )