aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2011-12-05 20:55:23 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2011-12-05 20:55:23 -0800
commitd34f85613a7bf32283abaff73965cf8a0436ea4f (patch)
treed71c5120c5c04d07f9341ceadbd46c0e5bded2d9 /src/Text/Pandoc
parentfa255f68ba4d75e327427ed9802ac7484fe03e63 (diff)
downloadpandoc-d34f85613a7bf32283abaff73965cf8a0436ea4f.tar.gz
Changes to fit new charsInBalanced.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs4
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs17
2 files changed, 13 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 9610b75a5..9ad31cba5 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -59,7 +59,7 @@ specialChars = "\\`$%^&_~#{}[]\n \t|<>'\"-"
-- | Returns text between brackets and its matching pair.
bracketedText :: Char -> Char -> GenParser Char st [Char]
bracketedText openB closeB = do
- result <- charsInBalanced' openB closeB
+ result <- charsInBalanced openB closeB anyChar
return $ [openB] ++ result ++ [closeB]
-- | Returns an option or argument of a LaTeX command.
@@ -888,7 +888,7 @@ ensureMath = try $ do
url :: GenParser Char ParserState Inline
url = try $ do
string "\\url"
- url' <- charsInBalanced '{' '}'
+ url' <- charsInBalanced '{' '}' anyChar
return $ Link [Code ("",["url"],[]) url'] (escapeURI url', "")
link :: GenParser Char ParserState Inline
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index cdd75650c..e2379bdc3 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -108,6 +108,11 @@ atMostSpaces :: Int -> GenParser Char ParserState ()
atMostSpaces 0 = notFollowedBy (char ' ')
atMostSpaces n = (char ' ' >> atMostSpaces (n-1)) <|> return ()
+litChar :: GenParser Char ParserState Char
+litChar = escapedChar'
+ <|> noneOf "\n"
+ <|> (newline >> notFollowedBy blankline >> return ' ')
+
-- | Fail unless we're at beginning of a line.
failUnlessBeginningOfLine :: GenParser tok st ()
failUnlessBeginningOfLine = do
@@ -233,12 +238,12 @@ referenceKey = try $ do
-- return blanks so line count isn't affected
return $ replicate (sourceLine endPos - sourceLine startPos) '\n'
-referenceTitle :: GenParser Char st String
-referenceTitle = try $ do
+referenceTitle :: GenParser Char ParserState String
+referenceTitle = try $ do
skipSpaces >> optional newline >> skipSpaces
- tit <- (charsInBalanced '(' ')' >>= return . unwords . words)
+ tit <- (charsInBalanced '(' ')' litChar >>= return . unwords . words)
<|> do delim <- char '\'' <|> char '"'
- manyTill anyChar (try (char delim >> skipSpaces >>
+ manyTill litChar (try (char delim >> skipSpaces >>
notFollowedBy (noneOf ")\n")))
return $ decodeCharacterReferences tit
@@ -1136,9 +1141,9 @@ reference = do notFollowedBy' (string "[^") -- footnote reference
return $ normalizeSpaces result
-- source for a link, with optional title
-source :: GenParser Char st (String, [Char])
+source :: GenParser Char ParserState (String, [Char])
source =
- (try $ charsInBalanced '(' ')' >>= parseFromString source') <|>
+ (try $ charsInBalanced '(' ')' litChar >>= parseFromString source') <|>
-- the following is needed for cases like: [ref](/url(a).
(enclosed (char '(') (char ')') anyChar >>=
parseFromString source')