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.hs2
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs33
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs27
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs9
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs19
-rw-r--r--src/Text/Pandoc/Readers/RST.hs4
6 files changed, 50 insertions, 44 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index fdf4f28e0..c78faebbd 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -551,7 +551,7 @@ pFigure = try $ do
let caption = fromMaybe mempty mbcap
case B.toList <$> mbimg of
Just [Image attr _ (url, tit)] ->
- return $ B.para $ B.imageWith attr url ("fig:" <> tit) caption
+ return $ B.simpleFigureWith attr caption url tit
_ -> mzero
pCodeBlock :: PandocMonad m => TagParser m Blocks
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 34eb53245..15148debb 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1095,24 +1095,25 @@ figure = try $ do
addImageCaption :: PandocMonad m => Blocks -> LP m Blocks
addImageCaption = walkM go
- where go (Image attr@(_, cls, kvs) alt (src,tit))
+ where go p@(Para [Image attr@(_, cls, kvs) _ (src, tit)])
| not ("fig:" `T.isPrefixOf` tit) = do
st <- getState
- let (alt', tit') = case sCaption st of
- Just ils -> (toList ils, "fig:" <> tit)
- Nothing -> (alt, tit)
- attr' = case sLastLabel st of
- Just lab -> (lab, cls, kvs)
- Nothing -> attr
- case attr' of
- ("", _, _) -> return ()
- (ident, _, _) -> do
- num <- getNextNumber sLastFigureNum
- setState
- st{ sLastFigureNum = num
- , sLabels = M.insert ident
- [Str (renderDottedNum num)] (sLabels st) }
- return $ Image attr' alt' (src, tit')
+ case sCaption st of
+ Nothing -> return p
+ Just figureCaption -> do
+ let attr' = case sLastLabel st of
+ Just lab -> (lab, cls, kvs)
+ Nothing -> attr
+ case attr' of
+ ("", _, _) -> return ()
+ (ident, _, _) -> do
+ num <- getNextNumber sLastFigureNum
+ setState
+ st{ sLastFigureNum = num
+ , sLabels = M.insert ident
+ [Str (renderDottedNum num)] (sLabels st) }
+
+ return $ SimpleFigure attr' (B.toList figureCaption) (src, tit)
go x = return x
coloredBlock :: PandocMonad m => Text -> LP m Blocks
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 03becd144..e7ab8efb4 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1015,19 +1015,18 @@ normalDefinitionList = do
para :: PandocMonad m => MarkdownParser m (F Blocks)
para = try $ do
exts <- getOption readerExtensions
- let implicitFigures x
- | extensionEnabled Ext_implicit_figures exts = do
- x' <- x
- case B.toList x' of
- [Image attr alt (src,tit)]
- | not (null alt) ->
- -- the fig: at beginning of title indicates a figure
- return $ B.singleton
- $ Image attr alt (src, "fig:" <> tit)
- _ -> return x'
- | otherwise = x
- result <- implicitFigures . trimInlinesF <$> inlines1
- option (B.plain <$> result)
+
+ result <- trimInlinesF <$> inlines1
+ let figureOr constr inlns =
+ case B.toList inlns of
+ [Image attr figCaption (src, tit)]
+ | extensionEnabled Ext_implicit_figures exts
+ , not (null figCaption) -> do
+ B.simpleFigureWith attr (B.fromList figCaption) src tit
+
+ _ -> constr inlns
+
+ option (figureOr B.plain <$> result)
$ try $ do
newline
(mempty <$ blanklines)
@@ -1049,7 +1048,7 @@ para = try $ do
if divLevel > 0
then lookAhead divFenceEnd
else mzero
- return $ B.para <$> result
+ return $ figureOr B.para <$> result
plain :: PandocMonad m => MarkdownParser m (F Blocks)
plain = fmap B.plain . trimInlinesF <$> inlines1
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 825e4a2eb..9348a8053 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -201,7 +201,12 @@ para = do
contents <- trimInlines . mconcat <$> many1 inline
if F.all (==Space) contents
then return mempty
- else return $ B.para contents
+ else case B.toList contents of
+ -- For the MediaWiki format all images are considered figures
+ [Image attr figureCaption (src, title)] ->
+ return $ B.simpleFigureWith
+ attr (B.fromList figureCaption) src title
+ _ -> return $ B.para contents
table :: PandocMonad m => MWParser m Blocks
table = do
@@ -631,7 +636,7 @@ image = try $ do
let attr = ("", [], kvs)
caption <- (B.str fname <$ sym "]]")
<|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]")))
- return $ B.imageWith attr fname ("fig:" <> stringify caption) caption
+ return $ B.imageWith attr fname (stringify caption) caption
imageOption :: PandocMonad m => MWParser m Text
imageOption = try $ char '|' *> opt
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 2ec97d903..9a689b0e8 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -474,15 +474,16 @@ figure = try $ do
figCaption = fromMaybe mempty $ blockAttrCaption figAttrs
figKeyVals = blockAttrKeyValues figAttrs
attr = (figLabel, mempty, figKeyVals)
- figTitle = (if isFigure then withFigPrefix else id) figName
- in
- B.para . B.imageWith attr imgSrc figTitle <$> figCaption
-
- withFigPrefix :: Text -> Text
- withFigPrefix cs =
- if "fig:" `T.isPrefixOf` cs
- then cs
- else "fig:" <> cs
+ in if isFigure
+ then (\c ->
+ B.simpleFigureWith
+ attr c imgSrc (unstackFig figName)) <$> figCaption
+ else B.para . B.imageWith attr imgSrc figName <$> figCaption
+ unstackFig :: Text -> Text
+ unstackFig figName =
+ if "fig:" `T.isPrefixOf` figName
+ then T.drop 4 figName
+ else figName
-- | Succeeds if looking at the end of the current paragraph
endOfParagraph :: Monad m => OrgParser m ()
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 458a2d48b..8ee017342 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -725,8 +725,8 @@ directive' = do
"figure" -> do
(caption, legend) <- parseFromString' extractCaption body'
let src = escapeURI $ trim top
- return $ B.para (B.imageWith (imgAttr "figclass") src "fig:"
- caption) <> legend
+ return $ B.simpleFigureWith
+ (imgAttr "figclass") caption src "" <> legend
"image" -> do
let src = escapeURI $ trim top
let alt = B.str $ maybe "image" trim $ lookup "alt" fields