aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs3
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs5
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs5
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs3
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs4
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs5
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs3
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs6
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs4
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs5
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs6
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs4
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs3
-rw-r--r--src/Text/Pandoc/Writers/Org.hs4
-rw-r--r--src/Text/Pandoc/Writers/RST.hs34
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs3
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs4
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs4
19 files changed, 43 insertions, 66 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 4d3906c5f..24438370a 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -149,9 +149,8 @@ blockToAsciiDoc opts (Div (id',"section":_,_)
blockToAsciiDoc opts (Plain inlines) = do
contents <- inlineListToAsciiDoc opts inlines
return $ contents <> blankline
-blockToAsciiDoc opts (Para [Image attr alternate (src,tgt)])
+blockToAsciiDoc opts (SimpleFigure attr alternate (src, tit))
-- image::images/logo.png[Company logo, title="blah"]
- | Just tit <- T.stripPrefix "fig:" tgt
= (\args -> "image::" <> args <> blankline) <$>
imageArguments opts attr alternate src tit
blockToAsciiDoc opts (Para inlines) = do
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 3cafcefba..13970cbc3 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -162,10 +162,7 @@ blockToConTeXt (Div attr@(_,"section":_,_)
innerContents <- blockListToConTeXt xs
return $ header' $$ innerContents $$ footer'
blockToConTeXt (Plain lst) = inlineListToConTeXt lst
--- title beginning with fig: indicates that the image is a figure
-blockToConTeXt (Para [Image attr txt (src,tgt)])
- | Just _ <- T.stripPrefix "fig:" tgt
- = do
+blockToConTeXt (SimpleFigure attr txt (src, _)) = do
capt <- inlineListToConTeXt txt
img <- inlineToConTeXt (Image attr txt (src, ""))
let (ident, _, _) = attr
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 33a6f5f0c..c9e49517f 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.Docbook
Copyright : Copyright (C) 2006-2021 John MacFarlane
@@ -188,7 +187,7 @@ blockToDocbook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs))
-- standalone documents will include them in the template.
then [("xmlns", "http://docbook.org/ns/docbook"),("xmlns:xlink", "http://www.w3.org/1999/xlink")]
else []
-
+
-- Populate miscAttr with Header.Attr.attributes, filtering out non-valid DocBook section attributes, id, and xml:id
miscAttr = filter (isSectionAttr version) attrs
attribs = nsAttr <> idAttr <> miscAttr
@@ -233,7 +232,7 @@ blockToDocbook _ h@Header{} = do
return empty
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
-- title beginning with fig: indicates that the image is a figure
-blockToDocbook opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just _)]) = do
+blockToDocbook opts (SimpleFigure attr txt (src, _)) = do
alt <- inlinesToDocbook opts txt
let capt = if null txt
then empty
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 686a2f662..fccbb0719 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -854,8 +854,7 @@ blockToOpenXML' opts (Plain lst) = do
then withParaProp prop block
else block
-- title beginning with fig: indicates that the image is a figure
-blockToOpenXML' opts (Para [Image attr@(imgident,_,_) alt
- (src,T.stripPrefix "fig:" -> Just tit)]) = do
+blockToOpenXML' opts (SimpleFigure attr@(imgident, _, _) alt (src, tit)) = do
setFirstPara
fignum <- gets stNextFigureNum
unless (null alt) $ modify $ \st -> st{ stNextFigureNum = fignum + 1 }
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 602c70ebe..c77f20ec1 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -109,9 +109,7 @@ blockToDokuWiki opts (Plain inlines) =
-- title beginning with fig: indicates that the image is a figure
-- dokuwiki doesn't support captions - so combine together alt and caption into alt
-blockToDokuWiki opts (Para [Image attr txt (src,tgt)])
- | Just tit <- T.stripPrefix "fig:" tgt
- = do
+blockToDokuWiki opts (SimpleFigure attr txt (src, tit)) = do
capt <- if null txt
then return ""
else (" " <>) `fmap` inlineListToDokuWiki opts txt
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 6bad37404..ce3fe25a9 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -299,9 +299,8 @@ blockToXml :: PandocMonad m => Block -> FBM m [Content]
blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2
blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula
-- title beginning with fig: indicates that the image is a figure
-blockToXml (Para [Image atr alt (src,tgt)])
- | Just tit <- T.stripPrefix "fig:" tgt
- = insertImage NormalImage (Image atr alt (src,tit))
+blockToXml (SimpleFigure atr alt (src, tit)) =
+ insertImage NormalImage (Image atr alt (src,tit))
blockToXml (Para ss) = list . el "p" <$> cMapM toXml ss
blockToXml (CodeBlock _ s) = return . spaceBeforeAfter .
map (el "p" . el "code") . T.lines $ s
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 8fc81ed24..0a4c47387 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -742,8 +742,8 @@ blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)])
inlineToHtml opts (Image attr txt (src, tit))
_ -> figure opts attr txt (src, tit)
-- title beginning with fig: indicates that the image is a figure
-blockToHtmlInner opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) =
- figure opts attr txt (s,tit)
+blockToHtmlInner opts (SimpleFigure attr caption (src, title)) =
+ figure opts attr caption (src, title)
blockToHtmlInner opts (Para lst) = do
contents <- inlineListToHtml opts lst
case contents of
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 75e14714b..dfd89bc54 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -98,8 +98,7 @@ blockToHaddock opts (Plain inlines) = do
contents <- inlineListToHaddock opts inlines
return $ contents <> cr
-- title beginning with fig: indicates figure
-blockToHaddock opts (Para [Image attr alt (src,tgt)])
- | Just tit <- T.stripPrefix "fig:" tgt
+blockToHaddock opts (SimpleFigure attr alt (src, tit))
= blockToHaddock opts (Para [Image attr alt (src,tit)])
blockToHaddock opts (Para inlines) =
-- TODO: if it contains linebreaks, we need to use a @...@ block
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index c254fbc58..ea6009fd1 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.ICML
@@ -309,9 +308,8 @@ blocksToICML opts style lst = do
-- | Convert a Pandoc block element to ICML.
blockToICML :: PandocMonad m => WriterOptions -> Style -> Block -> WS m (Doc Text)
blockToICML opts style (Plain lst) = parStyle opts style "" lst
--- title beginning with fig: indicates that the image is a figure
-blockToICML opts style (Para img@[Image _ txt (_,Text.stripPrefix "fig:" -> Just _)]) = do
- figure <- parStyle opts (figureName:style) "" img
+blockToICML opts style (SimpleFigure attr txt (src, tit)) = do
+ figure <- parStyle opts (figureName:style) "" [Image attr txt (src, tit)]
caption <- parStyle opts (imgCaptionName:style) "" txt
return $ intersperseBrs [figure, caption]
blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) "" lst
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index 9db8723d1..d58da8bd2 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -291,9 +291,7 @@ blockToJATS opts (Header _ _ title) = do
return $ inTagsSimple "title" title'
-- No Plain, everything needs to be in a block-level tag
blockToJATS opts (Plain lst) = blockToJATS opts (Para lst)
--- title beginning with fig: indicates that the image is a figure
-blockToJATS opts (Para [Image (ident,_,kvs) txt
- (src,T.stripPrefix "fig:" -> Just tit)]) = do
+blockToJATS opts (SimpleFigure (ident, _, kvs) txt (src, tit)) = do
alt <- inlinesToJATS opts txt
let (maintype, subtype) = imageMimeType src kvs
let capt = if null txt
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 8c45c8db5..f8847aa08 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -346,10 +346,7 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do
wrapNotes <$> wrapDiv (identifier,classes,kvs) result
blockToLaTeX (Plain lst) =
inlineListToLaTeX lst
--- title beginning with fig: indicates that the image is a figure
-blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,tgt)])
- | Just tit <- T.stripPrefix "fig:" tgt
- = do
+blockToLaTeX (SimpleFigure attr@(ident, _, _) txt (src, tit)) = do
(capt, captForLof, footnotes) <- getCaption inlineListToLaTeX True txt
lab <- labelFor ident
let caption = "\\caption" <> captForLof <> braces capt <> lab
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index fda2bbcef..f03dc375d 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.Markdown
Copyright : Copyright (C) 2006-2021 John MacFarlane
@@ -365,14 +364,13 @@ blockToMarkdown' opts (Plain inlines) = do
_ -> inlines
contents <- inlineListToMarkdown opts inlines'
return $ contents <> cr
--- title beginning with fig: indicates figure
-blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Just tit))])
+blockToMarkdown' opts (SimpleFigure attr alt (src, tit))
| isEnabled Ext_raw_html opts &&
not (isEnabled Ext_link_attributes opts || isEnabled Ext_attributes opts) &&
attr /= nullAttr = -- use raw HTML
(<> blankline) . literal . T.strip <$>
writeHtml5String opts{ writerTemplate = Nothing }
- (Pandoc nullMeta [Para [Image attr alt (src,tgt)]])
+ (Pandoc nullMeta [SimpleFigure attr alt (src, tit)])
| otherwise = blockToMarkdown opts (Para [Image attr alt (src,tit)])
blockToMarkdown' opts (Para inlines) =
(<> blankline) `fmap` blockToMarkdown opts (Plain inlines)
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 5029be69f..c7c53943a 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.MediaWiki
Copyright : Copyright (C) 2008-2021 John MacFarlane
@@ -91,8 +90,7 @@ blockToMediaWiki (Div attrs bs) = do
blockToMediaWiki (Plain inlines) =
inlineListToMediaWiki inlines
--- title beginning with fig: indicates that the image is a figure
-blockToMediaWiki (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do
+blockToMediaWiki (SimpleFigure attr txt (src, tit)) = do
capt <- inlineListToMediaWiki txt
img <- imageToMediaWiki attr
let opt = if T.null tit
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 5f3224c2f..a42c5df64 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.OpenDocument
Copyright : Copyright (C) 2008-2020 Andrea Rossato and John MacFarlane
@@ -377,7 +376,7 @@ blockToOpenDocument o = \case
Plain b -> if null b
then return empty
else inParagraphTags =<< inlinesToOpenDocument o b
- Para [Image attr c (s,T.stripPrefix "fig:" -> Just t)] -> figure attr c s t
+ SimpleFigure attr c (s, t) -> figure attr c s t
Para b -> if null b &&
not (isEnabled Ext_empty_paragraphs o)
then return empty
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index f4a22695c..24e664ae4 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -105,9 +105,7 @@ blockToOrg :: PandocMonad m
blockToOrg Null = return empty
blockToOrg (Div attr bs) = divToOrg attr bs
blockToOrg (Plain inlines) = inlineListToOrg inlines
--- title beginning with fig: indicates that the image is a figure
-blockToOrg (Para [Image attr txt (src,tgt)])
- | Just tit <- T.stripPrefix "fig:" tgt = do
+blockToOrg (SimpleFigure attr txt (src, tit)) = do
capt <- if null txt
then return empty
else ("#+caption: " <>) `fmap` inlineListToOrg txt
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 8b2002851..08733a792 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -219,28 +219,34 @@ blockToRST (Div (ident,classes,_kvs) bs) = do
nest 3 contents $$
blankline
blockToRST (Plain inlines) = inlineListToRST inlines
-blockToRST (Para [Image attr txt (src, rawtit)]) = do
+blockToRST (SimpleFigure attr txt (src, tit)) = do
description <- inlineListToRST txt
dims <- imageDimsToRST attr
- -- title beginning with fig: indicates that the image is a figure
- let (isfig, tit) = case T.stripPrefix "fig:" rawtit of
- Nothing -> (False, rawtit)
- Just tit' -> (True, tit')
- let fig | isfig = "figure:: " <> literal src
- | otherwise = "image:: " <> literal src
- alt | isfig = ":alt: " <> if T.null tit then description else literal tit
- | null txt = empty
+ let fig = "figure:: " <> literal src
+ alt = ":alt: " <> if T.null tit then description else literal tit
+ capt = description
+ (_,cls,_) = attr
+ classes = case cls of
+ [] -> empty
+ ["align-right"] -> ":align: right"
+ ["align-left"] -> ":align: left"
+ ["align-center"] -> ":align: center"
+ _ -> ":figclass: " <> literal (T.unwords cls)
+ return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline
+blockToRST (Para [Image attr txt (src, _)]) = do
+ description <- inlineListToRST txt
+ dims <- imageDimsToRST attr
+ let fig = "image:: " <> literal src
+ alt | null txt = empty
| otherwise = ":alt: " <> description
- capt | isfig = description
- | otherwise = empty
+ capt = empty
(_,cls,_) = attr
classes = case cls of
[] -> empty
["align-right"] -> ":align: right"
["align-left"] -> ":align: left"
["align-center"] -> ":align: center"
- _ | isfig -> ":figclass: " <> literal (T.unwords cls)
- | otherwise -> ":class: " <> literal (T.unwords cls)
+ _ -> ":class: " <> literal (T.unwords cls)
return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline
blockToRST (Para inlines)
| LineBreak `elem` inlines =
@@ -407,7 +413,7 @@ blockListToRST' topLevel blocks = do
toClose Header{} = False
toClose LineBlock{} = False
toClose HorizontalRule = False
- toClose (Para [Image _ _ (_,t)]) = "fig:" `T.isPrefixOf` t
+ toClose SimpleFigure{} = True
toClose Para{} = False
toClose _ = True
commentSep = RawBlock "rst" "..\n\n"
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 6a33b4283..3c5591b3a 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -123,8 +123,7 @@ blockToTexinfo (Plain lst) =
inlineListToTexinfo lst
-- title beginning with fig: indicates that the image is a figure
-blockToTexinfo (Para [Image attr txt (src,tgt)])
- | Just tit <- T.stripPrefix "fig:" tgt = do
+blockToTexinfo (SimpleFigure attr txt (src, tit)) = do
capt <- if null txt
then return empty
else (\c -> text "@caption" <> braces c) `fmap`
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 03d030477..7f0d668e5 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.Textile
Copyright : Copyright (C) 2010-2021 John MacFarlane
@@ -111,8 +110,7 @@ blockToTextile opts (Div attr bs) = do
blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
--- title beginning with fig: indicates that the image is a figure
-blockToTextile opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do
+blockToTextile opts (SimpleFigure attr txt (src, tit)) = do
capt <- blockToTextile opts (Para txt)
im <- inlineToTextile opts (Image attr txt (src,tit))
return $ im <> "\n" <> capt
diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs
index df914f590..5722b6d2e 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.ZimWiki
Copyright : © 2008-2021 John MacFarlane,
@@ -86,9 +85,8 @@ blockToZimWiki opts (Div _attrs bs) = do
blockToZimWiki opts (Plain inlines) = inlineListToZimWiki opts inlines
--- title beginning with fig: indicates that the image is a figure
-- ZimWiki doesn't support captions - so combine together alt and caption into alt
-blockToZimWiki opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do
+blockToZimWiki opts (SimpleFigure attr txt (src, tit)) = do
capt <- if null txt
then return ""
else (" " <>) `fmap` inlineListToZimWiki opts txt