aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/RST.hs69
-rw-r--r--tests/rst-reader.native29
-rw-r--r--tests/rst-reader.rst17
3 files changed, 81 insertions, 34 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 1769b84d6..d1139ebd0 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -113,13 +113,13 @@ parseBlocks = manyTill block eof
block = choice [ codeBlock
, rawHtmlBlock
, rawLaTeXBlock
+ , fieldList
, blockQuote
, imageBlock
, unknownDirective
, header
, hrule
, list
- , fieldList
, lineBlock
, para
, plain
@@ -129,36 +129,42 @@ block = choice [ codeBlock
-- field list
--
-fieldListItem = try $ do
+fieldListItem indent = try $ do
+ string indent
char ':'
name <- many1 alphaNum
string ": "
skipSpaces
first <- manyTill anyChar newline
- rest <- many (notFollowedBy ((char ':') <|> blankline) >>
- skipSpaces >> manyTill anyChar newline)
- return $ (name, (joinWithSep " " (first:rest)))
+ rest <- option "" $ try $ lookAhead (string indent >> oneOf " \t") >>
+ indentedBlock
+ return (name, joinWithSep " " (first:(lines rest)))
fieldList = try $ do
- items <- many1 fieldListItem
+ indent <- lookAhead $ many (oneOf " \t")
+ items <- many1 $ fieldListItem indent
blanklines
let authors = case lookup "Authors" items of
Just auth -> [auth]
Nothing -> map snd (filter (\(x,y) -> x == "Author") items)
- let date = case (lookup "Date" items) of
- Just dat -> dat
- Nothing -> ""
- let title = case (lookup "Title" items) of
- Just tit -> [Str tit]
- Nothing -> []
+ if null authors
+ then return ()
+ else updateState $ \st -> st {stateAuthors = authors}
+ case (lookup "Date" items) of
+ Just dat -> updateState $ \st -> st {stateDate = dat}
+ Nothing -> return ()
+ case (lookup "Title" items) of
+ Just tit -> parseFromString (many inline) tit >>=
+ \t -> updateState $ \st -> st {stateTitle = t}
+ Nothing -> return ()
let remaining = filter (\(x,y) -> (x /= "Authors") && (x /= "Author") &&
(x /= "Date") && (x /= "Title")) items
- let result = map (\(x,y) ->
- Para [Strong [Str x], Str ":", Space, Str y]) remaining
- updateState (\st -> st { stateAuthors = authors,
- stateDate = date,
- stateTitle = title })
- return $ BlockQuote result
+ if null remaining
+ then return Null
+ else do terms <- mapM (return . (:[]) . Str . fst) remaining
+ defs <- mapM (parseFromString (many block) . snd)
+ remaining
+ return $ DefinitionList $ zip terms defs
--
-- line block
@@ -207,8 +213,12 @@ plain = many1 inline >>= return . Plain . normalizeSpaces
imageBlock = try $ do
string ".. image:: "
src <- manyTill anyChar newline
- return $ Plain [Image [Str "image"] (src, "")]
-
+ fields <- option [] $ do indent <- lookAhead $ many (oneOf " /t")
+ many1 $ fieldListItem indent
+ optional blanklines
+ case lookup "alt" fields of
+ Just alt -> return $ Plain [Image [Str alt] (src, alt)]
+ Nothing -> return $ Plain [Image [Str "image"] (src, "")]
--
-- header blocks
--
@@ -282,17 +292,14 @@ indentedLine indents = try $ do
-- two or more indented lines, possibly separated by blank lines.
-- any amount of indentation will work.
-indentedBlock = try $ do
- state <- getState
- let tabStop = stateTabStop state
- indents <- many1 (oneOf " \t")
- firstline <- manyTill anyChar newline
- rest <- many (choice [ indentedLine indents,
- try (do b <- blanklines
- l <- indentedLine indents
- return (b ++ l))])
- optional blanklines
- return $ firstline ++ "\n" ++ concat rest
+indentedBlock = do
+ indents <- lookAhead $ many1 (oneOf " \t")
+ lns <- many $ choice $ [ indentedLine indents,
+ try $ do b <- blanklines
+ l <- indentedLine indents
+ return (b ++ l) ]
+ optional blanklines
+ return $ concat lns
codeBlock = try $ do
codeBlockStart
diff --git a/tests/rst-reader.native b/tests/rst-reader.native
index bbd139776..8536a2874 100644
--- a/tests/rst-reader.native
+++ b/tests/rst-reader.native
@@ -1,7 +1,8 @@
Pandoc (Meta [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":",Space,Str "Subtitle"] ["John MacFarlane","Anonymous"] "July 17, 2006")
-[ BlockQuote
- [ Para [Strong [Str "Revision"],Str ":",Space,Str "3"] ]
-
+[ DefinitionList
+ [ ([Str "Revision"],
+ [ Plain [Str "3"] ]
+ ) ]
, Header 1 [Str "Level",Space,Str "one",Space,Str "header"]
, Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
, Header 2 [Str "Level",Space,Str "two",Space,Str "header"]
@@ -156,6 +157,27 @@ Pandoc (Meta [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":",Space,Str
([Str "term",Space,Str "with",Space,Emph [Str "emphasis"]],
[ Para [Str "Definition",Space,Str "3."] ]
) ]
+, Header 1 [Str "Field",Space,Str "Lists"]
+, DefinitionList
+ [ ([Str "address"],
+ [ Plain [Str "61",Space,Str "Main",Space,Str "St."] ]
+ ),
+ ([Str "city"],
+ [ Plain [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"] ]
+ ),
+ ([Str "phone"],
+ [ Plain [Str "123",Str "-",Str "4567"] ]
+ ) ]
+, DefinitionList
+ [ ([Str "address"],
+ [ Plain [Str "61",Space,Str "Main",Space,Str "St."] ]
+ ),
+ ([Str "city"],
+ [ Plain [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"] ]
+ ),
+ ([Str "phone"],
+ [ Plain [Str "123",Str "-",Str "4567"] ]
+ ) ]
, Header 1 [Str "HTML",Space,Str "Blocks"]
, Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line",Str ":"]
, RawHtml "<div>foo</div>\n"
@@ -207,5 +229,6 @@ Pandoc (Meta [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":",Space,Str
, Header 1 [Str "Images"]
, Para [Str "From",Space,Str "\"Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902)",Str ":"]
, Plain [Image [Str "image"] ("lalune.jpg","")]
+, Plain [Image [Str "Voyage dans la Lune"] ("lalune.jpg","Voyage dans la Lune")]
, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ]
diff --git a/tests/rst-reader.rst b/tests/rst-reader.rst
index 36fd4ff9d..f3d07b49d 100644
--- a/tests/rst-reader.rst
+++ b/tests/rst-reader.rst
@@ -256,6 +256,19 @@ term 2
term with *emphasis*
Definition 3.
+Field Lists
+===========
+
+ :address: 61 Main St.
+ :city: *Nowhere*, MA,
+ USA
+ :phone: 123-4567
+
+:address: 61 Main St.
+:city: *Nowhere*, MA,
+ USA
+:phone: 123-4567
+
HTML Blocks
===========
@@ -382,6 +395,10 @@ From "Voyage dans la Lune" by Georges Melies (1902):
.. image:: lalune.jpg
+.. image:: lalune.jpg
+ :height: 2343
+ :alt: Voyage dans la Lune
+
Here is a movie |movie| icon.
.. |movie| image:: movie.jpg