pandoc/Text/Pandoc/ASCIIMathML.hs
fiddlosopher ba32c2ec42 Simplified build process using template haskell.
+ Text/Pandoc/ASCIIMathML.hs, Text/Pandoc/DefaultHeaders.hs,
  and Text/Pandoc/Writers/S5.hs are no longer built in Setup.hs
  from templates in the templates/ directory.
+ Instead, they use template haskell to read data at compile
  time from the relevant files in data/.
+ Setup.hs is back to the default simple configuration.
+ Removed old templates and Extra-Tmp-Files field from
  pandoc.cabal.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@1357 788f1e2b-df1e-0410-8736-df70ead52e1b
2008-08-01 06:35:42 +00:00

11 lines
538 B
Haskell

{-# LANGUAGE TemplateHaskell #-}
-- | Definitions for use of ASCIIMathML in HTML.
-- (See <http://www1.chapman.edu/~jipsen/mathml/asciimath.html>.)
module Text.Pandoc.ASCIIMathML ( asciiMathMLScript ) where
import Text.Pandoc.Shared ( contentsOf )
-- | String containing ASCIIMathML javascript.
asciiMathMLScript :: String
asciiMathMLScript = "<script type=\"text/javascript\">\n" ++
$(contentsOf $ "data/ASCIIMathML.js.comment") ++
$(contentsOf $ "data/ASCIIMathML.js.packed") ++ "</script>\n"