summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:11:13 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:11:13 +0000
commitae44c7297f5ce12a3f1acd8c44efe11870805c0c (patch)
tree0369f97549314489af296f7c7d95227ece546622 /src
parent9551e363891c2cf31c8a82941c9101571d32987e (diff)
Removed TH dependency from S5 module, removed DefaultTemplates.
S5 module now exports s5HeaderIncludes, which pandoc.hs includes if writer is s5 and standalone. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1691 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/DefaultTemplates.hs69
-rw-r--r--src/Text/Pandoc/Writers/S5.hs75
-rw-r--r--src/pandoc.hs13
3 files changed, 42 insertions, 115 deletions
diff --git a/src/Text/Pandoc/DefaultTemplates.hs b/src/Text/Pandoc/DefaultTemplates.hs
deleted file mode 100644
index 533fb10a6..000000000
--- a/src/Text/Pandoc/DefaultTemplates.hs
+++ /dev/null
@@ -1,69 +0,0 @@
-{-# LANGUAGE CPP, TemplateHaskell #-}
-{-
-Copyright (C) 2006-7 John MacFarlane <jgm@berkeley.edu>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
--}
-
-{- |
- Module : Text.Pandoc.DefaultTemplates
- Copyright : Copyright (C) 2006-7 John MacFarlane
- License : GNU GPL, version 2 or above
-
- Maintainer : John MacFarlane <jgm@berkeley.edu>
- Stability : alpha
- Portability : portable
-
-Default templates for Pandoc writers.
--}
-module Text.Pandoc.DefaultTemplates ( defaultLaTeXTemplate,
- defaultConTeXtTemplate,
- defaultDocbookTemplate,
- defaultOpenDocumentTemplate,
- defaultS5Template,
- defaultRTFTemplate
- ) where
-import Text.Pandoc.Writers.S5
-import Text.Pandoc.Shared
-import System.FilePath ( (</>) )
-import Text.Pandoc.TH ( contentsOf )
-
-defaultLaTeXTemplate :: String
-#ifndef __HADDOCK__
-defaultLaTeXTemplate = $(contentsOf $ "data" </> "templates" </> "LaTeX.template")
-#endif
-
-defaultConTeXtTemplate :: String
-#ifndef __HADDOCK__
-defaultConTeXtTemplate = $(contentsOf $ "data" </> "templates" </> "ConTeXt.template")
-#endif
-
-defaultDocbookTemplate :: String
-#ifndef __HADDOCK__
-defaultDocbookTemplate = $(contentsOf $ "data" </> "templates" </> "Docbook.template")
-#endif
-
-defaultOpenDocumentTemplate :: String
-#ifndef __HADDOCK__
-defaultOpenDocumentTemplate = $(contentsOf $ "data" </> "templates" </> "OpenDocument.template")
-#endif
-
-defaultS5Template :: String
-defaultS5Template = substitute "$" "$$" $ s5Meta ++ s5CSS ++ s5Javascript
-
-defaultRTFTemplate :: String
-#ifndef __HADDOCK__
-defaultRTFTemplate = $(contentsOf $ "data" </> "templates" </> "RTF.template")
-#endif
diff --git a/src/Text/Pandoc/Writers/S5.hs b/src/Text/Pandoc/Writers/S5.hs
index 6f528503a..6187bc9a8 100644
--- a/src/Text/Pandoc/Writers/S5.hs
+++ b/src/Text/Pandoc/Writers/S5.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP, TemplateHaskell #-}
{-
Copyright (C) 2006-7 John MacFarlane <jgm@berkeley.edu>
@@ -30,10 +29,8 @@ Definitions for creation of S5 powerpoint-like HTML.
(See <http://meyerweb.com/eric/tools/s5/>.)
-}
module Text.Pandoc.Writers.S5 (
- -- * Strings
- s5Meta,
- s5Javascript,
- s5CSS,
+ -- * Header includes
+ s5HeaderIncludes,
s5Links,
-- * Functions
writeS5,
@@ -41,55 +38,43 @@ module Text.Pandoc.Writers.S5 (
insertS5Structure
) where
import Text.Pandoc.Shared ( WriterOptions )
-import Text.Pandoc.TH ( contentsOf )
import Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString )
import Text.Pandoc.Definition
import Text.XHtml.Strict
import System.FilePath ( (</>) )
import Data.List ( intercalate )
+import Prelude hiding (readFile)
+import System.IO.UTF8 (readFile)
+import Paths_pandoc (getDataFileName)
+
+readDataFile :: FilePath -> IO String
+readDataFile fname = getDataFileName fname >>= readFile
+
+s5HeaderIncludes :: IO String
+s5HeaderIncludes = do
+ c <- s5CSS
+ j <- s5Javascript
+ return $ s5Meta ++ c ++ j
s5Meta :: String
s5Meta = "<!-- configuration parameters -->\n<meta name=\"defaultView\" content=\"slideshow\" />\n<meta name=\"controlVis\" content=\"hidden\" />\n"
-s5Javascript :: String
-#ifndef __HADDOCK__
-s5Javascript = "<script type=\"text/javascript\">\n" ++
- $(contentsOf $ "data" </> "ui" </> "default" </> "slides.js.comment") ++
- $(contentsOf $ "data" </> "ui" </> "default" </> "slides.js.packed") ++ "</script>\n"
-#endif
-
-s5CoreCSS :: String
-#ifndef __HADDOCK__
-s5CoreCSS = $(contentsOf $ "data" </> "ui" </> "default" </> "s5-core.css")
-#endif
-
-s5FramingCSS :: String
-#ifndef __HADDOCK__
-s5FramingCSS = $(contentsOf $ "data" </> "ui" </> "default" </> "framing.css")
-#endif
-
-s5PrettyCSS :: String
-#ifndef __HADDOCK__
-s5PrettyCSS = $(contentsOf $ "data" </> "ui" </> "default" </> "pretty.css")
-#endif
-
-s5OperaCSS :: String
-#ifndef __HADDOCK__
-s5OperaCSS = $(contentsOf $ "data" </> "ui" </> "default" </> "opera.css")
-#endif
-
-s5OutlineCSS :: String
-#ifndef __HADDOCK__
-s5OutlineCSS = $(contentsOf $ "data" </> "ui" </> "default" </> "outline.css")
-#endif
-
-s5PrintCSS :: String
-#ifndef __HADDOCK__
-s5PrintCSS = $(contentsOf $ "data" </> "ui" </> "default" </> "print.css")
-#endif
-
-s5CSS :: String
-s5CSS = "<style type=\"text/css\" media=\"projection\" id=\"slideProj\">\n" ++ s5CoreCSS ++ "\n" ++ s5FramingCSS ++ "\n" ++ s5PrettyCSS ++ "\n</style>\n<style type=\"text/css\" media=\"projection\" id=\"operaFix\">\n" ++ s5OperaCSS ++ "\n</style>\n<style type=\"text/css\" media=\"screen\" id=\"outlineStyle\">\n" ++ s5OutlineCSS ++ "\n</style>\n<style type=\"text/css\" media=\"print\" id=\"slidePrint\">\n" ++ s5PrintCSS ++ "\n</style>\n"
+s5Javascript :: IO String
+s5Javascript = do
+ jsCom <- readDataFile $ "data" </> "ui" </> "default" </> "slides.js.comment"
+ jsPacked <- readDataFile $ "data" </> "ui" </> "default" </> "slides.js.packed"
+ return $ "<script type=\"text/javascript\">\n" ++ jsCom ++ jsPacked ++
+ "</script>\n"
+
+s5CSS :: IO String
+s5CSS = do
+ s5CoreCSS <- readDataFile $ "data" </> "ui" </> "default" </> "s5-core.css"
+ s5FramingCSS <- readDataFile $ "data" </> "ui" </> "default" </> "framing.css"
+ s5PrettyCSS <- readDataFile $ "data" </> "ui" </> "default" </> "pretty.css"
+ s5OperaCSS <- readDataFile $ "data" </> "ui" </> "default" </> "opera.css"
+ s5OutlineCSS <- readDataFile $ "data" </> "ui" </> "default" </> "outline.css"
+ s5PrintCSS <- readDataFile $ "data" </> "ui" </> "default" </> "print.css"
+ return $ "<style type=\"text/css\" media=\"projection\" id=\"slideProj\">\n" ++ s5CoreCSS ++ "\n" ++ s5FramingCSS ++ "\n" ++ s5PrettyCSS ++ "\n</style>\n<style type=\"text/css\" media=\"projection\" id=\"operaFix\">\n" ++ s5OperaCSS ++ "\n</style>\n<style type=\"text/css\" media=\"screen\" id=\"outlineStyle\">\n" ++ s5OutlineCSS ++ "\n</style>\n<style type=\"text/css\" media=\"print\" id=\"slidePrint\">\n" ++ s5PrintCSS ++ "\n</style>\n"
s5Links :: String
s5Links = "<!-- style sheet links -->\n<link rel=\"stylesheet\" href=\"ui/default/slides.css\" type=\"text/css\" media=\"projection\" id=\"slideProj\" />\n<link rel=\"stylesheet\" href=\"ui/default/outline.css\" type=\"text/css\" media=\"screen\" id=\"outlineStyle\" />\n<link rel=\"stylesheet\" href=\"ui/default/print.css\" type=\"text/css\" media=\"print\" id=\"slidePrint\" />\n<link rel=\"stylesheet\" href=\"ui/default/opera.css\" type=\"text/css\" media=\"projection\" id=\"operaFix\" />\n<!-- S5 JS -->\n<script src=\"ui/default/slides.js\" type=\"text/javascript\"></script>\n"
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 44d0b96e6..26bf0abb8 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -32,6 +32,7 @@ writers.
module Main where
import Text.Pandoc
import Text.Pandoc.ODT
+import Text.Pandoc.Writers.S5 (s5HeaderIncludes)
import Text.Pandoc.Templates (getDefaultTemplate)
import Text.Pandoc.Shared ( HTMLMathMethod (..), tabFilter, ObfuscationMethod (..) )
#ifdef _HIGHLIGHTING
@@ -631,6 +632,16 @@ main = do
refs <- if null biblioFile then return [] else readBiblioFile biblioFile biblioFormat
#endif
+ variables' <- if writerName' == "s5" && standalone'
+ then do
+ inc <- s5HeaderIncludes
+ return $ case lookup "header-includes" variables of
+ Nothing -> ("header-includes", inc) : variables
+ Just a -> ("header-includes", a ++ inc) :
+ filter ((/= "header-includes") . fst)
+ variables
+ else return variables
+
let startParserState =
defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop,
@@ -650,7 +661,7 @@ main = do
writerTemplate = if null template
then defaultTemplate
else template,
- writerVariables = variables,
+ writerVariables = variables',
writerTabStop = tabStop,
writerTableOfContents = toc &&
writerName' /= "s5",