summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Readers/RST.hs1
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs6
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs8
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs6
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs9
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs10
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs6
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs13
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs13
-rw-r--r--src/Text/Pandoc/Writers/Man.hs10
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs14
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs12
-rw-r--r--src/Text/Pandoc/Writers/RST.hs15
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs12
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs19
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs14
-rw-r--r--tests/Tests/Arbitrary.hs8
19 files changed, 106 insertions, 76 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 0068ab5c1..7ca554fa3 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -182,7 +182,7 @@ pRawHtmlBlock = do
raw <- pHtmlBlock "script" <|> pHtmlBlock "style" <|> pRawTag
parseRaw <- getOption readerParseRaw
if parseRaw && not (null raw)
- then return [RawBlock "html" raw]
+ then return [RawBlock (Format "html") raw]
else return []
pHtmlBlock :: String -> TagParser String
@@ -408,7 +408,7 @@ pRawHtmlInline = do
result <- pSatisfy (tagComment (const True)) <|> pSatisfy isInlineTag
parseRaw <- getOption readerParseRaw
if parseRaw
- then return [RawInline "html" $ renderTags' [result]]
+ then return [RawInline (Format "html") $ renderTags' [result]]
else return []
pInlinesInTags :: String -> ([Inline] -> Inline)
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 6b5035d93..eb0baedda 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ScopedTypeVariables, OverloadedStrings #-}
{-
Copyright (C) 2006-2012 John MacFarlane <jgm@berkeley.edu>
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 34962b553..df0a8294d 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 9191f6908..8ccd1e227 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -290,13 +290,13 @@ rawHtmlBlock :: Parser [Char] ParserState Block
rawHtmlBlock = try $ do
(_,b) <- htmlTag isBlockTag
optional blanklines
- return $ RawBlock "html" b
+ return $ RawBlock (Format "html") b
-- | Raw block of LaTeX content
rawLaTeXBlock' :: Parser [Char] ParserState Block
rawLaTeXBlock' = do
guardEnabled Ext_raw_tex
- RawBlock "latex" <$> (rawLaTeXBlock <* spaces)
+ RawBlock (Format "latex") <$> (rawLaTeXBlock <* spaces)
-- | In textile, paragraphs are separated by blank lines.
@@ -487,7 +487,7 @@ endline = try $ do
return LineBreak
rawHtmlInline :: Parser [Char] ParserState Inline
-rawHtmlInline = RawInline "html" . snd <$> htmlTag isInlineTag
+rawHtmlInline = RawInline (Format "html") . snd <$> htmlTag isInlineTag
-- | Raw LaTeX Inline
rawLaTeXInline' :: Parser [Char] ParserState Inline
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 00cea27e5..68b525742 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -132,7 +132,9 @@ blockToAsciiDoc opts (Para inlines) = do
then text "\\"
else empty
return $ esc <> contents <> blankline
-blockToAsciiDoc _ (RawBlock _ _) = return empty
+blockToAsciiDoc _ (RawBlock f s)
+ | f == "asciidoc" = return $ text s
+ | otherwise = return empty
blockToAsciiDoc _ HorizontalRule =
return $ blankline <> text "'''''" <> blankline
blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
@@ -347,7 +349,9 @@ inlineToAsciiDoc _ (Math InlineMath str) =
return $ "latexmath:[$" <> text str <> "$]"
inlineToAsciiDoc _ (Math DisplayMath str) =
return $ "latexmath:[\\[" <> text str <> "\\]]"
-inlineToAsciiDoc _ (RawInline _ _) = return empty
+inlineToAsciiDoc _ (RawInline f s)
+ | f == "asciidoc" = return $ text s
+ | otherwise = return empty
inlineToAsciiDoc _ (LineBreak) = return $ " +" <> cr
inlineToAsciiDoc _ Space = return space
inlineToAsciiDoc opts (Cite _ lst) = inlineListToAsciiDoc opts lst
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index c250a240e..0234e1e35 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Writers.Custom ( writeCustom ) where
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Data.List ( intersperse )
+import Data.Char ( toLower )
import Scripting.Lua (LuaState, StackValue, callfunc)
import qualified Scripting.Lua as Lua
import Text.Pandoc.UTF8 (fromString, toString)
@@ -78,6 +79,11 @@ instance StackValue a => StackValue [a] where
return (Just lst)
valuetype _ = Lua.TTABLE
+instance StackValue Format where
+ push lua (Format f) = Lua.push lua (map toLower f)
+ peek l n = fmap Format `fmap` Lua.peek l n
+ valuetype _ = Lua.TSTRING
+
instance (StackValue a, StackValue b) => StackValue (M.Map a b) where
push lua m = do
let xs = M.toList m
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 2f415f3ee..3d150d19b 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
@@ -199,10 +200,10 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) =
in inTags True "orderedlist" attribs items
blockToDocbook opts (DefinitionList lst) =
inTagsIndented "variablelist" $ deflistItemsToDocbook opts lst
-blockToDocbook _ (RawBlock "docbook" str) = text str -- raw XML block
--- we allow html for compatibility with earlier versions of pandoc
-blockToDocbook _ (RawBlock "html" str) = text str -- raw XML block
-blockToDocbook _ (RawBlock _ _) = empty
+blockToDocbook _ (RawBlock f str)
+ | f == "docbook" = text str -- raw XML block
+ | f == "html" = text str -- allow html for backwards compatibility
+ | otherwise = empty
blockToDocbook _ HorizontalRule = empty -- not semantic
blockToDocbook opts (Table caption aligns widths headers rows) =
let captionDoc = if null caption
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index d93254971..2483e243f 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -460,8 +460,8 @@ blockToOpenXML opts (Para lst) = do
contents <- inlinesToOpenXML opts lst
return [mknode "w:p" [] (paraProps ++ contents)]
blockToOpenXML _ (RawBlock format str)
- | format == "openxml" = return [ x | Elem x <- parseXML str ]
- | otherwise = return []
+ | format == Format "openxml" = return [ x | Elem x <- parseXML str ]
+ | otherwise = return []
blockToOpenXML opts (BlockQuote blocks) =
withParaProp (pStyle "BlockQuote") $ blocksToOpenXML opts blocks
blockToOpenXML opts (CodeBlock attrs str) =
@@ -653,8 +653,8 @@ inlineToOpenXML opts (Strikeout lst) =
$ inlinesToOpenXML opts lst
inlineToOpenXML _ LineBreak = return [br]
inlineToOpenXML _ (RawInline f str)
- | f == "openxml" = return [ x | Elem x <- parseXML str ]
- | otherwise = return []
+ | f == Format "openxml" = return [ x | Elem x <- parseXML str ]
+ | otherwise = return []
inlineToOpenXML opts (Quoted quoteType lst) =
inlinesToOpenXML opts $ [Str open] ++ lst ++ [Str close]
where (open, close) = case quoteType of
@@ -688,7 +688,7 @@ inlineToOpenXML opts (Note bs) = do
let notemarker = mknode "w:r" []
[ mknode "w:rPr" [] (rStyle "FootnoteRef")
, mknode "w:footnoteRef" [] () ]
- let notemarkerXml = RawInline "openxml" $ ppElement notemarker
+ let notemarkerXml = RawInline (Format "openxml") $ ppElement notemarker
let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : ils) : xs
insertNoteRef (Para ils : xs) = Para (notemarkerXml : ils) : xs
insertNoteRef xs = Para [notemarkerXml] : xs
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index fb756f196..ab14ff8a0 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -103,7 +103,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
Just img -> do
let coverImage = "cover-image" ++ takeExtension img
let cpContent = renderHtml $ writeHtml opts'
- (Pandoc meta [RawBlock "html" $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"])
+ (Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"])
imgContent <- B.readFile img
return ( [mkEntry "cover.xhtml" cpContent]
, [mkEntry coverImage imgContent] )
@@ -422,7 +422,7 @@ transformInline opts sourceDir picsRef (Image lab (src,tit))
| isAbsoluteURI src = do
raw <- makeSelfContained Nothing
$ writeHtmlInline opts (Image lab (src,tit))
- return $ RawInline "html" raw
+ return $ RawInline (Format "html") raw
| otherwise = do
let src' = unEscapeString src
pics <- readIORef picsRef
@@ -438,7 +438,7 @@ transformInline opts sourceDir picsRef (Image lab (src,tit))
transformInline opts _ _ (x@(Math _ _))
| WebTeX _ <- writerHTMLMathMethod opts = do
raw <- makeSelfContained Nothing $ writeHtmlInline opts x
- return $ RawInline "html" raw
+ return $ RawInline (Format "html") raw
transformInline _ _ _ x = return x
writeHtmlInline :: WriterOptions -> Inline -> String
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 560c26c76..25079574e 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -410,8 +410,9 @@ blockToHtml opts (Para lst) = do
blockToHtml opts (Div attr bs) = do
contents <- blockListToHtml opts bs
return $ addAttrs opts attr $ H.div $ nl opts >> contents >> nl opts
-blockToHtml _ (RawBlock "html" str) = return $ preEscapedString str
-blockToHtml _ (RawBlock _ _) = return mempty
+blockToHtml _ (RawBlock f str)
+ | f == Format "html" = return $ preEscapedString str
+ | otherwise = return mempty
blockToHtml opts (HorizontalRule) = return $ if writerHtml5 opts then H5.hr else H.hr
blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
let tolhs = isEnabled Ext_literate_haskell opts &&
@@ -678,12 +679,14 @@ inlineToHtml opts inline =
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag )
- (RawInline "latex" str) -> case writerHTMLMathMethod opts of
+ (RawInline f str)
+ | f == Format "latex" ->
+ case writerHTMLMathMethod opts of
LaTeXMathML _ -> do modify (\st -> st {stMath = True})
return $ toHtml str
_ -> return mempty
- (RawInline "html" str) -> return $ preEscapedString str
- (RawInline _ _) -> return mempty
+ | f == Format "html" -> return $ preEscapedString str
+ | otherwise -> return mempty
(Link [Str str] (s,_)) | "mailto:" `isPrefixOf` s &&
s == escapeURI ("mailto" ++ str) ->
-- autolink
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 37de03e0f..d09ccc3b8 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -356,8 +356,10 @@ blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
Nothing -> rawCodeBlock
Just h -> modify (\st -> st{ stHighlighting = True }) >>
return (flush $ text h)
-blockToLaTeX (RawBlock "latex" x) = return $ text x
-blockToLaTeX (RawBlock _ _) = return empty
+blockToLaTeX (RawBlock f x)
+ | f == Format "latex" || f == Format "tex"
+ = return $ text x
+ | otherwise = return empty
blockToLaTeX (BulletList []) = return empty -- otherwise latex error
blockToLaTeX (BulletList lst) = do
incremental <- gets stIncremental
@@ -630,9 +632,10 @@ inlineToLaTeX (Math InlineMath str) =
return $ char '$' <> text str <> char '$'
inlineToLaTeX (Math DisplayMath str) =
return $ "\\[" <> text str <> "\\]"
-inlineToLaTeX (RawInline "latex" str) = return $ text str
-inlineToLaTeX (RawInline "tex" str) = return $ text str
-inlineToLaTeX (RawInline _ _) = return empty
+inlineToLaTeX (RawInline f str)
+ | f == Format "latex" || f == Format "tex"
+ = return $ text str
+ | otherwise = return empty
inlineToLaTeX (LineBreak) = return "\\\\"
inlineToLaTeX Space = return space
inlineToLaTeX (Link txt ('#':ident, _)) = do
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index ed66c7c2b..642a002d6 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -167,8 +167,9 @@ blockToMan opts (Para inlines) = do
contents <- liftM vcat $ mapM (inlineListToMan opts) $
splitSentences inlines
return $ text ".PP" $$ contents
-blockToMan _ (RawBlock "man" str) = return $ text str
-blockToMan _ (RawBlock _ _) = return empty
+blockToMan _ (RawBlock f str)
+ | f == Format "man" = return $ text str
+ | otherwise = return empty
blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *"
blockToMan opts (Header level _ inlines) = do
contents <- inlineListToMan opts inlines
@@ -333,8 +334,9 @@ inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str
inlineToMan opts (Math DisplayMath str) = do
contents <- inlineListToMan opts $ readTeXMath str
return $ cr <> text ".RS" $$ contents $$ text ".RE"
-inlineToMan _ (RawInline "man" str) = return $ text str
-inlineToMan _ (RawInline _ _) = return empty
+inlineToMan _ (RawInline f str)
+ | f == Format "man" = return $ text str
+ | otherwise = return empty
inlineToMan _ (LineBreak) = return $
cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr
inlineToMan _ Space = return space
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index fccf25753..4ffba1100 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -107,9 +107,10 @@ blockToMediaWiki opts (Para inlines) = do
then "<p>" ++ contents ++ "</p>"
else contents ++ if null listLevel then "\n" else ""
-blockToMediaWiki _ (RawBlock "mediawiki" str) = return str
-blockToMediaWiki _ (RawBlock "html" str) = return str
-blockToMediaWiki _ (RawBlock _ _) = return ""
+blockToMediaWiki _ (RawBlock f str)
+ | f == Format "mediawiki" = return str
+ | f == Format "html" = return str
+ | otherwise = return ""
blockToMediaWiki _ HorizontalRule = return "\n-----\n"
@@ -374,9 +375,10 @@ inlineToMediaWiki _ (Str str) = return $ escapeString str
inlineToMediaWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>"
-- note: str should NOT be escaped
-inlineToMediaWiki _ (RawInline "mediawiki" str) = return str
-inlineToMediaWiki _ (RawInline "html" str) = return str
-inlineToMediaWiki _ (RawInline _ _) = return ""
+inlineToMediaWiki _ (RawInline f str)
+ | f == Format "mediawiki" = return str
+ | f == Format "html" = return str
+ | otherwise = return ""
inlineToMediaWiki _ (LineBreak) = return "<br />"
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index d76d0f6ad..05c576c20 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE PatternGuards, OverloadedStrings #-}
{-
Copyright (C) 2008-2010 Andrea Rossato <andrea.rossato@ing.unitn.it>
and John MacFarlane.
@@ -296,7 +296,9 @@ blockToOpenDocument o bs
| Table c a w h r <- bs = setFirstPara >> table c a w h r
| HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p"
[ ("text:style-name", "Horizontal_20_Line") ])
- | RawBlock _ _ <- bs = return empty
+ | RawBlock f s <- bs = if f == "opendocument"
+ then preformatted s
+ else return empty
| Null <- bs = return empty
| otherwise = return empty
where
@@ -374,9 +376,9 @@ inlineToOpenDocument o ils
| Code _ s <- ils = preformatted s
| Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s)
| Cite _ l <- ils = inlinesToOpenDocument o l
- | RawInline "opendocument" s <- ils = preformatted s
- | RawInline "html" s <- ils = preformatted s -- for backwards compat.
- | RawInline _ _ <- ils = return empty
+ | RawInline f s <- ils = if f == "opendocument" || f == "html"
+ then preformatted s
+ else return empty
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
| Image _ (s,t) <- ils = return $ mkImg s t
| Note l <- ils = mkNote l
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 4d8daa15b..5fbbb6afc 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -42,7 +42,7 @@ import Network.URI (isAbsoluteURI)
import Text.Pandoc.Pretty
import Control.Monad.State
import Control.Applicative ( (<$>) )
-import Data.Char (isSpace)
+import Data.Char (isSpace, toLower)
type Refs = [([Inline], Target)]
@@ -176,9 +176,11 @@ blockToRST (Para inlines)
| otherwise = do
contents <- inlineListToRST inlines
return $ contents <> blankline
-blockToRST (RawBlock f str) =
- return $ blankline <> ".. raw:: " <> text f $+$
- (nest 3 $ text str) $$ blankline
+blockToRST (RawBlock f str)
+ | f == "rst" = return $ text str
+ | otherwise = return $ blankline <> ".. raw:: " <>
+ text (map toLower $ unFormat f) $+$
+ (nest 3 $ text str) $$ blankline
blockToRST HorizontalRule =
return $ blankline $$ "--------------" $$ blankline
blockToRST (Header level _ inlines) = do
@@ -374,8 +376,9 @@ inlineToRST (Math t str) = do
then blankline $$ ".. math::" $$
blankline $$ nest 3 (text str) $$ blankline
else blankline $$ (".. math:: " <> text str) $$ blankline
-inlineToRST (RawInline "rst" x) = return $ text x
-inlineToRST (RawInline _ _) = return empty
+inlineToRST (RawInline f x)
+ | f == "rst" = return $ text x
+ | otherwise = return empty
inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para)
inlineToRST Space = return space
-- autolink
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 7e5d33c50..6d2b1229d 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -62,7 +62,7 @@ rtfEmbedImage x@(Image _ (src,_)) = do
let raw = "{\\pict" ++ filetype ++ " " ++ concat bytes ++ "}"
return $ if B.null imgdata
then x
- else RawInline "rtf" raw
+ else RawInline (Format "rtf") raw
else return x
rtfEmbedImage x = return x
@@ -218,8 +218,9 @@ blockToRTF indent alignment (BlockQuote lst) =
concatMap (blockToRTF (indent + indentIncrement) alignment) lst
blockToRTF indent _ (CodeBlock _ str) =
rtfPar indent 0 AlignLeft ("\\f1 " ++ (codeStringToRTF str))
-blockToRTF _ _ (RawBlock "rtf" str) = str
-blockToRTF _ _ (RawBlock _ _) = ""
+blockToRTF _ _ (RawBlock f str)
+ | f == Format "rtf" = str
+ | otherwise = ""
blockToRTF indent alignment (BulletList lst) = spaceAtEnd $
concatMap (listItemToRTF alignment indent (bulletMarker indent)) lst
blockToRTF indent alignment (OrderedList attribs lst) = spaceAtEnd $ concat $
@@ -325,8 +326,9 @@ inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
inlineToRTF (Str str) = stringToRTF str
inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str
inlineToRTF (Cite _ lst) = inlineListToRTF lst
-inlineToRTF (RawInline "rtf" str) = str
-inlineToRTF (RawInline _ _) = ""
+inlineToRTF (RawInline f str)
+ | f == Format "rtf" = str
+ | otherwise = ""
inlineToRTF (LineBreak) = "\\line "
inlineToRTF Space = " "
inlineToRTF (Link text (src, _)) =
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index f8b460001..b1fd3d6af 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2008-2010 John MacFarlane and Peter Wang
@@ -152,10 +153,11 @@ blockToTexinfo (CodeBlock _ str) = do
flush (text str) $$
text "@end verbatim" <> blankline
-blockToTexinfo (RawBlock "texinfo" str) = return $ text str
-blockToTexinfo (RawBlock "latex" str) =
- return $ text "@tex" $$ text str $$ text "@end tex"
-blockToTexinfo (RawBlock _ _) = return empty
+blockToTexinfo (RawBlock f str)
+ | f == "texinfo" = return $ text str
+ | f == "latex" || f == "tex" =
+ return $ text "@tex" $$ text str $$ text "@end tex"
+ | otherwise = return empty
blockToTexinfo (BulletList lst) = do
items <- mapM listItemToTexinfo lst
@@ -418,10 +420,11 @@ inlineToTexinfo (Cite _ lst) =
inlineListToTexinfo lst
inlineToTexinfo (Str str) = return $ text (stringToTexinfo str)
inlineToTexinfo (Math _ str) = return $ inCmd "math" $ text str
-inlineToTexinfo (RawInline f str) | f == "latex" || f == "tex" =
- return $ text "@tex" $$ text str $$ text "@end tex"
-inlineToTexinfo (RawInline "texinfo" str) = return $ text str
-inlineToTexinfo (RawInline _ _) = return empty
+inlineToTexinfo (RawInline f str)
+ | f == "latex" || f == "tex" =
+ return $ text "@tex" $$ text str $$ text "@end tex"
+ | f == "texinfo" = return $ text str
+ | otherwise = return empty
inlineToTexinfo (LineBreak) = return $ text "@*"
inlineToTexinfo Space = return $ char ' '
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 3fb554dca..27e8b60ec 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -121,10 +121,9 @@ blockToTextile opts (Para inlines) = do
then "<p>" ++ contents ++ "</p>"
else contents ++ if null listLevel then "\n" else ""
-blockToTextile _ (RawBlock f str) =
- if f == "html" || f == "textile"
- then return str
- else return ""
+blockToTextile _ (RawBlock f str)
+ | f == Format "html" || f == Format "textile" = return str
+ | otherwise = return ""
blockToTextile _ HorizontalRule = return "<hr />\n"
@@ -401,10 +400,9 @@ inlineToTextile _ (Str str) = return $ escapeStringForTextile str
inlineToTextile _ (Math _ str) =
return $ "<span class=\"math\">" ++ escapeStringForXML str ++ "</math>"
-inlineToTextile _ (RawInline f str) =
- if f == "html" || f == "textile"
- then return str
- else return ""
+inlineToTextile _ (RawInline f str)
+ | f == Format "html" || f == Format "textile" = return str
+ | otherwise = return ""
inlineToTextile _ (LineBreak) = return "\n"
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs
index 5939d088d..31c0cb46a 100644
--- a/tests/Tests/Arbitrary.hs
+++ b/tests/Tests/Arbitrary.hs
@@ -41,8 +41,8 @@ arbInline :: Int -> Gen Inline
arbInline n = frequency $ [ (60, liftM Str realString)
, (60, return Space)
, (10, liftM2 Code arbAttr realString)
- , (5, elements [ RawInline "html" "<a id=\"eek\">"
- , RawInline "latex" "\\my{command}" ])
+ , (5, elements [ RawInline (Format "html") "<a id=\"eek\">"
+ , RawInline (Format "latex") "\\my{command}" ])
] ++ [ x | x <- nesters, n > 1]
where nesters = [ (10, liftM Emph $ arbInlines (n-1))
, (10, liftM Strong $ arbInlines (n-1))
@@ -74,9 +74,9 @@ arbBlock :: Int -> Gen Block
arbBlock n = frequency $ [ (10, liftM Plain $ arbInlines (n-1))
, (15, liftM Para $ arbInlines (n-1))
, (5, liftM2 CodeBlock arbAttr realString)
- , (2, elements [ RawBlock "html"
+ , (2, elements [ RawBlock (Format "html")
"<div>\n*&amp;*\n</div>"
- , RawBlock "latex"
+ , RawBlock (Format "latex")
"\\begin[opt]{env}\nhi\n{\\end{env}"
])
, (5, do x1 <- choose (1 :: Int, 6)