diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Haddock.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ICML.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 87 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 15 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 15 |
10 files changed, 133 insertions, 76 deletions
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 482cae3db..597851f65 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -47,7 +47,8 @@ import qualified Text.Pandoc.Builder as B import Text.TeXMath import qualified Text.XML.Light as Xml import Data.Generics (everywhere, mkT) -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Logging import Control.Monad.Reader data DocBookVersion = DocBook4 | DocBook5 @@ -275,14 +276,16 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) = do blockToDocbook opts (DefinitionList lst) = do let attribs = [("spacing", "compact") | isTightList $ concatMap snd lst] inTags True "variablelist" attribs <$> deflistItemsToDocbook opts lst -blockToDocbook _ (RawBlock f str) +blockToDocbook _ b@(RawBlock f str) | f == "docbook" = return $ text str -- raw XML block | f == "html" = do version <- ask if version == DocBook5 then return empty -- No html in Docbook5 else return $ text str -- allow html for backwards compatibility - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToDocbook _ HorizontalRule = return empty -- not semantic blockToDocbook opts (Table caption aligns widths headers rows) = do captionDoc <- if null caption @@ -384,9 +387,11 @@ inlineToDocbook opts (Math t str) removeAttr e = e{ Xml.elAttribs = [] } fixNS' qname = qname{ Xml.qPrefix = Just "mml" } fixNS = everywhere (mkT fixNS') -inlineToDocbook _ (RawInline f x) +inlineToDocbook _ il@(RawInline f x) | f == "html" || f == "docbook" = return $ text x - | otherwise = return empty + | otherwise = do + report $ InlineNotRendered il + return empty inlineToDocbook _ LineBreak = return $ text "\n" -- currently ignore, would require the option to add custom -- styles to the document diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 235358bf6..56aa29211 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -859,9 +859,11 @@ blockToOpenXML' opts (Para lst) = do contents <- inlinesToOpenXML opts lst return [mknode "w:p" [] (paraProps' ++ contents)] blockToOpenXML' opts (LineBlock lns) = blockToOpenXML opts $ linesToPara lns -blockToOpenXML' _ (RawBlock format str) +blockToOpenXML' _ b@(RawBlock format str) | format == Format "openxml" = return [ x | Elem x <- parseXML str ] - | otherwise = return [] + | otherwise = do + report $ BlockNotRendered b + return [] blockToOpenXML' opts (BlockQuote blocks) = do p <- withParaPropM (pStyleM "Block Text") $ blocksToOpenXML opts blocks setFirstPara @@ -1099,9 +1101,11 @@ inlineToOpenXML' opts (Strikeout lst) = withTextProp (mknode "w:strike" [] ()) $ inlinesToOpenXML opts lst inlineToOpenXML' _ LineBreak = return [br] -inlineToOpenXML' _ (RawInline f str) +inlineToOpenXML' _ il@(RawInline f str) | f == Format "openxml" = return [ x | Elem x <- parseXML str ] - | otherwise = return [] + | otherwise = do + report $ InlineNotRendered il + return [] inlineToOpenXML' opts (Quoted quoteType lst) = inlinesToOpenXML opts $ [Str open] ++ lst ++ [Str close] where (open, close) = case quoteType of diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 1c160ea1c..945e4a0f1 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -42,7 +42,8 @@ import Control.Monad.State import Text.Pandoc.Writers.Math (texMathToInlines) import Network.URI (isURI) import Data.Default -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Logging type Notes = [[Block]] data WriterState = WriterState { stNotes :: Notes } @@ -114,10 +115,12 @@ blockToHaddock opts (Para inlines) = (<> blankline) `fmap` blockToHaddock opts (Plain inlines) blockToHaddock opts (LineBlock lns) = blockToHaddock opts $ linesToPara lns -blockToHaddock _ (RawBlock f str) +blockToHaddock _ b@(RawBlock f str) | f == "haddock" = do return $ text str <> text "\n" - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToHaddock opts HorizontalRule = return $ blankline <> text (replicate (writerColumns opts) '_') <> blankline blockToHaddock opts (Header level (ident,_,_) inlines) = do @@ -334,9 +337,11 @@ inlineToHaddock opts (Math mt str) = do DisplayMath -> cr <> x <> cr InlineMath -> x adjust <$> (lift (texMathToInlines mt str) >>= inlineListToHaddock opts) -inlineToHaddock _ (RawInline f str) +inlineToHaddock _ il@(RawInline f str) | f == "haddock" = return $ text str - | otherwise = return empty + | otherwise = do + report $ InlineNotRendered il + return empty -- no line break in haddock (see above on CodeBlock) inlineToHaddock _ LineBreak = return cr inlineToHaddock opts SoftBreak = diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 50edc1865..efec17d26 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -304,9 +304,11 @@ 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) +blockToICML _ _ b@(RawBlock f str) | f == Format "icml" = return $ text str - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToICML opts style (BlockQuote blocks) = blocksToICML opts (blockQuoteName:style) blocks blockToICML opts style (OrderedList attribs lst) = listItemsToICML opts orderedListName style (Just attribs) lst blockToICML opts style (BulletList lst) = listItemsToICML opts bulletListName style Nothing lst @@ -439,9 +441,11 @@ inlineToICML _ style LineBreak = charStyle style $ text lineSeparator inlineToICML opts style (Math mt str) = lift (texMathToInlines mt str) >>= (fmap cat . mapM (inlineToICML opts style)) -inlineToICML _ _ (RawInline f str) +inlineToICML _ _ il@(RawInline f str) | f == Format "icml" = return $ text str - | otherwise = return empty + | otherwise = do + report $ InlineNotRendered il + return empty inlineToICML opts style (Link _ lst (url, title)) = do content <- inlinesToICML opts (linkName:style) lst state $ \st -> diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 9e987406a..ac2b5d758 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -39,6 +39,7 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Templates +import Text.Pandoc.Logging import Text.Printf ( printf ) import Network.URI ( isURI, unEscapeString ) import Data.Aeson (object, (.=), FromJSON) @@ -57,7 +58,7 @@ import Text.Pandoc.Slides import Text.Pandoc.Highlighting (highlight, styleToLaTeX, formatLaTeXInline, formatLaTeXBlock, toListingsLanguage) -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) data WriterState = WriterState { stInNote :: Bool -- true if we're in a note @@ -110,17 +111,20 @@ startingState options = WriterState { -- | Convert Pandoc to LaTeX. writeLaTeX :: PandocMonad m => WriterOptions -> Pandoc -> m String -writeLaTeX options document = return $ - evalState (pandocToLaTeX options document) $ +writeLaTeX options document = + evalStateT (pandocToLaTeX options document) $ startingState options -- | Convert Pandoc to LaTeX Beamer. writeBeamer :: PandocMonad m => WriterOptions -> Pandoc -> m String -writeBeamer options document = return $ - evalState (pandocToLaTeX options document) $ +writeBeamer options document = + evalStateT (pandocToLaTeX options document) $ (startingState options){ stBeamer = True } -pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String +type LW m = StateT WriterState m + +pandocToLaTeX :: PandocMonad m + => WriterOptions -> Pandoc -> LW m String pandocToLaTeX options (Pandoc meta blocks) = do -- Strip off final 'references' header if --natbib or --biblatex let method = writerCiteMethod options @@ -279,7 +283,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do Just tpl -> renderTemplate' tpl context' -- | Convert Elements to LaTeX -elementToLaTeX :: WriterOptions -> Element -> State WriterState Doc +elementToLaTeX :: PandocMonad m => WriterOptions -> Element -> LW m Doc elementToLaTeX _ (Blk block) = blockToLaTeX block elementToLaTeX opts (Sec level _ (id',classes,_) title' elements) = do modify $ \s -> s{stInHeading = True} @@ -294,7 +298,7 @@ data StringContext = TextString deriving (Eq) -- escape things as needed for LaTeX -stringToLaTeX :: StringContext -> String -> State WriterState String +stringToLaTeX :: PandocMonad m => StringContext -> String -> LW m String stringToLaTeX _ [] = return "" stringToLaTeX ctx (x:xs) = do opts <- gets stOptions @@ -339,7 +343,7 @@ stringToLaTeX ctx (x:xs) = do '\x2013' | ligatures -> "--" ++ rest _ -> x : rest -toLabel :: String -> State WriterState String +toLabel :: PandocMonad m => String -> LW m String toLabel z = go `fmap` stringToLaTeX URLString z where go [] = "" go (x:xs) @@ -351,14 +355,14 @@ toLabel z = go `fmap` stringToLaTeX URLString z inCmd :: String -> Doc -> Doc inCmd cmd contents = char '\\' <> text cmd <> braces contents -toSlides :: [Block] -> State WriterState [Block] +toSlides :: PandocMonad m => [Block] -> LW m [Block] toSlides bs = do opts <- gets stOptions let slideLevel = fromMaybe (getSlideLevel bs) $ writerSlideLevel opts let bs' = prepSlides slideLevel bs concat `fmap` (mapM (elementToBeamer slideLevel) $ hierarchicalize bs') -elementToBeamer :: Int -> Element -> State WriterState [Block] +elementToBeamer :: PandocMonad m => Int -> Element -> LW m [Block] elementToBeamer _slideLevel (Blk b) = return [b] elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts) | lvl > slideLevel = do @@ -408,8 +412,9 @@ isLineBreakOrSpace Space = True isLineBreakOrSpace _ = False -- | Convert Pandoc block element to LaTeX. -blockToLaTeX :: Block -- ^ Block to convert - -> State WriterState Doc +blockToLaTeX :: PandocMonad m + => Block -- ^ Block to convert + -> LW m Doc blockToLaTeX Null = return empty blockToLaTeX (Div (identifier,classes,kvs) bs) = do beamer <- gets stBeamer @@ -541,10 +546,12 @@ blockToLaTeX (CodeBlock (identifier,classes,keyvalAttr) str) = do | not (null classes) && isJust (writerHighlightStyle opts) -> highlightedCodeBlock | otherwise -> rawCodeBlock -blockToLaTeX (RawBlock f x) +blockToLaTeX b@(RawBlock f x) | f == Format "latex" || f == Format "tex" = return $ text x - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToLaTeX (BulletList []) = return empty -- otherwise latex error blockToLaTeX (BulletList lst) = do incremental <- gets stIncremental @@ -652,14 +659,15 @@ toColDescriptor align = AlignCenter -> "c" AlignDefault -> "l" -blockListToLaTeX :: [Block] -> State WriterState Doc +blockListToLaTeX :: PandocMonad m => [Block] -> LW m Doc blockListToLaTeX lst = vsep `fmap` mapM blockToLaTeX lst -tableRowToLaTeX :: Bool +tableRowToLaTeX :: PandocMonad m + => Bool -> [Alignment] -> [Double] -> [[Block]] - -> State WriterState Doc + -> LW m Doc tableRowToLaTeX header aligns widths cols = do -- scale factor compensates for extra space between columns -- so the whole table isn't larger than columnwidth @@ -700,8 +708,8 @@ displayMathToInline :: Inline -> Inline displayMathToInline (Math DisplayMath x) = Math InlineMath x displayMathToInline x = x -tableCellToLaTeX :: Bool -> (Double, Alignment, [Block]) - -> State WriterState Doc +tableCellToLaTeX :: PandocMonad m => Bool -> (Double, Alignment, [Block]) + -> LW m Doc tableCellToLaTeX _ (0, _, blocks) = blockListToLaTeX $ walk fixLineBreaks $ walk displayMathToInline blocks tableCellToLaTeX header (width, align, blocks) = do @@ -734,7 +742,7 @@ notesToLaTeX ns = (case length ns of $ map (\x -> "\\footnotetext" <> braces x) $ reverse ns) -listItemToLaTeX :: [Block] -> State WriterState Doc +listItemToLaTeX :: PandocMonad m => [Block] -> LW m Doc listItemToLaTeX lst -- we need to put some text before a header if it's the first -- element in an item. This will look ugly in LaTeX regardless, but @@ -744,7 +752,7 @@ listItemToLaTeX lst | otherwise = blockListToLaTeX lst >>= return . (text "\\item" $$) . (nest 2) -defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc +defListItemToLaTeX :: PandocMonad m => ([Inline], [[Block]]) -> LW m Doc defListItemToLaTeX (term, defs) = do term' <- inlineListToLaTeX term -- put braces around term if it contains an internal link, @@ -762,11 +770,12 @@ defListItemToLaTeX (term, defs) = do "\\item" <> brackets term'' $$ def' -- | Craft the section header, inserting the secton reference, if supplied. -sectionHeader :: Bool -- True for unnumbered +sectionHeader :: PandocMonad m + => Bool -- True for unnumbered -> [Char] -> Int -> [Inline] - -> State WriterState Doc + -> LW m Doc sectionHeader unnumbered ident level lst = do txt <- inlineListToLaTeX lst plain <- stringToLaTeX TextString $ concatMap stringify lst @@ -831,7 +840,7 @@ sectionHeader unnumbered ident level lst = do braces txtNoNotes else empty -hypertarget :: String -> Doc -> State WriterState Doc +hypertarget :: PandocMonad m => String -> Doc -> LW m Doc hypertarget ident x = do ref <- text `fmap` toLabel ident internalLinks <- gets stInternalLinks @@ -842,15 +851,16 @@ hypertarget ident x = do <> braces x else x -labelFor :: String -> State WriterState Doc +labelFor :: PandocMonad m => String -> LW m Doc labelFor "" = return empty labelFor ident = do ref <- text `fmap` toLabel ident return $ text "\\label" <> braces ref -- | Convert list of inline elements to LaTeX. -inlineListToLaTeX :: [Inline] -- ^ Inlines to convert - -> State WriterState Doc +inlineListToLaTeX :: PandocMonad m + => [Inline] -- ^ Inlines to convert + -> LW m Doc inlineListToLaTeX lst = mapM inlineToLaTeX (fixBreaks $ fixLineInitialSpaces lst) >>= return . hcat @@ -878,8 +888,9 @@ isQuoted (Quoted _ _) = True isQuoted _ = False -- | Convert inline element to LaTeX -inlineToLaTeX :: Inline -- ^ Inline to convert - -> State WriterState Doc +inlineToLaTeX :: PandocMonad m + => Inline -- ^ Inline to convert + -> LW m Doc inlineToLaTeX (Span (id',classes,kvs) ils) = do ref <- toLabel id' let linkAnchor = if null id' @@ -980,10 +991,12 @@ inlineToLaTeX (Math InlineMath str) = return $ "\\(" <> text str <> "\\)" inlineToLaTeX (Math DisplayMath str) = return $ "\\[" <> text str <> "\\]" -inlineToLaTeX (RawInline f str) +inlineToLaTeX il@(RawInline f str) | f == Format "latex" || f == Format "tex" = return $ text str - | otherwise = return empty + | otherwise = do + report $ InlineNotRendered il + return empty inlineToLaTeX (LineBreak) = return $ "\\\\" <> cr inlineToLaTeX SoftBreak = do wrapText <- gets (writerWrapText . stOptions) @@ -1066,7 +1079,7 @@ protectCode (x@(Code _ _) : xs) = ltx "\\mbox{" : x : ltx "}" : xs where ltx = RawInline (Format "latex") protectCode (x : xs) = x : protectCode xs -citationsToNatbib :: [Citation] -> State WriterState Doc +citationsToNatbib :: PandocMonad m => [Citation] -> LW m Doc citationsToNatbib (one:[]) = citeCommand c p s k where @@ -1113,12 +1126,14 @@ citationsToNatbib cits = do SuppressAuthor -> citeCommand "citeyear" p s k NormalCitation -> citeCommand "citealp" p s k -citeCommand :: String -> [Inline] -> [Inline] -> String -> State WriterState Doc +citeCommand :: PandocMonad m + => String -> [Inline] -> [Inline] -> String -> LW m Doc citeCommand c p s k = do args <- citeArguments p s k return $ text ("\\" ++ c) <> args -citeArguments :: [Inline] -> [Inline] -> String -> State WriterState Doc +citeArguments :: PandocMonad m + => [Inline] -> [Inline] -> String -> LW m Doc citeArguments p s k = do let s' = case s of (Str (x:[]) : r) | isPunctuation x -> dropWhile (== Space) r @@ -1132,7 +1147,7 @@ citeArguments p s k = do (_ , _ ) -> brackets pdoc <> brackets sdoc return $ optargs <> braces (text k) -citationsToBiblatex :: [Citation] -> State WriterState Doc +citationsToBiblatex :: PandocMonad m => [Citation] -> LW m Doc citationsToBiblatex (one:[]) = citeCommand cmd p s k where diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 36ed5fab0..f33acef32 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -43,7 +43,8 @@ import Text.Pandoc.Builder (deleteMeta) import Control.Monad.State import Text.Pandoc.Error import Control.Monad.Except (throwError) -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Logging type Notes = [[Block]] data WriterState = WriterState { stNotes :: Notes @@ -177,9 +178,11 @@ blockToMan opts (Para inlines) = do return $ text ".PP" $$ contents blockToMan opts (LineBlock lns) = blockToMan opts $ linesToPara lns -blockToMan _ (RawBlock f str) +blockToMan _ b@(RawBlock f str) | f == Format "man" = return $ text str - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *" blockToMan opts (Header level _ inlines) = do contents <- inlineListToMan opts inlines @@ -346,9 +349,11 @@ inlineToMan opts (Math InlineMath str) = inlineToMan opts (Math DisplayMath str) = do contents <- lift (texMathToInlines DisplayMath str) >>= inlineListToMan opts return $ cr <> text ".RS" $$ contents $$ text ".RE" -inlineToMan _ (RawInline f str) +inlineToMan _ il@(RawInline f str) | f == Format "man" = return $ text str - | otherwise = return empty + | otherwise = do + report $ InlineNotRendered il + return empty inlineToMan _ LineBreak = return $ cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr inlineToMan _ SoftBreak = return space diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 8327ea9bc..a97c32542 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -59,7 +59,8 @@ import qualified Data.Text as T import qualified Data.Set as Set import Network.HTTP ( urlEncode ) import Text.Pandoc.Error -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Logging type Notes = [[Block]] type Ref = ([Inline], Target, Attr) @@ -414,7 +415,7 @@ blockToMarkdown' opts (LineBlock lns) = mdLines <- mapM (inlineListToMarkdown opts) lns return $ (vcat $ map (hang 2 (text "| ")) mdLines) <> blankline else blockToMarkdown opts $ linesToPara lns -blockToMarkdown' opts (RawBlock f str) +blockToMarkdown' opts b@(RawBlock f str) | f == "markdown" = return $ text str <> text "\n" | f == "html" && isEnabled Ext_raw_html opts = do plain <- asks envPlain @@ -428,7 +429,9 @@ blockToMarkdown' opts (RawBlock f str) return $ if plain then empty else text str <> text "\n" - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToMarkdown' opts HorizontalRule = do return $ blankline <> text (replicate (writerColumns opts) '-') <> blankline blockToMarkdown' opts (Header level attr inlines) = do @@ -1016,14 +1019,16 @@ inlineToMarkdown opts (Math DisplayMath str) = return $ "\\\\[" <> text str <> "\\\\]" | otherwise -> (\x -> cr <> x <> cr) `fmap` (texMathToInlines DisplayMath str >>= inlineListToMarkdown opts) -inlineToMarkdown opts (RawInline f str) = do +inlineToMarkdown opts il@(RawInline f str) = do plain <- asks envPlain if not plain && ( f == "markdown" || (isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex")) || (isEnabled Ext_raw_html opts && f == "html") ) then return $ text str - else return empty + else do + report $ InlineNotRendered il + return empty inlineToMarkdown opts (LineBreak) = do plain <- asks envPlain if plain || isEnabled Ext_hard_line_breaks opts diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 59470c2f9..851e18b8e 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -46,7 +46,8 @@ import qualified Data.Map as Map import Text.Pandoc.Writers.Shared import Data.List (sortBy) import Data.Ord (comparing) -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Logging -- | Auxiliary function to convert Plain block to Para. plainToPara :: Block -> Block @@ -335,7 +336,9 @@ blockToOpenDocument o bs [ ("text:style-name", "Horizontal_20_Line") ]) | RawBlock f s <- bs = if f == Format "opendocument" then return $ text s - else return empty + else do + report $ BlockNotRendered bs + return empty | Null <- bs = return empty | otherwise = return empty where @@ -454,7 +457,9 @@ inlineToOpenDocument o ils Cite _ l -> inlinesToOpenDocument o l RawInline f s -> if f == Format "opendocument" then return $ text s - else return empty + else do + report $ InlineNotRendered ils + return empty Link _ l (s,t) -> mkLink s t <$> inlinesToOpenDocument o l Image attr _ (s,t) -> mkImg attr s t Note l -> mkNote l diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 25c631b9f..ef012e58e 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -258,9 +258,11 @@ blockToRTF indent alignment (BlockQuote lst) = blocksToRTF (indent + indentIncrement) alignment lst blockToRTF indent _ (CodeBlock _ str) = return $ rtfPar indent 0 AlignLeft ("\\f1 " ++ (codeStringToRTF str)) -blockToRTF _ _ (RawBlock f str) +blockToRTF _ _ b@(RawBlock f str) | f == Format "rtf" = return str - | otherwise = return "" + | otherwise = do + report $ BlockNotRendered b + return "" blockToRTF indent alignment (BulletList lst) = (spaceAtEnd . concat) <$> mapM (listItemToRTF alignment indent (bulletMarker indent)) lst blockToRTF indent alignment (OrderedList attribs lst) = @@ -390,9 +392,11 @@ inlineToRTF (Code _ str) = return $ "{\\f1 " ++ (codeStringToRTF str) ++ "}" inlineToRTF (Str str) = return $ stringToRTF str inlineToRTF (Math t str) = texMathToInlines t str >>= inlinesToRTF inlineToRTF (Cite _ lst) = inlinesToRTF lst -inlineToRTF (RawInline f str) +inlineToRTF il@(RawInline f str) | f == Format "rtf" = return str - | otherwise = return "" + | otherwise = do + return $ InlineNotRendered il + return "" inlineToRTF (LineBreak) = return "\\line " inlineToRTF SoftBreak = return " " inlineToRTF Space = return " " diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index a66ffe88b..fe6024351 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -46,7 +46,8 @@ import System.FilePath import qualified Data.Set as Set import Control.Monad.Except (throwError) import Text.Pandoc.Error -import Text.Pandoc.Class ( PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Logging data WriterState = WriterState { stStrikeout :: Bool -- document contains strikeout @@ -166,11 +167,13 @@ blockToTexinfo (CodeBlock _ str) = do flush (text str) $$ text "@end verbatim" <> blankline -blockToTexinfo (RawBlock f str) +blockToTexinfo b@(RawBlock f str) | f == "texinfo" = return $ text str | f == "latex" || f == "tex" = return $ text "@tex" $$ text str $$ text "@end tex" - | otherwise = return empty + | otherwise = do + report $ BlockNotRendered b + return empty blockToTexinfo (BulletList lst) = do items <- mapM listItemToTexinfo lst @@ -444,11 +447,13 @@ inlineToTexinfo (Cite _ lst) = inlineListToTexinfo lst inlineToTexinfo (Str str) = return $ text (stringToTexinfo str) inlineToTexinfo (Math _ str) = return $ inCmd "math" $ text str -inlineToTexinfo (RawInline f str) +inlineToTexinfo il@(RawInline f str) | f == "latex" || f == "tex" = return $ text "@tex" $$ text str $$ text "@end tex" | f == "texinfo" = return $ text str - | otherwise = return empty + | otherwise = do + report $ InlineNotRendered il + return empty inlineToTexinfo (LineBreak) = return $ text "@*" <> cr inlineToTexinfo SoftBreak = do wrapText <- gets (writerWrapText . stOptions) |