diff options
-rw-r--r-- | src/Main.hs | 24 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 11 |
3 files changed, 28 insertions, 11 deletions
diff --git a/src/Main.hs b/src/Main.hs index 0c9bc598a..43fb4e62d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -31,7 +31,6 @@ writers. module Main where import Text.Pandoc import Text.Pandoc.UTF8 -import Text.Pandoc.ASCIIMathML import Text.Pandoc.Shared ( joinWithSep, tabsToSpaces ) import Text.Regex ( mkRegex, matchRegex ) import System.Environment ( getArgs, getProgName, getEnvironment ) @@ -102,7 +101,8 @@ data Opt = Opt , optNumberSections :: Bool -- ^ Number sections in LaTeX , optIncremental :: Bool -- ^ Use incremental lists in S5 , optSmart :: Bool -- ^ Use smart typography - , optASCIIMathML :: Bool -- ^ Use ASCIIMathML in HTML + , optUseASCIIMathML :: Bool -- ^ Use ASCIIMathML + , optASCIIMathMLURL :: Maybe String -- ^ URL to ASCIIMathML.js , optDumpArgs :: Bool -- ^ Output command-line arguments , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments , optStrict :: Bool -- ^ Use strict markdown syntax @@ -129,7 +129,8 @@ defaultOpts = Opt , optNumberSections = False , optIncremental = False , optSmart = False - , optASCIIMathML = False + , optUseASCIIMathML = False + , optASCIIMathMLURL = Nothing , optDumpArgs = False , optIgnoreArgs = False , optStrict = False @@ -195,9 +196,11 @@ options = "" -- "Use smart quotes, dashes, and ellipses" , Option "m" ["asciimathml"] - (NoArg - (\opt -> return opt { optASCIIMathML = True, - optStandalone = True })) + (OptArg + (\arg opt -> return opt { optUseASCIIMathML = True, + optASCIIMathMLURL = arg, + optStandalone = True }) + "URL") "" -- "Use ASCIIMathML script in html output" , Option "i" ["incremental"] @@ -399,7 +402,8 @@ main = do , optNumberSections = numberSections , optIncremental = incremental , optSmart = smart - , optASCIIMathML = math + , optUseASCIIMathML = useAsciiMathML + , optASCIIMathMLURL = asciiMathMLURL , optDumpArgs = dumpArgs , optIgnoreArgs = ignoreArgs , optStrict = strict @@ -455,11 +459,9 @@ main = do then "" else "<link rel=\"stylesheet\" href=\"" ++ css ++ "\" type=\"text/css\" media=\"all\" />\n" - let asciiMathML = if math then asciiMathMLScript else "" let header = (if (customHeader == "DEFAULT") then defaultHeader - else customHeader) ++ - csslink ++ asciiMathML ++ includeHeader + else customHeader) ++ csslink ++ includeHeader let writerOptions = WriterOptions { writerStandalone = standalone && (not strict), writerHeader = header, @@ -468,6 +470,8 @@ main = do writerTableOfContents = toc && (not strict) && writerName/="s5", + writerUseASCIIMathML = useAsciiMathML, + writerASCIIMathMLURL = asciiMathMLURL, writerS5 = (writerName=="s5"), writerIgnoreNotes = False, writerIncremental = incremental, diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index f1df22c4f..b79af235d 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -421,6 +421,8 @@ data WriterOptions = WriterOptions , writerIncludeAfter :: String -- ^ String to include after the body , writerTableOfContents :: Bool -- ^ Include table of contents , writerS5 :: Bool -- ^ We're writing S5 + , writerUseASCIIMathML :: Bool -- ^ Use ASCIIMathML + , writerASCIIMathMLURL :: Maybe String -- ^ URL to asciiMathML.js , writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc) , writerIncremental :: Bool -- ^ Incremental S5 lists , writerNumberSections :: Bool -- ^ Number sections in LaTeX @@ -438,6 +440,8 @@ defaultWriterOptions = writerTabStop = 4, writerTableOfContents = False, writerS5 = False, + writerUseASCIIMathML = False, + writerASCIIMathMLURL = Nothing, writerIgnoreNotes = False, writerIncremental = False, writerNumberSections = False, diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 4637ffde4..c860d73e6 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -29,6 +29,7 @@ Conversion of 'Pandoc' documents to HTML. -} module Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString ) where import Text.Pandoc.Definition +import Text.Pandoc.ASCIIMathML import Text.Pandoc.Shared import Text.Pandoc.Entities (decodeEntities) import Text.Regex ( mkRegex, matchRegex ) @@ -358,7 +359,15 @@ inlineToHtml opts inline = primHtmlChar "rdquo") in do contents <- inlineListToHtml opts lst return $ leftQuote +++ contents +++ rightQuote - (TeX str) -> return $ stringToHtml str + (TeX str) -> do if writerUseASCIIMathML opts + then addToHeader $ + case writerASCIIMathMLURL opts of + Just path -> script ! [src path, + thetype "text/javascript"] $ + noHtml + Nothing -> primHtml asciiMathMLScript + else return () + return $ stringToHtml str (HtmlInline str) -> return $ primHtml str (Link txt (src,tit)) -> do linkText <- inlineListToHtml opts txt |