aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorYan Pas <yanp.bugz@gmail.com>2018-05-12 11:42:39 +0300
committerYan Pas <yanp.bugz@gmail.com>2018-05-12 11:42:39 +0300
commitb0b41cbbe6e316d63f196d8043b636a9050376fc (patch)
tree1226053cabecb78399fdc1bc3f28a224e55d34ba /src/Text/Pandoc
parentad19166bc308a2428bd040851a2a97c76e8873f9 (diff)
parenta00ca6f0d8e83821d9be910f1eebf3d3cdd1170f (diff)
downloadpandoc-b0b41cbbe6e316d63f196d8043b636a9050376fc.tar.gz
Merge branch 'master' into groff_reader
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/App.hs6
-rw-r--r--src/Text/Pandoc/Options.hs1
-rw-r--r--src/Text/Pandoc/Parsing.hs6
-rw-r--r--src/Text/Pandoc/Readers/Org/Shared.hs13
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs25
5 files changed, 31 insertions, 20 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 920462d48..a59fd9bbe 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -1403,6 +1403,12 @@ options =
"URL")
"" -- Use KaTeX for HTML Math
+ , Option "" ["gladtex"]
+ (NoArg
+ (\opt ->
+ return opt { optHTMLMathMethod = GladTeX }))
+ "" -- "Use gladtex for HTML math"
+
, Option "" ["abbreviations"]
(ReqArg
(\arg opt -> return opt { optAbbreviations = Just arg })
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 4797a3094..e5ca1764c 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -107,6 +107,7 @@ data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Gener
data HTMLMathMethod = PlainMath
| WebTeX String -- url of TeX->image script.
+ | GladTeX
| MathML
| MathJax String -- url of MathJax.js
| KaTeX String -- url of KaTeX files
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index fa6baf1c7..05f4f7d36 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -1366,7 +1366,9 @@ singleQuoteStart = do
failIfInQuoteContext InSingleQuote
-- single quote start can't be right after str
guard =<< notAfterString
- () <$ charOrRef "'\8216\145"
+ try $ do
+ charOrRef "'\8216\145"
+ notFollowedBy (oneOf [' ', '\t', '\n'])
singleQuoteEnd :: Stream s m Char
=> ParserT s st m ()
@@ -1379,7 +1381,7 @@ doubleQuoteStart :: (HasQuoteContext st m, Stream s m Char)
doubleQuoteStart = do
failIfInQuoteContext InDoubleQuote
try $ do charOrRef "\"\8220\147"
- notFollowedBy . satisfy $ flip elem [' ', '\t', '\n']
+ notFollowedBy (oneOf [' ', '\t', '\n'])
doubleQuoteEnd :: Stream s m Char
=> ParserT s st m ()
diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs
index 07dbeca2a..17fe34738 100644
--- a/src/Text/Pandoc/Readers/Org/Shared.hs
+++ b/src/Text/Pandoc/Readers/Org/Shared.hs
@@ -36,17 +36,18 @@ module Text.Pandoc.Readers.Org.Shared
import Prelude
import Data.Char (isAlphaNum)
-import Data.List (isPrefixOf, isSuffixOf)
+import Data.List (isPrefixOf)
+import System.FilePath (isValid, takeExtension)
-- | Check whether the given string looks like the path to of URL of an image.
isImageFilename :: String -> Bool
-isImageFilename filename =
- any (\x -> ('.':x) `isSuffixOf` filename) imageExtensions &&
- (any (\x -> (x ++ "://") `isPrefixOf` filename) protocols ||
- ':' `notElem` filename)
+isImageFilename fp = hasImageExtension && (isValid fp || isKnownProtocolUri)
where
- imageExtensions = [ "jpeg" , "jpg" , "png" , "gif" , "svg" ]
+ hasImageExtension = takeExtension fp `elem` imageExtensions
+ isKnownProtocolUri = any (\x -> (x ++ "://") `isPrefixOf` fp) protocols
+
+ imageExtensions = [ ".jpeg", ".jpg", ".png", ".gif", ".svg" ]
protocols = [ "file", "http", "https" ]
-- | Cleanup and canonicalize a string describing a link. Return @Nothing@ if
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