aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2017-08-19 23:01:38 -0700
committerJohn MacFarlane <[email protected]>2017-08-19 23:01:38 -0700
commitbb2a4f2bc0ef7dcf2e9110762f8994a5c3834574 (patch)
treef414f3c830d01f4cb89dabe5036eb31f86c7d208 /src
parentf11a4b65ad6b7d878327320c9d3ce6a9a1a7fd0f (diff)
Checkpoint - converting writers.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs4
-rw-r--r--src/Text/Pandoc/Writers/CommonMark.hs4
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs16
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs3
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs18
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs23
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs16
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs4
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs20
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs5
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs9
-rw-r--r--src/Text/Pandoc/Writers/Man.hs2
-rw-r--r--src/Text/Pandoc/Writers/Ms.hs2
-rw-r--r--src/Text/Pandoc/Writers/Native.hs5
-rw-r--r--src/Text/Pandoc/Writers/Org.hs13
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs14
16 files changed, 70 insertions, 88 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 112f8b657..a85bdd819 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -137,8 +137,6 @@ blockToAsciiDoc _ Null = return empty
blockToAsciiDoc opts (Plain inlines) = do
contents <- inlineListToAsciiDoc opts inlines
return $ contents <> blankline
-blockToAsciiDoc opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do
- blockToAsciiDoc opts (Para [Image attr alt (src,tit)])
blockToAsciiDoc opts (Para inlines) = do
contents <- inlineListToAsciiDoc opts inlines
-- escape if para starts with ordered list marker
@@ -146,6 +144,8 @@ blockToAsciiDoc opts (Para inlines) = do
then text "\\"
else empty
return $ esc <> contents <> blankline
+blockToAsciiDoc opts (Figure attr _capt bs) =
+ blockListToAsciiDoc opts bs -- TODO use asciidoc syntax for caption etc.
blockToAsciiDoc opts (LineBlock lns) = do
let docify line = if null line
then return blankline
diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs
index 446578f42..84b952608 100644
--- a/src/Text/Pandoc/Writers/CommonMark.hs
+++ b/src/Text/Pandoc/Writers/CommonMark.hs
@@ -139,6 +139,10 @@ blockToNodes opts (Header lev _ ils) ns =
blockToNodes opts (Div _ bs) ns = do
nodes <- blocksToNodes opts bs
return (nodes ++ ns)
+blockToNodes opts (Figure _ (Caption _ cs) bs) ns = do
+ nodes <- blocksToNodes opts bs
+ captNodes <- blocksToNodes opts cs
+ return (nodes ++ captNodes)
blockToNodes opts (DefinitionList items) ns =
blockToNodes opts (BulletList items') ns
where items' = map dlToBullet items
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 6f2cb2b9e..be086439c 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -165,18 +165,18 @@ elementToConTeXt opts (Sec level _ attr title' elements) = do
blockToConTeXt :: PandocMonad m => Block -> WM m Doc
blockToConTeXt Null = return empty
blockToConTeXt (Plain lst) = inlineListToConTeXt lst
--- title beginning with fig: indicates that the image is a figure
-blockToConTeXt (Para [Image attr txt (src,'f':'i':'g':':':_)]) = do
- capt <- inlineListToConTeXt txt
- img <- inlineToConTeXt (Image attr txt (src, ""))
+blockToConTeXt (Para lst) = do
+ contents <- inlineListToConTeXt lst
+ return $ contents <> blankline
+blockToConTeXt (Figure attr (Caption _short capt') bs) = do
+ capt <- inlineListToConTeXt capt'
+ contents <- blockListToConTeXt bs
let (ident, _, _) = attr
label = if null ident
then empty
else "[]" <> brackets (text $ toLabel ident)
- return $ blankline $$ "\\placefigure" <> label <> braces capt <> img <> blankline
-blockToConTeXt (Para lst) = do
- contents <- inlineListToConTeXt lst
- return $ contents <> blankline
+ return $ blankline $$ "\\placefigure" <> label <> braces capt <>
+ contents <> blankline
blockToConTeXt (LineBlock lns) = do
doclines <- nowrap . vcat <$> mapM inlineListToConTeXt lns
return $ "\\startlines" $$ doclines $$ "\\stoplines" <> blankline
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index d7dff6d19..177fbec85 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -182,6 +182,9 @@ blockToCustom (DefinitionList items) =
blockToCustom (Div attr items) =
callFunc "Div" items (attrToMap attr)
+blockToCustom (Figure attr (Caption short long) items) =
+ callFunc "Figure" short long items (attrToMap attr)
+
-- | Convert list of Pandoc block elements to Custom.
blockListToCustom :: [Block] -- ^ List of block elements
-> Lua String
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 9db9a0102..8ce80d365 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -222,22 +222,16 @@ blockToDocbook _ h@(Header _ _ _) = do
report $ BlockNotRendered h
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,'f':'i':'g':':':_)]) = do
- alt <- inlinesToDocbook opts txt
- let capt = if null txt
- then empty
- else inTagsSimple "title" alt
- return $ inTagsIndented "figure" $
- capt $$
- (inTagsIndented "mediaobject" $
- (inTagsIndented "imageobject"
- (imageToDocbook opts attr src)) $$
- inTagsSimple "textobject" (inTagsSimple "phrase" alt))
blockToDocbook opts (Para lst)
| hasLineBreaks lst = (flush . nowrap . inTagsSimple "literallayout")
<$> inlinesToDocbook opts lst
| otherwise = inTagsIndented "para" <$> inlinesToDocbook opts lst
+blockToDocbook opts (Figure attr (Caption _short long) bs) = do
+ alt <- inlinesToDocbook opts txt
+ let capt = if null long
+ then empty
+ else inTagsSimple "title" alt
+ return $ inTagsIndented "figure" $ capt $$ bs
blockToDocbook opts (LineBlock lns) =
blockToDocbook opts $ linesToPara lns
blockToDocbook opts (BlockQuote blocks) =
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 3d6eb9fe5..c55e043ff 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -909,18 +909,6 @@ blockToOpenXML' opts (Header lev (ident,_,_) lst) = do
[bookmarkStart] ++ contents ++ [bookmarkEnd])]
blockToOpenXML' opts (Plain lst) = withParaProp (pCustomStyle "Compact")
$ blockToOpenXML opts (Para lst)
--- title beginning with fig: indicates that the image is a figure
-blockToOpenXML' opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do
- setFirstPara
- let prop = pCustomStyle $
- if null alt
- then "Figure"
- else "CaptionedFigure"
- paraProps <- local (\env -> env { envParaProperties = prop : envParaProperties env }) (getParaProps False)
- contents <- inlinesToOpenXML opts [Image attr alt (src,tit)]
- captionNode <- withParaProp (pCustomStyle "ImageCaption")
- $ blockToOpenXML opts (Para alt)
- return $ mknode "w:p" [] (paraProps ++ contents) : captionNode
-- fixDisplayMath sometimes produces a Para [] as artifact
blockToOpenXML' _ (Para []) = return []
blockToOpenXML' opts (Para lst) = do
@@ -936,6 +924,17 @@ blockToOpenXML' opts (Para lst) = do
modify $ \s -> s { stFirstPara = False }
contents <- inlinesToOpenXML opts lst
return [mknode "w:p" [] (paraProps' ++ contents)]
+blockToOpenXML' opts (Figure attr (Caption _short long) bs) = do
+ setFirstPara
+ let prop = pCustomStyle $
+ if null alt
+ then "Figure"
+ else "CaptionedFigure"
+ paraProps <- local (\env -> env { envParaProperties = prop : envParaProperties env }) (getParaProps False)
+ contents <- blocksToOpenXML opts bs
+ captionNode <- withParaProp (pCustomStyle "ImageCaption")
+ $ blocksToOpenXML opts long
+ return $ mknode "w:p" [] (paraProps ++ contents) : captionNode
blockToOpenXML' opts (LineBlock lns) = blockToOpenXML opts $ linesToPara lns
blockToOpenXML' _ b@(RawBlock format str)
| format == Format "openxml" = return [ x | Elem x <- parseXML str ]
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 279475a21..6802f6c96 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -126,19 +126,6 @@ blockToDokuWiki opts (Div _attrs bs) = do
blockToDokuWiki opts (Plain inlines) =
inlineListToDokuWiki opts 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,'f':'i':'g':':':tit)]) = do
- capt <- if null txt
- then return ""
- else (" " ++) `fmap` inlineListToDokuWiki opts txt
- let opt = if null txt
- then ""
- else "|" ++ if null tit then capt else tit ++ capt
- -- Relative links fail isURI and receive a colon
- prefix = if isURI src then "" else ":"
- return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n"
-
blockToDokuWiki opts (Para inlines) = do
indent <- stIndent <$> ask
useTags <- stUseTags <$> ask
@@ -147,6 +134,9 @@ blockToDokuWiki opts (Para inlines) = do
then "<HTML><p></HTML>" ++ contents ++ "<HTML></p></HTML>"
else contents ++ if null indent then "\n" else ""
+blockToDokuWiki opts (Figure _attr _capt bs) = do
+ blockListToDokuWiki opts bs
+
blockToDokuWiki opts (LineBlock lns) =
blockToDokuWiki opts $ linesToPara lns
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 4c764d987..f1b105fdc 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -320,10 +320,8 @@ linkID i = "l" ++ (show i)
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,'f':'i':'g':':':tit)]) =
- insertImage NormalImage (Image atr alt (src,tit))
blockToXml (Para ss) = liftM (list . el "p") $ cMapM toXml ss
+blockToXml (Figure _attr _capt xs) = cMapM blockToXml bs
blockToXml (CodeBlock _ s) = return . spaceBeforeAfter .
map (el "p" . el "code") . lines $ s
blockToXml b@(RawBlock _ _) = do
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 9ac37a0ba..bf8f26116 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -591,17 +591,17 @@ treatAsImage fp =
in null ext || ext `elem` imageExts
figure :: PandocMonad m
- => WriterOptions -> Attr -> [Inline] -> (String, String)
+ => WriterOptions -> Attr -> [Block] -> [Block] ->
-> StateT WriterState m Html
-figure opts attr txt (s,tit) = do
- img <- inlineToHtml opts (Image attr txt (s,tit))
+figure opts attr caption bs = do
+ bs <- blockListToHtml opts bs
html5 <- gets stHtml5
let tocapt = if html5
then H5.figcaption
else H.p ! A.class_ "caption"
- capt <- if null txt
- then return mempty
- else tocapt `fmap` inlineListToHtml opts txt
+ cs <- if null caption
+ then return mempty
+ else tocapt <$> blockListToHtml opts caption
return $ if html5
then H5.figure $ mconcat
[nl opts, img, capt, nl opts]
@@ -620,10 +620,8 @@ blockToHtml opts (Para [Image attr@(_,classes,_) txt (src,tit)])
-- a "stretched" image in reveal.js must be a direct child
-- of the slide container
inlineToHtml opts (Image attr txt (src, tit))
- _ -> figure opts attr txt (src, tit)
--- title beginning with fig: indicates that the image is a figure
-blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) =
- figure opts attr txt (s,tit)
+ _ -> figure opts attr (Caption txt [Plain txt])
+ [Plain [Image attr txt (src, tit)]]
blockToHtml opts (Para lst)
| isEmptyRaw lst = return mempty
| otherwise = do
@@ -633,6 +631,8 @@ blockToHtml opts (Para lst)
isEmptyRaw [RawInline f _] = f `notElem` [Format "html",
Format "html4", Format "html5"]
isEmptyRaw _ = False
+blockToHtml opts (Figure attr (Caption _short long) bs) =
+ figure opts attr long bs
blockToHtml opts (LineBlock lns) =
if writerWrapText opts == WrapNone
then blockToHtml opts $ linesToPara lns
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index d1146ca73..6ba7536f7 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -109,12 +109,11 @@ blockToHaddock opts (Div _ ils) = do
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,'f':'i':'g':':':tit)]) =
- blockToHaddock opts (Para [Image attr alt (src,tit)])
blockToHaddock opts (Para inlines) =
-- TODO: if it contains linebreaks, we need to use a @...@ block
(<> blankline) `fmap` blockToHaddock opts (Plain inlines)
+blockToHaddock opts (Figure _attr _capt bs) =
+ blockListToHaddock opts bs
blockToHaddock opts (LineBlock lns) =
blockToHaddock opts $ linesToPara lns
blockToHaddock _ b@(RawBlock f str)
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 37df58e65..398a07614 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -297,12 +297,11 @@ blocksToICML opts style lst = do
-- | Convert a Pandoc block element to ICML.
blockToICML :: PandocMonad m => WriterOptions -> Style -> Block -> WS m Doc
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 (_,'f':'i':'g':':':_)]) = do
- figure <- parStyle opts (figureName:style) img
- caption <- parStyle opts (imgCaptionName:style) txt
- return $ intersperseBrs [figure, caption]
blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) lst
+blockToICML opts style (Figure attr (Caption _short capt) bs) = do
+ contents <- blocksToICML opts (figureName:style) bs
+ caption <- blocksToICML opts (imgCaptionName:style) capt
+ return $ intersperseBrs [figure, caption]
blockToICML opts style (LineBlock lns) =
blockToICML opts style $ linesToPara lns
blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) $ [Str str]
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 8adb3e7eb..87fdd9527 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -184,6 +184,8 @@ blockToMan :: PandocMonad m
-> StateT WriterState m Doc
blockToMan _ Null = return empty
blockToMan opts (Div _ bs) = blockListToMan opts bs
+blockToMan opts (Figure _attr (Caption _short long) bs) =
+ blockListToMan opts (bs ++ long)
blockToMan opts (Plain inlines) =
liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines
blockToMan opts (Para inlines) = do
diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs
index 493da1545..54eecdcc6 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -226,7 +226,7 @@ blockToMs opts (Div _ bs) = do
return res
blockToMs opts (Plain inlines) =
liftM vcat $ mapM (inlineListToMs' opts) $ splitSentences inlines
-blockToMs opts (Para [Image attr alt (src,_tit)])
+blockToMs opts (Para [Image attr alt (src,_tit)]) -- figure
| let ext = takeExtension src in (ext == ".ps" || ext == ".eps") = do
let (mbW,mbH) = (inPoints opts <$> dimension Width attr,
inPoints opts <$> dimension Height attr)
diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs
index 3ef33f05c..f972fbc9a 100644
--- a/src/Text/Pandoc/Writers/Native.hs
+++ b/src/Text/Pandoc/Writers/Native.hs
@@ -57,6 +57,11 @@ prettyBlock (DefinitionList items) = "DefinitionList" $$
(prettyList $ map deflistitem items)
where deflistitem (term, defs) = "(" <> text (show term) <> "," <> cr <>
nest 1 (prettyList $ map (prettyList . map prettyBlock) defs) <> ")"
+prettyBlock (Figure attr (Caption short long) bs) =
+ "Figure" <> space <> text (show attr) $$
+ nest 1 ("Caption" <> space <> show short $$
+ nest 1 (prettyList (map prettyBlock long) $$
+ (prettyList (map prettyBlock bs)))
prettyBlock (Table caption aligns widths header rows) =
"Table " <> text (show caption) <> " " <> text (show aligns) <> " " <>
text (show widths) $$
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 48f17c4fb..920facda3 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -160,16 +160,15 @@ blockToOrg (Div attrs bs) = do
contents $$ blankline $$ "#+BEGIN_HTML" $$
nest 2 endTag $$ "#+END_HTML" $$ blankline
blockToOrg (Plain inlines) = inlineListToOrg inlines
--- title beginning with fig: indicates that the image is a figure
-blockToOrg (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
- capt <- if null txt
- then return empty
- else ("#+CAPTION: " <>) `fmap` inlineListToOrg txt
- img <- inlineToOrg (Image attr txt (src,tit))
- return $ capt $$ img $$ blankline
blockToOrg (Para inlines) = do
contents <- inlineListToOrg inlines
return $ contents <> blankline
+blockToOrg (Figure attr (Caption _short long) bs) = do
+ capt <- if null long
+ then return empty
+ else ("#+CAPTION: " <>) `fmap` blockListToOrg long
+ contents <- blockListToOrg bs
+ return $ bs $$ capt $$ blankline
blockToOrg (LineBlock lns) = do
let splitStanza [] = []
splitStanza xs = case break (== mempty) xs of
diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs
index ced02d4be..6a400cad4 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -99,18 +99,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,'f':'i':'g':':':tit)]) = do
- capt <- if null txt
- then return ""
- else (" " ++) `fmap` inlineListToZimWiki opts txt
- let opt = if null txt
- then ""
- else "|" ++ if null tit then capt else tit ++ capt
- -- Relative links fail isURI and receive a colon
- prefix = if isURI src then "" else ":"
- return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n"
+blockToZimWiki opts (Figure _attr _capt bs) =
+ blockListToZimWiki opts bs
blockToZimWiki opts (Para inlines) = do
indent <- gets stIndent