aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs4
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs20
-rw-r--r--src/Text/Pandoc/Readers/RST.hs8
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs5
5 files changed, 22 insertions, 19 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 0cbdf72b0..d267a4ff2 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -169,7 +169,7 @@ pRawHtmlBlock = do
raw <- pHtmlBlock "script" <|> pHtmlBlock "style" <|> pRawTag
state <- getState
if stateParseRaw state && not (null raw)
- then return [RawHtml raw]
+ then return [RawBlock "html" raw]
else return []
pHtmlBlock :: String -> TagParser String
@@ -347,7 +347,7 @@ pRawHtmlInline = do
result <- pSatisfy (tagComment (const True)) <|> pSatisfy isInlineTag
state <- getState
if stateParseRaw state
- then return [HtmlInline $ renderTags' [result]]
+ then return [RawInline "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 ad4953648..1944dd651 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -448,7 +448,7 @@ rawLaTeXEnvironment :: GenParser Char st Block
rawLaTeXEnvironment = do
contents <- rawLaTeXEnvironment'
spaces
- return $ Para [TeX contents]
+ return $ RawBlock "latex" contents
-- | Parse any LaTeX environment and return a string containing
-- the whole literal environment as raw TeX.
@@ -491,7 +491,7 @@ demacro (n,st,args) = try $ do
let raw = "\\" ++ n ++ st ++ concat args
s' <- applyMacros' raw
if raw == s'
- then return $ TeX raw
+ then return $ RawInline "latex" raw
else do
inp <- getInput
setInput $ s' ++ inp
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 0334cf8f4..e7abbc695 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -661,10 +661,10 @@ definitionList = do
--
isHtmlOrBlank :: Inline -> Bool
-isHtmlOrBlank (HtmlInline _) = True
-isHtmlOrBlank (Space) = True
-isHtmlOrBlank (LineBreak) = True
-isHtmlOrBlank _ = False
+isHtmlOrBlank (RawInline "html" _) = True
+isHtmlOrBlank (Space) = True
+isHtmlOrBlank (LineBreak) = True
+isHtmlOrBlank _ = False
para :: GenParser Char ParserState Block
para = try $ do
@@ -693,7 +693,7 @@ htmlBlock = try $ do
first <- htmlElement
finalSpace <- many spaceChar
finalNewlines <- many newline
- return $ RawHtml $ first ++ finalSpace ++ finalNewlines
+ return $ RawBlock "html" $ first ++ finalSpace ++ finalNewlines
strictHtmlBlock :: GenParser Char ParserState [Char]
strictHtmlBlock = do
@@ -713,7 +713,7 @@ rawTeXBlock = do
failIfStrict
result <- rawLaTeXEnvironment' <|> rawConTeXtEnvironment'
spaces
- return $ Para [TeX result]
+ return $ RawBlock "latex" result
rawHtmlBlocks :: GenParser Char ParserState Block
rawHtmlBlocks = do
@@ -730,7 +730,7 @@ rawHtmlBlocks = do
return $ blk ++ sps
let combined = concat htmlBlocks
let combined' = if last combined == '\n' then init combined else combined
- return $ RawHtml combined'
+ return $ RawBlock "html" combined'
--
-- Tables
@@ -1186,8 +1186,8 @@ inlineNote = try $ do
rawLaTeXInline' :: GenParser Char ParserState Inline
rawLaTeXInline' = do
failIfStrict
- (rawConTeXtEnvironment' >>= return . TeX)
- <|> (rawLaTeXEnvironment' >>= return . TeX)
+ (rawConTeXtEnvironment' >>= return . RawInline "latex")
+ <|> (rawLaTeXEnvironment' >>= return . RawInline "latex")
<|> rawLaTeXInline
rawConTeXtEnvironment' :: GenParser Char st String
@@ -1212,7 +1212,7 @@ rawHtmlInline = do
(_,result) <- if stateStrict st
then htmlTag (not . isTextTag)
else htmlTag isInlineTag
- return $ HtmlInline result
+ return $ RawInline "html" result
-- Citations
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index d65aac6e5..fec49b40e 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -373,8 +373,10 @@ birdTrackLine = do
--
rawHtmlBlock :: GenParser Char st Block
-rawHtmlBlock = try $ string ".. raw:: html" >> blanklines >>
- indentedBlock >>= return . RawHtml
+rawHtmlBlock = try $ do
+ string ".. raw:: html"
+ blanklines
+ indentedBlock >>= return . RawBlock "html"
--
-- raw latex
@@ -385,7 +387,7 @@ rawLaTeXBlock = try $ do
string ".. raw:: latex"
blanklines
result <- indentedBlock
- return $ Para [(TeX result)]
+ return $ RawBlock "latex" result
--
-- block quotes
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 7749a946c..714cac9f4 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -281,7 +281,7 @@ rawHtmlBlock :: GenParser Char ParserState Block
rawHtmlBlock = try $ do
(_,b) <- htmlTag isBlockTag
optional blanklines
- return $ RawHtml b
+ return $ RawBlock "html" b
-- | In textile, paragraphs are separated by blank lines.
para :: GenParser Char ParserState Block
@@ -457,7 +457,8 @@ endline = try $ do
return LineBreak
rawHtmlInline :: GenParser Char ParserState Inline
-rawHtmlInline = liftM (HtmlInline . snd) $ htmlTag isInlineTag
+rawHtmlInline = liftM (RawInline "html" . snd)
+ $ htmlTag isInlineTag
-- | Textile standard link syntax is "label":target
link :: GenParser Char ParserState Inline