diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 41 |
1 files changed, 20 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index d8b85c1a2..a53c3fb86 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -35,13 +35,13 @@ import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Readers.TeXMath import Data.List ( isPrefixOf, intercalate ) import Data.Char ( toLower ) -import Text.PrettyPrint.HughesPJ hiding ( Str ) import Text.Pandoc.Highlighting (languages, languagesByExtension) +import Text.Pandoc.Pretty -- | Convert list of authors to a docbook <author> section authorToDocbook :: WriterOptions -> [Inline] -> Doc authorToDocbook opts name' = - let name = render $ inlinesToDocbook opts name' + let name = render Nothing $ inlinesToDocbook opts name' in if ',' `elem` name then -- last name first let (lastname, rest) = break (==',') name @@ -61,16 +61,20 @@ authorToDocbook opts name' = -- | Convert Pandoc document to string in Docbook format. writeDocbook :: WriterOptions -> Pandoc -> String writeDocbook opts (Pandoc (Meta tit auths dat) blocks) = - let title = wrap opts tit + let title = inlinesToDocbook opts tit authors = map (authorToDocbook opts) auths date = inlinesToDocbook opts dat elements = hierarchicalize blocks - main = render $ vcat (map (elementToDocbook opts) elements) + colwidth = if writerWrapText opts + then Just $ writerColumns opts + else Nothing + render' = render colwidth + main = render' $ vcat (map (elementToDocbook opts) elements) context = writerVariables opts ++ [ ("body", main) - , ("title", render title) - , ("date", render date) ] ++ - [ ("author", render a) | a <- authors ] + , ("title", render' title) + , ("date", render' date) ] ++ + [ ("author", render' a) | a <- authors ] in if writerStandalone opts then renderTemplate context $ writerTemplate opts else main @@ -84,7 +88,7 @@ elementToDocbook opts (Sec _ _num id' title elements) = then [Blk (Para [])] else elements in inTags True "section" [("id",id')] $ - inTagsSimple "title" (wrap opts title) $$ + inTagsSimple "title" (inlinesToDocbook opts title) $$ vcat (map (elementToDocbook opts) elements') -- | Convert a list of Pandoc blocks to Docbook. @@ -123,7 +127,7 @@ listItemToDocbook opts item = blockToDocbook :: WriterOptions -> Block -> Doc blockToDocbook _ Null = empty blockToDocbook _ (Header _ _) = empty -- should not occur after hierarchicalize -blockToDocbook opts (Plain lst) = wrap opts lst +blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst blockToDocbook opts (Para [Image txt (src,_)]) = let capt = inlinesToDocbook opts txt in inTagsIndented "figure" $ @@ -132,12 +136,13 @@ blockToDocbook opts (Para [Image txt (src,_)]) = (inTagsIndented "imageobject" (selfClosingTag "imagedata" [("fileref",src)])) $$ inTagsSimple "textobject" (inTagsSimple "phrase" capt)) -blockToDocbook opts (Para lst) = inTagsIndented "para" $ wrap opts lst +blockToDocbook opts (Para lst) = + inTagsIndented "para" $ inlinesToDocbook opts lst blockToDocbook opts (BlockQuote blocks) = inTagsIndented "blockquote" $ blocksToDocbook opts blocks blockToDocbook _ (CodeBlock (_,classes,_) str) = - text ("<screen" ++ lang ++ ">\n") <> - text (escapeStringForXML str) <> text "\n</screen>" + text ("<screen" ++ lang ++ ">") <> cr <> + flush (text (escapeStringForXML str) <> cr <> text "</screen>") where lang = if null langs then "" else " language=\"" ++ escapeStringForXML (head langs) ++ @@ -214,12 +219,6 @@ tableItemToDocbook opts tag align item = let attrib = [("align", align)] in inTags True tag attrib $ vcat $ map (blockToDocbook opts) item --- | Take list of inline elements and return wrapped doc. -wrap :: WriterOptions -> [Inline] -> Doc -wrap opts lst = if writerWrapText opts - then fsep $ map (inlinesToDocbook opts) (splitBy (== Space) lst) - else inlinesToDocbook opts lst - -- | Convert a list of inline elements to Docbook. inlinesToDocbook :: WriterOptions -> [Inline] -> Doc inlinesToDocbook opts lst = hcat $ map (inlineToDocbook opts) lst @@ -254,8 +253,8 @@ inlineToDocbook _ (Code str) = inlineToDocbook opts (Math _ str) = inlinesToDocbook opts $ readTeXMath str inlineToDocbook _ (TeX _) = empty inlineToDocbook _ (HtmlInline _) = empty -inlineToDocbook _ LineBreak = text $ "<literallayout></literallayout>" -inlineToDocbook _ Space = char ' ' +inlineToDocbook _ LineBreak = inTagsSimple "literallayout" empty +inlineToDocbook _ Space = space inlineToDocbook opts (Link txt (src, _)) = if isPrefixOf "mailto:" src then let src' = drop 7 src @@ -275,6 +274,6 @@ inlineToDocbook _ (Image _ (src, tit)) = else inTagsIndented "objectinfo" $ inTagsIndented "title" (text $ escapeStringForXML tit) in inTagsIndented "inlinemediaobject" $ inTagsIndented "imageobject" $ - titleDoc $$ selfClosingTag "imagedata" [("fileref", src)] + titleDoc $$ selfClosingTag "imagedata" [("fileref", src)] inlineToDocbook opts (Note contents) = inTagsIndented "footnote" $ blocksToDocbook opts contents |