aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2013-08-10 17:23:51 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-08-10 17:24:54 -0700
commitcbfa9321066212b912583481015224f3c944ae21 (patch)
treef858055ee94dc44214f046db2dbf5dad07da8133 /src/Text/Pandoc/Readers
parente9de0f0e22b9b64b5684efe81d03539c3f57a71c (diff)
downloadpandoc-cbfa9321066212b912583481015224f3c944ae21.tar.gz
Adjustments for new Format newtype.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-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
4 files changed, 7 insertions, 6 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