Added HTMLMathMethod writer option.

This selects between asciimathml, mimetex, gladtex, and plain math.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@1123 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2007-12-01 03:11:44 +00:00
parent 7ddd01eb3a
commit 0b15448d64
3 changed files with 31 additions and 17 deletions

11
Main.hs
View file

@ -31,7 +31,7 @@ writers.
module Main where
import Text.Pandoc
import Text.Pandoc.UTF8
import Text.Pandoc.Shared ( joinWithSep )
import Text.Pandoc.Shared ( joinWithSep, HTMLMathMethod (..) )
import Text.Regex ( mkRegex, matchRegex )
import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) )
@ -406,7 +406,7 @@ main = do
, optNumberSections = numberSections
, optIncremental = incremental
, optSmart = smart
, optUseASCIIMathML = useAsciiMathML
, optUseASCIIMathML = useASCIIMathML
, optASCIIMathMLURL = asciiMathMLURL
, optDumpArgs = dumpArgs
, optIgnoreArgs = ignoreArgs
@ -450,6 +450,10 @@ main = do
Just cols -> read cols
Nothing -> stateColumns defaultParserState
let mathMethod = if useASCIIMathML
then ASCIIMathML asciiMathMLURL
else PlainMath
let tabFilter _ [] = ""
tabFilter _ ('\n':xs) = '\n':(tabFilter tabStop xs)
-- remove DOS line endings
@ -487,8 +491,7 @@ main = do
writerTableOfContents = toc &&
(not strict) &&
writerName/="s5",
writerUseASCIIMathML = useAsciiMathML,
writerASCIIMathMLURL = asciiMathMLURL,
writerHTMLMathMethod = mathMethod,
writerS5 = (writerName=="s5"),
writerIgnoreNotes = False,
writerIncremental = incremental,

View file

@ -92,6 +92,7 @@ module Text.Pandoc.Shared (
hierarchicalize,
isHeaderBlock,
-- * Writer options
HTMLMathMethod (..),
WriterOptions (..),
defaultWriterOptions
) where
@ -796,6 +797,12 @@ isHeaderBlock _ = False
-- Writer options
--
data HTMLMathMethod = PlainMath
| ASCIIMathML (Maybe String) -- url of ASCIIMathML.js
| GladTeX
| MimeTeX String -- url of mimetex.cgi
deriving (Show, Read, Eq)
-- | Options for writers
data WriterOptions = WriterOptions
{ writerStandalone :: Bool -- ^ Include header and footer
@ -804,8 +811,7 @@ data WriterOptions = WriterOptions
, writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs
, writerTableOfContents :: Bool -- ^ Include table of contents
, writerS5 :: Bool -- ^ We're writing S5
, writerUseASCIIMathML :: Bool -- ^ Use ASCIIMathML
, writerASCIIMathMLURL :: Maybe String -- ^ URL to asciiMathML.js
, writerHTMLMathMethod :: HTMLMathMethod -- ^ How to print math in HTML
, writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc)
, writerIncremental :: Bool -- ^ Incremental S5 lists
, writerNumberSections :: Bool -- ^ Number sections in LaTeX
@ -825,8 +831,7 @@ defaultWriterOptions =
, writerTabStop = 4
, writerTableOfContents = False
, writerS5 = False
, writerUseASCIIMathML = False
, writerASCIIMathMLURL = Nothing
, writerHTMLMathMethod = PlainMath
, writerIgnoreNotes = False
, writerIncremental = False
, writerNumberSections = False

View file

@ -100,11 +100,14 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) =
else style ! [thetype "text/css"] $ primHtml $
'\n':(unlines $ S.toList cssLines)
math = if stMath newstate
then case writerASCIIMathMLURL opts of
Just path -> script ! [src path,
thetype "text/javascript"] $
noHtml
Nothing -> primHtml asciiMathMLScript
then case writerHTMLMathMethod opts of
ASCIIMathML Nothing ->
primHtml asciiMathMLScript
ASCIIMathML (Just url) ->
script !
[src url, thetype "text/javascript"] $
noHtml
_ -> noHtml
else noHtml
head = header $ metadata +++ math +++ css +++
primHtml (writerHeader opts)
@ -397,10 +400,13 @@ inlineToHtml opts inline =
primHtmlChar "rdquo")
in do contents <- inlineListToHtml opts lst
return $ leftQuote +++ contents +++ rightQuote
(Math str) -> (if writerUseASCIIMathML opts
then modify (\st -> st {stMath = True})
else return ()) >>
return (stringToHtml ("$" ++ str ++ "$"))
(Math str) -> modify (\st -> st {stMath = True}) >>
(return $ case writerHTMLMathMethod opts of
ASCIIMathML _ ->
stringToHtml ("$" ++ str ++ "$")
GladTeX ->
tag "eq" << str
_ -> stringToHtml ("$" ++ str ++ "$"))
(TeX str) -> return noHtml
(HtmlInline str) -> return $ primHtml str
(Link [Code str] (src,tit)) | "mailto:" `isPrefixOf` src ->