aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/RST.hs15
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs15
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs2
-rw-r--r--src/Text/Pandoc/Writers/Org.hs6
4 files changed, 23 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 35fe5d768..d1010a736 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -127,6 +127,7 @@ block = choice [ codeBlock
, blockQuote
, fieldList
, imageBlock
+ , figureBlock
, customCodeBlock
, mathBlock
, defaultRoleBlock
@@ -362,6 +363,20 @@ customCodeBlock = try $ do
result <- indentedBlock
return $ CodeBlock ("", ["sourceCode", language], []) $ stripTrailingNewlines result
+
+figureBlock :: GenParser Char ParserState Block
+figureBlock = try $ do
+ string ".. figure::"
+ src <- removeLeadingTrailingSpace `fmap` manyTill anyChar newline
+ body <- indentedBlock
+ caption <- parseFromString extractCaption body
+ return $ Para [Image caption (src,"")]
+
+extractCaption :: GenParser Char ParserState [Inline]
+extractCaption = try $ do
+ manyTill anyLine blanklines
+ many inline
+
-- | The 'math' directive (from Sphinx) for display math.
mathBlock :: GenParser Char st Block
mathBlock = try $ do
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index abc686a84..348900d38 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -493,19 +493,12 @@ escapedInline :: GenParser Char ParserState Inline
escapedInline = escapedEqs <|> escapedTag
escapedEqs :: GenParser Char ParserState Inline
-escapedEqs = Str <$> (try $ surrounded (string "==") anyChar)
-
--- -- | literal text escaped between == ... ==
--- escapedEqs :: GenParser Char ParserState Inline
--- escapedEqs = try $ do
--- string "=="
--- contents <- manyTill anyChar (try $ string "==")
--- return $ Str contents
+escapedEqs = Str <$> (try $ string "==" *> manyTill anyChar (try $ string "=="))
-- | literal text escaped btw <notextile> tags
escapedTag :: GenParser Char ParserState Inline
-escapedTag = try $ Str <$>
- enclosed (string "<notextile>") (string "</notextile>") anyChar
+escapedTag = Str <$>
+ (try $ string "<notextile>" *> manyTill anyChar (try $ string "</notextile>"))
-- | Any special symbol defined in wordBoundaries
symbol :: GenParser Char ParserState Inline
@@ -533,7 +526,7 @@ attributes = choice [ enclosed (char '(') (char ')') anyChar,
surrounded :: GenParser Char st t -- ^ surrounding parser
-> GenParser Char st a -- ^ content parser (to be used repeatedly)
-> GenParser Char st [a]
-surrounded border = enclosed border border
+surrounded border = enclosed border (try border)
-- | Inlines are most of the time of the same form
simpleInline :: GenParser Char ParserState t -- ^ surrounding parser
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 08165ea1b..886d55da1 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -271,7 +271,7 @@ inlineToConTeXt (Str str) = do
inlineToConTeXt (Math InlineMath str) =
return $ char '$' <> text str <> char '$'
inlineToConTeXt (Math DisplayMath str) =
- return $ text "\\startformula " <> text str <> text " \\stopformula"
+ return $ text "\\startformula " <> text str <> text " \\stopformula" <> space
inlineToConTeXt (RawInline "context" str) = return $ text str
inlineToConTeXt (RawInline "tex" str) = return $ text str
inlineToConTeXt (RawInline _ _) = return empty
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 4c77ba7c6..7eb943a22 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -139,9 +139,9 @@ blockToOrg (CodeBlock (_,classes,_) str) = do
"ledger", "lisp", "matlab", "mscgen", "ocaml", "octave",
"oz", "perl", "plantuml", "python", "R", "ruby", "sass",
"scheme", "screen", "sh", "sql", "sqlite"]
- let (beg, end) = if null at
- then ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE")
- else ("#+BEGIN_SRC" ++ head at, "#+END_SRC")
+ let (beg, end) = case at of
+ [] -> ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE")
+ (x:_) -> ("#+BEGIN_SRC " ++ x, "#+END_SRC")
return $ text beg $$ nest tabstop (text str) $$ text end $$ blankline
blockToOrg (BlockQuote blocks) = do
contents <- blockListToOrg blocks