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
This commit is contained in:
fiddlosopher 2009-12-31 01:11:13 +00:00
parent 9551e36389
commit ae44c7297f
4 changed files with 62 additions and 141 deletions

View file

@ -34,29 +34,21 @@ Description: Pandoc is a Haskell library for converting from one markup
which convert this native representation into a target
format. Thus, adding an input or output format requires
only adding a reader or writer.
Data-Files: templates/html.template, templates/docbook.template,
Data-Files:
-- templates
templates/html.template, templates/docbook.template,
templates/opendocument.template, templates/latex.template,
templates/context.template, templates/texinfo.template,
templates/man.template, templates/markdown.template,
templates/rst.template, templates/s5.template,
templates/mediawiki.template, templates/rtf.template
-- documentation
README, INSTALL, COPYRIGHT, BUGS, changelog,
-- wrappers
markdown2pdf, html2markdown, hsmarkdown
Extra-Source-Files:
-- sources for man pages
man/man1/pandoc.1.md, man/man1/markdown2pdf.1.md,
man/man1/html2markdown.1.md, man/man1/hsmarkdown.1.md,
-- Makefile
Makefile,
-- data for DefaultTemplates.hs
data/templates/ConTeXt.template,
data/templates/Docbook.template,
data/templates/LaTeX.template,
data/templates/OpenDocument.template,
data/templates/RTF.template,
data/templates/S5.template,
templates/mediawiki.template, templates/rtf.template,
-- data for ODT writer
data/odt-styles/meta.xml,
data/odt-styles/settings.xml,
data/odt-styles/META-INF/manifest.xml,
data/odt-styles/Thumbnails/thumbnail.png,
data/odt-styles/styles.xml,
data/odt-styles/mimetype,
-- data for LaTeXMathML writer
data/LaTeXMathML.js.comment,
data/LaTeXMathML.js.packed,
@ -69,13 +61,16 @@ Extra-Source-Files:
data/ui/default/opera.css,
data/ui/default/outline.css,
data/ui/default/print.css,
-- data for ODT writer
data/odt-styles/meta.xml,
data/odt-styles/settings.xml,
data/odt-styles/META-INF/manifest.xml,
data/odt-styles/Thumbnails/thumbnail.png,
data/odt-styles/styles.xml,
data/odt-styles/mimetype,
-- documentation
README, INSTALL, COPYRIGHT, BUGS, changelog,
-- wrappers
markdown2pdf, html2markdown, hsmarkdown
Extra-Source-Files:
-- sources for man pages
man/man1/pandoc.1.md, man/man1/markdown2pdf.1.md,
man/man1/html2markdown.1.md, man/man1/hsmarkdown.1.md,
-- Makefile
Makefile,
-- tests
tests/bodybg.gif,
tests/writer.latex,
@ -177,7 +172,6 @@ Library
Text.Pandoc.Shared,
Text.Pandoc.ODT,
Text.Pandoc.LaTeXMathML,
Text.Pandoc.DefaultTemplates,
Text.Pandoc.Highlighting,
Text.Pandoc.Readers.HTML,
Text.Pandoc.Readers.LaTeX,

View file

@ -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

View file

@ -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
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"
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"
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"

View file

@ -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",