Merge pull request #1240 from neilmayhew/master
Docbook output of Line Blocks
This commit is contained in:
commit
857fcff7d6
4 changed files with 72 additions and 7 deletions
|
@ -32,12 +32,14 @@ module Text.Pandoc.Writers.Docbook ( writeDocbook) where
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.XML
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Pandoc.Writers.Shared
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
import Text.Pandoc.Readers.TeXMath
|
||||
import Data.List ( isPrefixOf, intercalate, isSuffixOf )
|
||||
import Data.Char ( toLower )
|
||||
import Data.Monoid ( Any(..) )
|
||||
import Text.Pandoc.Highlighting ( languages, languagesByExtension )
|
||||
import Text.Pandoc.Pretty
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
|
@ -165,8 +167,9 @@ blockToDocbook opts (Para [Image txt (src,'f':'i':'g':':':_)]) =
|
|||
(inTagsIndented "imageobject"
|
||||
(selfClosingTag "imagedata" [("fileref",src)])) $$
|
||||
inTagsSimple "textobject" (inTagsSimple "phrase" alt))
|
||||
blockToDocbook opts (Para lst) =
|
||||
inTagsIndented "para" $ inlinesToDocbook opts lst
|
||||
blockToDocbook opts (Para lst)
|
||||
| hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst
|
||||
| otherwise = inTagsIndented "para" $ inlinesToDocbook opts lst
|
||||
blockToDocbook opts (BlockQuote blocks) =
|
||||
inTagsIndented "blockquote" $ blocksToDocbook opts blocks
|
||||
blockToDocbook _ (CodeBlock (_,classes,_) str) =
|
||||
|
@ -226,6 +229,16 @@ blockToDocbook opts (Table caption aligns widths headers rows) =
|
|||
(inTags True "tgroup" [("cols", show (length headers))] $
|
||||
coltags $$ head' $$ body')
|
||||
|
||||
hasLineBreaks :: [Inline] -> Bool
|
||||
hasLineBreaks = getAny . query isLineBreak . walk removeNote
|
||||
where
|
||||
removeNote :: Inline -> Inline
|
||||
removeNote (Note _) = Str ""
|
||||
removeNote x = x
|
||||
isLineBreak :: Inline -> Any
|
||||
isLineBreak LineBreak = Any True
|
||||
isLineBreak _ = Any False
|
||||
|
||||
alignmentToString :: Alignment -> [Char]
|
||||
alignmentToString alignment = case alignment of
|
||||
AlignLeft -> "left"
|
||||
|
@ -293,7 +306,7 @@ inlineToDocbook opts (Math t str)
|
|||
fixNS = everywhere (mkT fixNS')
|
||||
inlineToDocbook _ (RawInline f x) | f == "html" || f == "docbook" = text x
|
||||
| otherwise = empty
|
||||
inlineToDocbook _ LineBreak = flush $ inTagsSimple "literallayout" (text "\n")
|
||||
inlineToDocbook _ LineBreak = text "\n"
|
||||
inlineToDocbook _ Space = space
|
||||
inlineToDocbook opts (Link txt (src, _)) =
|
||||
if isPrefixOf "mailto:" src
|
||||
|
|
52
tests/Tests/Writers/Docbook.hs
Normal file
52
tests/Tests/Writers/Docbook.hs
Normal file
|
@ -0,0 +1,52 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.Docbook (tests) where
|
||||
|
||||
import Test.Framework
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc
|
||||
import Tests.Helpers
|
||||
import Tests.Arbitrary()
|
||||
|
||||
docbook :: (ToString a, ToPandoc a) => a -> String
|
||||
docbook = writeDocbook def{ writerWrapText = False } . toPandoc
|
||||
|
||||
{-
|
||||
"my test" =: X =?> Y
|
||||
|
||||
is shorthand for
|
||||
|
||||
test docbook "my test" $ X =?> Y
|
||||
|
||||
which is in turn shorthand for
|
||||
|
||||
test docbook "my test" (X,Y)
|
||||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
=> String -> (a, String) -> Test
|
||||
(=:) = test docbook
|
||||
|
||||
lineblock :: Blocks
|
||||
lineblock = para ("some text" <> linebreak <>
|
||||
"and more lines" <> linebreak <>
|
||||
"and again")
|
||||
lineblock_out :: String
|
||||
lineblock_out = "<literallayout>some text\n" ++
|
||||
"and more lines\n" ++
|
||||
"and again</literallayout>"
|
||||
|
||||
tests :: [Test]
|
||||
tests = [ testGroup "line blocks"
|
||||
[ "none" =: para "This is a test"
|
||||
=?> "<para>\n This is a test\n</para>"
|
||||
, "basic" =: lineblock
|
||||
=?> lineblock_out
|
||||
, "blockquote" =: blockQuote lineblock
|
||||
=?> ("<blockquote>\n" ++ lineblock_out ++ "\n</blockquote>")
|
||||
, "footnote" =: para ("This is a test" <> note lineblock <> " of footnotes")
|
||||
=?> ("<para>\n This is a test<footnote>\n" ++
|
||||
lineblock_out ++
|
||||
"\n </footnote> of footnotes\n</para>")
|
||||
]
|
||||
]
|
|
@ -12,6 +12,7 @@ import qualified Tests.Readers.RST
|
|||
import qualified Tests.Writers.ConTeXt
|
||||
import qualified Tests.Writers.LaTeX
|
||||
import qualified Tests.Writers.HTML
|
||||
import qualified Tests.Writers.Docbook
|
||||
import qualified Tests.Writers.Native
|
||||
import qualified Tests.Writers.Markdown
|
||||
import qualified Tests.Shared
|
||||
|
@ -27,6 +28,7 @@ tests = [ testGroup "Old" Tests.Old.tests
|
|||
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests
|
||||
, testGroup "LaTeX" Tests.Writers.LaTeX.tests
|
||||
, testGroup "HTML" Tests.Writers.HTML.tests
|
||||
, testGroup "Docbook" Tests.Writers.Docbook.tests
|
||||
, testGroup "Markdown" Tests.Writers.Markdown.tests
|
||||
]
|
||||
, testGroup "Readers"
|
||||
|
|
|
@ -68,10 +68,8 @@
|
|||
<para>
|
||||
Here’s one with a bullet. * criminey.
|
||||
</para>
|
||||
<para>
|
||||
There should be a hard line break<literallayout>
|
||||
</literallayout>here.
|
||||
</para>
|
||||
<literallayout>There should be a hard line break
|
||||
here.</literallayout>
|
||||
</sect1>
|
||||
<sect1 id="block-quotes">
|
||||
<title>Block Quotes</title>
|
||||
|
|
Loading…
Add table
Reference in a new issue