aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs8
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs10
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs19
-rw-r--r--src/Text/Pandoc/Readers/RST.hs12
4 files changed, 25 insertions, 24 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index e6ca05d87..94cde2d8d 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -382,7 +382,7 @@ parseTitle = try $ do
return contents
-- parse header and return meta-information (for now, just title)
-parseHead :: GenParser Char ParserState ([Inline], [a], [Char])
+parseHead :: GenParser Char ParserState Meta
parseHead = try $ do
htmlTag "head"
spaces
@@ -390,7 +390,7 @@ parseHead = try $ do
contents <- option [] parseTitle
skipMany nonTitleNonHead
htmlEndTag "head"
- return (contents, [], "")
+ return $ Meta contents [] []
skipHtmlTag :: String -> GenParser Char ParserState ()
skipHtmlTag tag = optional (htmlTag tag)
@@ -409,7 +409,7 @@ parseHtml = do
sepEndBy (choice [xmlDec, definition, htmlComment]) spaces
skipHtmlTag "html"
spaces
- (title, authors, date) <- option ([], [], "") parseHead
+ meta <- option (Meta [] [] []) parseHead
spaces
skipHtmlTag "body"
spaces
@@ -420,7 +420,7 @@ parseHtml = do
spaces
optional (htmlEndTag "html" >> many anyChar) -- ignore anything after </html>
eof
- return $ Pandoc (Meta title authors date) blocks
+ return $ Pandoc meta blocks
--
-- parsing blocks
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index b4c01fe19..cd1312966 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -317,19 +317,19 @@ title = try $ do
authors :: GenParser Char ParserState Block
authors = try $ do
string "\\author{"
- authors' <- manyTill anyChar (char '}')
+ authors' <- sepBy (many1 (notFollowedBy (oneOf "};,") >> inline)) (oneOf ",;")
+ char '}'
spaces
- let authors'' = map removeLeadingTrailingSpace $ lines $
- substitute "\\\\" "\n" authors'
+ let authors'' = map normalizeSpaces authors'
updateState (\s -> s { stateAuthors = authors'' })
return Null
date :: GenParser Char ParserState Block
date = try $ do
string "\\date{"
- date' <- manyTill anyChar (char '}')
+ date' <- manyTill inline (char '}')
spaces
- updateState (\state -> state { stateDate = date' })
+ updateState (\state -> state { stateDate = normalizeSpaces date' })
return Null
--
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 0de700537..8a09b191c 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -132,28 +132,27 @@ inlinesInBalancedBrackets parser = try $ do
titleLine :: GenParser Char ParserState [Inline]
titleLine = try $ char '%' >> skipSpaces >> manyTill inline newline
-authorsLine :: GenParser Char st [String]
+authorsLine :: GenParser Char ParserState [[Inline]]
authorsLine = try $ do
char '%'
skipSpaces
- authors <- sepEndBy (many1 (noneOf ",;\n")) (oneOf ",;")
+ authors <- sepEndBy (many1 (notFollowedBy (oneOf ",;\n") >> inline)) (oneOf ",;")
newline
- return $ map (decodeCharacterReferences . removeLeadingTrailingSpace) authors
+ return $ map normalizeSpaces authors
-dateLine :: GenParser Char st String
+dateLine :: GenParser Char ParserState [Inline]
dateLine = try $ do
char '%'
skipSpaces
- date <- many (noneOf "\n")
- newline
- return $ decodeCharacterReferences $ removeTrailingSpace date
+ date <- manyTill inline newline
+ return $ normalizeSpaces date
-titleBlock :: GenParser Char ParserState ([Inline], [String], [Char])
+titleBlock :: GenParser Char ParserState ([Inline], [[Inline]], [Inline])
titleBlock = try $ do
failIfStrict
title <- option [] titleLine
author <- option [] authorsLine
- date <- option "" dateLine
+ date <- option [] dateLine
optional blanklines
return (title, author, date)
@@ -175,7 +174,7 @@ parseMarkdown = do
let reversedNotes = stateNotes st'
updateState $ \s -> s { stateNotes = reverse reversedNotes }
-- now parse it for real...
- (title, author, date) <- option ([],[],"") titleBlock
+ (title, author, date) <- option ([],[],[]) titleBlock
blocks <- parseBlocks
return $ Pandoc (Meta title author date) $ filter (/= Null) blocks
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index fd6127cae..2f9282584 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -33,7 +33,7 @@ module Text.Pandoc.Readers.RST (
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.ParserCombinators.Parsec
-import Control.Monad ( when )
+import Control.Monad ( when, unless )
import Data.List ( findIndex, delete, intercalate )
-- | Parse reStructuredText string and return Pandoc document.
@@ -157,11 +157,13 @@ fieldList = try $ do
let authors = case lookup "Authors" items of
Just auth -> [auth]
Nothing -> map snd (filter (\(x,_) -> x == "Author") items)
- if null authors
- then return ()
- else updateState $ \st -> st {stateAuthors = authors}
+ unless (null authors) $ do
+ authors' <- mapM (parseFromString (many inline)) authors
+ updateState $ \st -> st {stateAuthors = map normalizeSpaces authors'}
case (lookup "Date" items) of
- Just dat -> updateState $ \st -> st {stateDate = dat}
+ Just dat -> do
+ dat' <- parseFromString (many inline) dat
+ updateState $ \st -> st{ stateDate = normalizeSpaces dat' }
Nothing -> return ()
case (lookup "Title" items) of
Just tit -> parseFromString (many inline) tit >>=