diff options
author | Albert Krewinkel <albert@zeitkraut.de> | 2016-10-13 08:46:44 +0200 |
---|---|---|
committer | Albert Krewinkel <albert@zeitkraut.de> | 2016-10-13 08:46:44 +0200 |
commit | 22cb9e3327ff4aea6109c048a185506e67f07ef1 (patch) | |
tree | f3d18ed0fcfa1c0ad273730151dbc80329590da6 /src/Text/Pandoc/Writers | |
parent | 64b77cc2c5aa9db5432f616f49a660ec9dbbcc9f (diff) | |
download | pandoc-22cb9e3327ff4aea6109c048a185506e67f07ef1.tar.gz |
Add support for the LineBlock element to writers
The following markup features are used to output the lines of the `LineBlock`
element:
- AsciiDoc: a `[verse]` block,
- ConTeXt: text surrounded by `\startlines` and `\endlines`,
- HTML: `div` with an per-element style setting to interpret the content as
pre-wrapped,
- Markdown: line blocks if the `line_blocks` extension is enabled, a simple
paragraph with hard linebreaks otherwise,
- Org: VERSE block,
- RST: a line block, and
- all other formats: a paragraph, containing hard linebreaks between lines.
Custom lua writers should be updated to use the `LineBlock` element.
Diffstat (limited to 'src/Text/Pandoc/Writers')
24 files changed, 102 insertions, 28 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 0dfbd705e..c7097c368 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -137,6 +137,13 @@ blockToAsciiDoc opts (Para inlines) = do then text "\\" else empty return $ esc <> contents <> blankline +blockToAsciiDoc opts (LineBlock lns) = do + let docify line = if null line + then return blankline + else inlineListToAsciiDoc opts line + let joinWithLinefeeds = nowrap . mconcat . intersperse cr + contents <- joinWithLinefeeds <$> mapM docify lns + return $ "[verse]" $$ text "--" $$ contents $$ text "--" $$ blankline blockToAsciiDoc _ (RawBlock f s) | f == "asciidoc" = return $ text s | otherwise = return empty @@ -459,4 +466,3 @@ inlineToAsciiDoc opts (Span (ident,_,_) ils) = do let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]") contents <- inlineListToAsciiDoc opts ils return $ identifier <> contents - diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 262f491a8..c6509fe92 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -33,7 +33,7 @@ module Text.Pandoc.Writers.CommonMark (writeCommonMark) where import Text.Pandoc.Writers.HTML (writeHtmlString) import Text.Pandoc.Definition -import Text.Pandoc.Shared (isTightList) +import Text.Pandoc.Shared (isTightList, linesToPara) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Shared import Text.Pandoc.Options @@ -94,6 +94,7 @@ blocksToNodes = foldr blockToNodes [] blockToNodes :: Block -> [Node] -> [Node] blockToNodes (Plain xs) = (node PARAGRAPH (inlinesToNodes xs) :) blockToNodes (Para xs) = (node PARAGRAPH (inlinesToNodes xs) :) +blockToNodes (LineBlock lns) = blockToNodes $ linesToPara lns blockToNodes (CodeBlock (_,classes,_) xs) = (node (CODE_BLOCK (T.pack (unwords classes)) (T.pack xs)) [] :) blockToNodes (RawBlock fmt xs) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 8d54d62bd..398d4170f 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -163,6 +163,9 @@ blockToConTeXt (Para [Image attr txt (src,'f':'i':'g':':':_)]) = do blockToConTeXt (Para lst) = do contents <- inlineListToConTeXt lst return $ contents <> blankline +blockToConTeXt (LineBlock lns) = do + doclines <- nowrap . vcat <$> mapM inlineListToConTeXt lns + return $ "\\startlines" $$ doclines $$ "\\stoplines" <> blankline blockToConTeXt (BlockQuote lst) = do contents <- blockListToConTeXt lst return $ "\\startblockquote" $$ nest 0 contents $$ "\\stopblockquote" <> blankline @@ -467,4 +470,3 @@ fromBcp47 x = fromIso $ head x fromIso "vi" = "vn" fromIso "zh" = "cn" fromIso l = l - diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index d69eaaa64..631241724 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -227,6 +227,8 @@ blockToCustom lua (Para [Image attr txt (src,tit)]) = blockToCustom lua (Para inlines) = callfunc lua "Para" inlines +blockToCustom lua (LineBlock linesList) = callfunc lua "LineBlock" linesList + blockToCustom lua (RawBlock format str) = callfunc lua "RawBlock" format str diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 8bb0810e4..e19b4666b 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -198,6 +198,8 @@ blockToDocbook opts (Para [Image attr txt (src,'f':'i':'g':':':_)]) = blockToDocbook opts (Para lst) | hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst | otherwise = inTagsIndented "para" $ inlinesToDocbook opts lst +blockToDocbook opts (LineBlock lns) = + blockToDocbook opts $ linesToPara lns blockToDocbook opts (BlockQuote blocks) = inTagsIndented "blockquote" $ blocksToDocbook opts blocks blockToDocbook _ (CodeBlock (_,classes,_) str) = @@ -385,4 +387,3 @@ idAndRole (id',cls,_) = ident ++ role role = if null cls then [] else [("role", unwords cls)] - diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a006773d6..dfa011784 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -275,7 +275,7 @@ writeDocx opts doc@(Pandoc meta _) = do } - ((contents, footnotes), st) <- runStateT + ((contents, footnotes), st) <- runStateT (runReaderT (writeOpenXML opts{writerWrapText = WrapNone} doc') env) @@ -446,7 +446,7 @@ writeDocx opts doc@(Pandoc meta _) = do let newstyles = map newParaPropToOpenXml newDynamicParaProps ++ map newTextPropToOpenXml newDynamicTextProps ++ - (styleToOpenXml styleMaps $ writerHighlightStyle opts) + (styleToOpenXml styleMaps $ writerHighlightStyle opts) let styledoc' = styledoc{ elContent = modifyContent (elContent styledoc) } where modifyContent @@ -859,6 +859,7 @@ blockToOpenXML' opts (Para lst) = do modify $ \s -> s { stFirstPara = False } contents <- inlinesToOpenXML opts lst return [mknode "w:p" [] (paraProps' ++ contents)] +blockToOpenXML' opts (LineBlock lns) = blockToOpenXML opts $ linesToPara lns blockToOpenXML' _ (RawBlock format str) | format == Format "openxml" = return [ x | Elem x <- parseXML str ] | otherwise = return [] @@ -1032,7 +1033,7 @@ setFirstPara = modify $ \s -> s { stFirstPara = True } -- | Convert an inline element to OpenXML. inlineToOpenXML :: WriterOptions -> Inline -> WS [Element] -inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il +inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il inlineToOpenXML' :: WriterOptions -> Inline -> WS [Element] inlineToOpenXML' _ (Str str) = formattedString str @@ -1286,7 +1287,7 @@ withDirection x = do textProps <- asks envTextProperties -- We want to clean all bidirection (bidi) and right-to-left (rtl) -- properties from the props first. This is because we don't want - -- them to stack up. + -- them to stack up. let paraProps' = filter (\e -> (qName . elName) e /= "bidi") paraProps textProps' = filter (\e -> (qName . elName) e /= "rtl") textProps if isRTL @@ -1298,5 +1299,3 @@ withDirection x = do else flip local x $ \env -> env { envParaProperties = paraProps' , envTextProperties = textProps' } - - diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 56e2b9027..402b74bc3 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -45,8 +45,8 @@ import Text.Pandoc.Options ( WriterOptions( , writerStandalone , writerTemplate , writerWrapText), WrapOption(..) ) -import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated - , trimr, normalize, substitute ) +import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting + , camelCaseToHyphenated, trimr, normalize, substitute ) import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) import Text.Pandoc.ImageSize import Text.Pandoc.Templates ( renderTemplate' ) @@ -147,6 +147,9 @@ blockToDokuWiki opts (Para inlines) = do then "<HTML><p></HTML>" ++ contents ++ "<HTML></p></HTML>" else contents ++ if null indent then "\n" else "" +blockToDokuWiki opts (LineBlock lns) = + blockToDokuWiki opts $ linesToPara lns + blockToDokuWiki _ (RawBlock f str) | f == Format "dokuwiki" = return str -- See https://www.dokuwiki.org/wiki:syntax diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 80296e111..6f47dbcd2 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -46,7 +46,8 @@ import qualified Text.XML.Light.Cursor as XC import Text.Pandoc.Definition import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def) -import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize) +import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize, + linesToPara) -- | Data to be written at the end of the document: -- (foot)notes, URLs, references, images. @@ -323,6 +324,7 @@ blockToXml (RawBlock _ s) = return . spaceBeforeAfter . map (el "p" . el "code") . lines $ s blockToXml (Div _ bs) = cMapM blockToXml bs blockToXml (BlockQuote bs) = liftM (list . el "cite") $ cMapM blockToXml bs +blockToXml (LineBlock lns) = blockToXml $ linesToPara lns blockToXml (OrderedList a bss) = do state <- get let pmrk = parentListMarker state diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index db8c301ef..2d0df4dbe 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -463,6 +463,13 @@ blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) = do blockToHtml opts (Para lst) = do contents <- inlineListToHtml opts lst return $ H.p contents +blockToHtml opts (LineBlock lns) = + if writerWrapText opts == WrapNone + then blockToHtml opts $ linesToPara lns + else do + let lf = preEscapedString "\n" + htmlLines <- mconcat . intersperse lf <$> mapM (inlineListToHtml opts) lns + return $ H.div ! A.style "white-space: pre-line;" $ htmlLines blockToHtml opts (Div attr@(ident, classes, kvs) bs) = do let speakerNotes = "notes" `elem` classes -- we don't want incremental output inside speaker notes, see #1394 @@ -807,7 +814,7 @@ inlineToHtml opts inline = let brtag = if writerHtml5 opts then H5.br else H.br return $ case t of InlineMath -> m - DisplayMath -> brtag >> m >> brtag + DisplayMath -> brtag >> m >> brtag (RawInline f str) | f == Format "html" -> return $ preEscapedString str | otherwise -> return mempty diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 2e5f2dd08..caf549916 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -108,6 +108,8 @@ blockToHaddock opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = blockToHaddock opts (Para inlines) = -- TODO: if it contains linebreaks, we need to use a @...@ block (<> blankline) `fmap` blockToHaddock opts (Plain inlines) +blockToHaddock opts (LineBlock lns) = + blockToHaddock opts $ linesToPara lns blockToHaddock _ (RawBlock f str) | f == "haddock" = do return $ text str <> text "\n" diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 57a61178e..8f6123e20 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -2,7 +2,7 @@ {- | Module : Text.Pandoc.Writers.ICML - Copyright : Copyright (C) 2013 github.com/mb21 + Copyright : Copyright (C) 2013-2016 github.com/mb21 License : GNU GPL, version 2 or above Stability : alpha @@ -18,7 +18,7 @@ import Text.Pandoc.Definition import Text.Pandoc.XML import Text.Pandoc.Readers.TeXMath (texMathToInlines) import Text.Pandoc.Writers.Shared -import Text.Pandoc.Shared (splitBy, fetchItem, warn) +import Text.Pandoc.Shared (linesToPara, splitBy, fetchItem, warn) import Text.Pandoc.Options import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Pretty @@ -297,6 +297,8 @@ blockToICML opts style (Para img@[Image _ txt (_,'f':'i':'g':':':_)]) = do caption <- parStyle opts (imgCaptionName:style) txt return $ intersperseBrs [figure, caption] blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) lst +blockToICML opts style (LineBlock lns) = + blockToICML opts style $ linesToPara lns blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) $ [Str str] blockToICML _ _ (RawBlock f str) | f == Format "icml" = return $ text str diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index a88ff303f..517460f5d 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -437,6 +437,8 @@ blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do else inlineListToLaTeX [Str ".",Space,Str ".",Space,Str "."] blockToLaTeX (Para lst) = inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst +blockToLaTeX (LineBlock lns) = do + blockToLaTeX $ linesToPara lns blockToLaTeX (BlockQuote lst) = do beamer <- writerBeamer `fmap` gets stOptions case lst of diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index caf26d515..159e89308 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -171,6 +171,8 @@ blockToMan opts (Para inlines) = do contents <- liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines return $ text ".PP" $$ contents +blockToMan opts (LineBlock lns) = + blockToMan opts $ linesToPara lns blockToMan _ (RawBlock f str) | f == Format "man" = return $ text str | otherwise = return empty @@ -367,4 +369,3 @@ inlineToMan _ (Note contents) = do notes <- liftM stNotes get let ref = show $ (length notes) return $ char '[' <> text ref <> char ']' - diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 3ad31d54a..379efd120 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -79,7 +79,7 @@ instance Default WriterEnv , envRefShortcutable = True , envBlockLevel = 0 } - + data WriterState = WriterState { stNotes :: Notes , stRefs :: Refs , stIds :: Set.Set String @@ -390,6 +390,12 @@ blockToMarkdown' opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = blockToMarkdown opts (Para [Image attr alt (src,tit)]) blockToMarkdown' opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) +blockToMarkdown' opts (LineBlock lns) = + if isEnabled Ext_line_blocks opts + then do + mdLines <- mapM (inlineListToMarkdown opts) lns + return $ (vcat $ map (hang 2 (text "| ")) mdLines) <> blankline + else blockToMarkdown opts $ linesToPara lns blockToMarkdown' opts (RawBlock f str) | f == "markdown" = return $ text str <> text "\n" | f == "html" && isEnabled Ext_raw_html opts = do diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 0da8bc98c..3b2028997 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -120,6 +120,9 @@ blockToMediaWiki (Para inlines) = do then "<p>" ++ contents ++ "</p>" else contents ++ if null lev then "\n" else "" +blockToMediaWiki (LineBlock lns) = + blockToMediaWiki $ linesToPara lns + blockToMediaWiki (RawBlock f str) | f == Format "mediawiki" = return str | f == Format "html" = return str diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index fc96e3e3c..2a9bc5138 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -45,6 +45,8 @@ prettyList ds = -- | Prettyprint Pandoc block element. prettyBlock :: Block -> Doc +prettyBlock (LineBlock lines') = + "LineBlock" $$ prettyList (map (text . show) lines') prettyBlock (BlockQuote blocks) = "BlockQuote" $$ prettyList (map prettyBlock blocks) prettyBlock (OrderedList attribs blockLists) = diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index e0434c630..583aa2e4a 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -33,6 +33,7 @@ module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.XML +import Text.Pandoc.Shared (linesToPara) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Pretty @@ -291,6 +292,7 @@ blockToOpenDocument o bs | Para b <- bs = if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b + | LineBlock b <- bs = blockToOpenDocument o $ linesToPara b | Div _ xs <- bs = blocksToOpenDocument o xs | Header i _ b <- bs = setFirstPara >> (inHeaderTags i =<< inlinesToOpenDocument o b) diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 96baacbb6..a74481171 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -164,6 +164,17 @@ blockToOrg (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do blockToOrg (Para inlines) = do contents <- inlineListToOrg inlines return $ contents <> blankline +blockToOrg (LineBlock lns) = do + let splitStanza [] = [] + splitStanza xs = case break (== mempty) xs of + (l, []) -> l : [] + (l, _:r) -> l : splitStanza r + let joinWithLinefeeds = nowrap . mconcat . intersperse cr + let joinWithBlankLines = mconcat . intersperse blankline + let prettyfyStanza ls = joinWithLinefeeds <$> mapM inlineListToOrg ls + contents <- joinWithBlankLines <$> mapM prettyfyStanza (splitStanza lns) + return $ blankline $$ "#+BEGIN_VERSE" $$ + nest 2 contents $$ "#+END_VERSE" <> blankline blockToOrg (RawBlock "html" str) = return $ blankline $$ "#+BEGIN_HTML" $$ nest 2 (text str) $$ "#+END_HTML" $$ blankline diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 98c39bdaf..21f1acd6e 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -201,11 +201,12 @@ blockToRST (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline blockToRST (Para inlines) | LineBreak `elem` inlines = do -- use line block if LineBreaks - lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines - return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline + linesToLineBlock $ splitBy (==LineBreak) inlines | otherwise = do contents <- inlineListToRST inlines return $ contents <> blankline +blockToRST (LineBlock lns) = + linesToLineBlock lns blockToRST (RawBlock f@(Format f') str) | f == "rst" = return $ text str | otherwise = return $ blankline <> ".. raw:: " <> @@ -328,6 +329,12 @@ definitionListItemToRST (label, defs) = do tabstop <- get >>= (return . writerTabStop . stOptions) return $ label' $$ nest tabstop (nestle contents <> cr) +-- | Format a list of lines as line block. +linesToLineBlock :: [[Inline]] -> State WriterState Doc +linesToLineBlock inlineLines = do + lns <- mapM inlineListToRST inlineLines + return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline + -- | Convert list of Pandoc block elements to RST. blockListToRST' :: Bool -> [Block] -- ^ List of block elements diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 79a28c880..b87ef0fd3 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -233,6 +233,8 @@ blockToRTF indent alignment (Plain lst) = rtfCompact indent 0 alignment $ inlineListToRTF lst blockToRTF indent alignment (Para lst) = rtfPar indent 0 alignment $ inlineListToRTF lst +blockToRTF indent alignment (LineBlock lns) = + blockToRTF indent alignment $ linesToPara lns blockToRTF indent alignment (BlockQuote lst) = concatMap (blockToRTF (indent + indentIncrement) alignment) lst blockToRTF indent _ (CodeBlock _ str) = diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index b9e683ab9..018884202 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -108,7 +108,7 @@ plainToPara :: Block -> Block plainToPara (Plain x) = Para x plainToPara x = x --- | Convert a list of pairs of terms and definitions into a TEI +-- | Convert a list of pairs of terms and definitions into a TEI -- list with labels and items. deflistItemsToTEI :: WriterOptions -> [([Inline],[[Block]])] -> Doc deflistItemsToTEI opts items = @@ -167,6 +167,8 @@ blockToTEI opts (Plain lst) = blockToTEI opts $ Para lst -- inTagsSimple "textobject" (inTagsSimple "phrase" alt)) blockToTEI opts (Para lst) = inTags False "p" [] $ inlinesToTEI opts lst +blockToTEI opts (LineBlock lns) = + blockToTEI opts $ linesToPara lns blockToTEI opts (BlockQuote blocks) = inTagsIndented "quote" $ blocksToTEI opts blocks blockToTEI _ (CodeBlock (_,classes,_) str) = @@ -174,7 +176,7 @@ blockToTEI _ (CodeBlock (_,classes,_) str) = flush (text (escapeStringForXML str) <> cr <> text "</ab>") where lang = if null langs then "" - else escapeStringForXML (head langs) + else escapeStringForXML (head langs) isLang l = map toLower l `elem` map (map toLower) languages langsFrom s = if isLang s then [s] @@ -210,7 +212,7 @@ blockToTEI _ HorizontalRule = selfClosingTag "milestone" [("unit","undefined"), ("type","separator"),("rendition","line")] -- | TEI Tables --- TEI Simple's tables are composed of cells and rows; other +-- TEI Simple's tables are composed of cells and rows; other -- table info in the AST is here lossily discard. blockToTEI opts (Table _ _ _ headers rows) = let @@ -219,8 +221,8 @@ blockToTEI opts (Table _ _ _ headers rows) = -- then return empty -- else tableRowToTEI opts headers in - inTags True "table" [] $ - vcat $ [headers'] <> map (tableRowToTEI opts) rows + inTags True "table" [] $ + vcat $ [headers'] <> map (tableRowToTEI opts) rows tableRowToTEI :: WriterOptions -> [[Block]] @@ -276,7 +278,7 @@ inlineToTEI _ (Math t str) = text (str) DisplayMath -> inTags True "figure" [("type","math")] $ inTags False "formula" [("notation","TeX")] $ text (str) - + inlineToTEI _ (RawInline f x) | f == "tei" = text x | otherwise = empty inlineToTEI _ LineBreak = selfClosingTag "lb" [] @@ -317,4 +319,3 @@ idAndRole (id',cls,_) = ident ++ role role = if null cls then [] else [("role", unwords cls)] - diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 8420704dc..b94229943 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -145,6 +145,9 @@ blockToTexinfo (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do blockToTexinfo (Para lst) = inlineListToTexinfo lst -- this is handled differently from Plain in blockListToTexinfo +blockToTexinfo (LineBlock lns) = + blockToTexinfo $ linesToPara lns + blockToTexinfo (BlockQuote lst) = do contents <- blockListToTexinfo lst return $ text "@quotation" $$ diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 98f9157fb..ec70f3072 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -130,6 +130,9 @@ blockToTextile opts (Para inlines) = do then "<p>" ++ contents ++ "</p>" else contents ++ if null listLevel then "\n" else "" +blockToTextile opts (LineBlock lns) = + blockToTextile opts $ linesToPara lns + blockToTextile _ (RawBlock f str) | f == Format "html" || f == Format "textile" = return str | otherwise = return "" diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 05563970a..8afbfef92 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -33,7 +33,8 @@ http://zim-wiki.org/manual/Help/Wiki_Syntax.html module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where import Text.Pandoc.Definition import Text.Pandoc.Options ( WriterOptions(writerTableOfContents, writerStandalone, writerTemplate, writerWrapText), WrapOption(..) ) -import Text.Pandoc.Shared ( escapeURI, removeFormatting, trimr, substitute ) +import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting, trimr + , substitute ) import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) import Text.Pandoc.ImageSize import Text.Pandoc.Templates ( renderTemplate' ) @@ -111,6 +112,9 @@ blockToZimWiki opts (Para inlines) = do contents <- inlineListToZimWiki opts inlines return $ contents ++ if null indent then "\n" else "" +blockToZimWiki opts (LineBlock lns) = do + blockToZimWiki opts $ linesToPara lns + blockToZimWiki opts (RawBlock f str) | f == Format "zimwiki" = return str | f == Format "html" = do cont <- indentFromHTML opts str; return cont |