aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs25
1 files changed, 13 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 646168c72..a09ad2fda 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -58,7 +58,7 @@ import qualified Data.Text.Lazy as TL
import Network.HTTP (urlEncode)
import Network.URI (URI (..), parseURIReference, unEscapeString)
import Numeric (showHex)
-import Text.Blaze.Internal (customLeaf, MarkupM(Empty))
+import Text.Blaze.Internal (customLeaf, customParent, MarkupM(Empty))
#if MIN_VERSION_blaze_markup(0,6,3)
#else
import Text.Blaze.Internal (preEscapedString, preEscapedText)
@@ -665,16 +665,11 @@ blockToHtml opts (Para [Image attr@(_,classes,_) txt (src,tit)])
-- title beginning with fig: indicates that the image is a figure
blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) =
figure opts attr txt (s,tit)
-blockToHtml opts (Para lst)
- | isEmptyRaw lst = return mempty
- | null lst && not (isEnabled Ext_empty_paragraphs opts) = return mempty
- | otherwise = do
- contents <- inlineListToHtml opts lst
- return $ H.p contents
- where
- isEmptyRaw [RawInline f _] = f `notElem` [Format "html",
- Format "html4", Format "html5"]
- isEmptyRaw _ = False
+blockToHtml opts (Para lst) = do
+ contents <- inlineListToHtml opts lst
+ case contents of
+ Empty _ | not (isEnabled Ext_empty_paragraphs opts) -> return mempty
+ _ -> return $ H.p contents
blockToHtml opts (LineBlock lns) =
if writerWrapText opts == WrapNone
then blockToHtml opts $ linesToPara lns
@@ -1034,6 +1029,13 @@ inlineToHtml opts inline = do
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag
+ GladTeX ->
+ return $
+ customParent (textTag "eq") !
+ customAttribute "env"
+ (toValue $ if t == InlineMath
+ then ("math" :: Text)
+ else "displaymath") $ strToHtml str
MathML -> do
let conf = useShortEmptyTags (const False)
defaultConfigPP
@@ -1063,7 +1065,6 @@ inlineToHtml opts inline = do
if ishtml
then return $ preEscapedString str
else if (f == Format "latex" || f == Format "tex") &&
- "\\begin" `isPrefixOf` str &&
allowsMathEnvironments (writerHTMLMathMethod opts) &&
isMathEnvironment str
then inlineToHtml opts $ Math DisplayMath str