aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Docbook.hs
diff options
context:
space:
mode:
authorAner Lucero <4rgento@gmail.com>2021-06-09 10:53:35 -0300
committerJohn MacFarlane <jgm@berkeley.edu>2021-10-22 15:14:23 -0700
commit921af3085422ed5896db6996c54009cf2a61a517 (patch)
tree0c1e58837b5105e972ac3717a95c54df14b52a2e /src/Text/Pandoc/Writers/Docbook.hs
parenta9f4bff5e29ed15fb567f4d5f59b60ef3c71933f (diff)
downloadpandoc-921af3085422ed5896db6996c54009cf2a61a517.tar.gz
Use simpleFigure in Readers.
Diffstat (limited to 'src/Text/Pandoc/Writers/Docbook.hs')
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs5
1 files changed, 2 insertions, 3 deletions
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