Changed how ASCIIMathML is handled:
+ -m|--asciimathml option now takes an *optional* argument, the URL to an asciiMathML.js script. This is much better in situations where multiple files with math must be served, as the script can be cached. + If the argument is provided, a link is inserted; otherwise, the whole script is inserted as before. + Nothing is inserted unless there is inline LaTeX. git-svn-id: https://pandoc.googlecode.com/svn/trunk@799 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
831fe2c6cf
commit
f2e21a8476
3 changed files with 28 additions and 11 deletions
24
src/Main.hs
24
src/Main.hs
|
@ -31,7 +31,6 @@ writers.
|
||||||
module Main where
|
module Main where
|
||||||
import Text.Pandoc
|
import Text.Pandoc
|
||||||
import Text.Pandoc.UTF8
|
import Text.Pandoc.UTF8
|
||||||
import Text.Pandoc.ASCIIMathML
|
|
||||||
import Text.Pandoc.Shared ( joinWithSep, tabsToSpaces )
|
import Text.Pandoc.Shared ( joinWithSep, tabsToSpaces )
|
||||||
import Text.Regex ( mkRegex, matchRegex )
|
import Text.Regex ( mkRegex, matchRegex )
|
||||||
import System.Environment ( getArgs, getProgName, getEnvironment )
|
import System.Environment ( getArgs, getProgName, getEnvironment )
|
||||||
|
@ -102,7 +101,8 @@ data Opt = Opt
|
||||||
, optNumberSections :: Bool -- ^ Number sections in LaTeX
|
, optNumberSections :: Bool -- ^ Number sections in LaTeX
|
||||||
, optIncremental :: Bool -- ^ Use incremental lists in S5
|
, optIncremental :: Bool -- ^ Use incremental lists in S5
|
||||||
, optSmart :: Bool -- ^ Use smart typography
|
, 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
|
, optDumpArgs :: Bool -- ^ Output command-line arguments
|
||||||
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
|
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
|
||||||
, optStrict :: Bool -- ^ Use strict markdown syntax
|
, optStrict :: Bool -- ^ Use strict markdown syntax
|
||||||
|
@ -129,7 +129,8 @@ defaultOpts = Opt
|
||||||
, optNumberSections = False
|
, optNumberSections = False
|
||||||
, optIncremental = False
|
, optIncremental = False
|
||||||
, optSmart = False
|
, optSmart = False
|
||||||
, optASCIIMathML = False
|
, optUseASCIIMathML = False
|
||||||
|
, optASCIIMathMLURL = Nothing
|
||||||
, optDumpArgs = False
|
, optDumpArgs = False
|
||||||
, optIgnoreArgs = False
|
, optIgnoreArgs = False
|
||||||
, optStrict = False
|
, optStrict = False
|
||||||
|
@ -195,9 +196,11 @@ options =
|
||||||
"" -- "Use smart quotes, dashes, and ellipses"
|
"" -- "Use smart quotes, dashes, and ellipses"
|
||||||
|
|
||||||
, Option "m" ["asciimathml"]
|
, Option "m" ["asciimathml"]
|
||||||
(NoArg
|
(OptArg
|
||||||
(\opt -> return opt { optASCIIMathML = True,
|
(\arg opt -> return opt { optUseASCIIMathML = True,
|
||||||
optStandalone = True }))
|
optASCIIMathMLURL = arg,
|
||||||
|
optStandalone = True })
|
||||||
|
"URL")
|
||||||
"" -- "Use ASCIIMathML script in html output"
|
"" -- "Use ASCIIMathML script in html output"
|
||||||
|
|
||||||
, Option "i" ["incremental"]
|
, Option "i" ["incremental"]
|
||||||
|
@ -399,7 +402,8 @@ main = do
|
||||||
, optNumberSections = numberSections
|
, optNumberSections = numberSections
|
||||||
, optIncremental = incremental
|
, optIncremental = incremental
|
||||||
, optSmart = smart
|
, optSmart = smart
|
||||||
, optASCIIMathML = math
|
, optUseASCIIMathML = useAsciiMathML
|
||||||
|
, optASCIIMathMLURL = asciiMathMLURL
|
||||||
, optDumpArgs = dumpArgs
|
, optDumpArgs = dumpArgs
|
||||||
, optIgnoreArgs = ignoreArgs
|
, optIgnoreArgs = ignoreArgs
|
||||||
, optStrict = strict
|
, optStrict = strict
|
||||||
|
@ -455,11 +459,9 @@ main = do
|
||||||
then ""
|
then ""
|
||||||
else "<link rel=\"stylesheet\" href=\"" ++ css ++
|
else "<link rel=\"stylesheet\" href=\"" ++ css ++
|
||||||
"\" type=\"text/css\" media=\"all\" />\n"
|
"\" type=\"text/css\" media=\"all\" />\n"
|
||||||
let asciiMathML = if math then asciiMathMLScript else ""
|
|
||||||
let header = (if (customHeader == "DEFAULT")
|
let header = (if (customHeader == "DEFAULT")
|
||||||
then defaultHeader
|
then defaultHeader
|
||||||
else customHeader) ++
|
else customHeader) ++ csslink ++ includeHeader
|
||||||
csslink ++ asciiMathML ++ includeHeader
|
|
||||||
let writerOptions = WriterOptions { writerStandalone = standalone &&
|
let writerOptions = WriterOptions { writerStandalone = standalone &&
|
||||||
(not strict),
|
(not strict),
|
||||||
writerHeader = header,
|
writerHeader = header,
|
||||||
|
@ -468,6 +470,8 @@ main = do
|
||||||
writerTableOfContents = toc &&
|
writerTableOfContents = toc &&
|
||||||
(not strict) &&
|
(not strict) &&
|
||||||
writerName/="s5",
|
writerName/="s5",
|
||||||
|
writerUseASCIIMathML = useAsciiMathML,
|
||||||
|
writerASCIIMathMLURL = asciiMathMLURL,
|
||||||
writerS5 = (writerName=="s5"),
|
writerS5 = (writerName=="s5"),
|
||||||
writerIgnoreNotes = False,
|
writerIgnoreNotes = False,
|
||||||
writerIncremental = incremental,
|
writerIncremental = incremental,
|
||||||
|
|
|
@ -421,6 +421,8 @@ data WriterOptions = WriterOptions
|
||||||
, writerIncludeAfter :: String -- ^ String to include after the body
|
, writerIncludeAfter :: String -- ^ String to include after the body
|
||||||
, writerTableOfContents :: Bool -- ^ Include table of contents
|
, writerTableOfContents :: Bool -- ^ Include table of contents
|
||||||
, writerS5 :: Bool -- ^ We're writing S5
|
, 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)
|
, writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc)
|
||||||
, writerIncremental :: Bool -- ^ Incremental S5 lists
|
, writerIncremental :: Bool -- ^ Incremental S5 lists
|
||||||
, writerNumberSections :: Bool -- ^ Number sections in LaTeX
|
, writerNumberSections :: Bool -- ^ Number sections in LaTeX
|
||||||
|
@ -438,6 +440,8 @@ defaultWriterOptions =
|
||||||
writerTabStop = 4,
|
writerTabStop = 4,
|
||||||
writerTableOfContents = False,
|
writerTableOfContents = False,
|
||||||
writerS5 = False,
|
writerS5 = False,
|
||||||
|
writerUseASCIIMathML = False,
|
||||||
|
writerASCIIMathMLURL = Nothing,
|
||||||
writerIgnoreNotes = False,
|
writerIgnoreNotes = False,
|
||||||
writerIncremental = False,
|
writerIncremental = False,
|
||||||
writerNumberSections = False,
|
writerNumberSections = False,
|
||||||
|
|
|
@ -29,6 +29,7 @@ Conversion of 'Pandoc' documents to HTML.
|
||||||
-}
|
-}
|
||||||
module Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString ) where
|
module Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString ) where
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
|
import Text.Pandoc.ASCIIMathML
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import Text.Pandoc.Entities (decodeEntities)
|
import Text.Pandoc.Entities (decodeEntities)
|
||||||
import Text.Regex ( mkRegex, matchRegex )
|
import Text.Regex ( mkRegex, matchRegex )
|
||||||
|
@ -358,7 +359,15 @@ inlineToHtml opts inline =
|
||||||
primHtmlChar "rdquo") in
|
primHtmlChar "rdquo") in
|
||||||
do contents <- inlineListToHtml opts lst
|
do contents <- inlineListToHtml opts lst
|
||||||
return $ leftQuote +++ contents +++ rightQuote
|
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
|
(HtmlInline str) -> return $ primHtml str
|
||||||
(Link txt (src,tit)) ->
|
(Link txt (src,tit)) ->
|
||||||
do linkText <- inlineListToHtml opts txt
|
do linkText <- inlineListToHtml opts txt
|
||||||
|
|
Loading…
Reference in a new issue