diff --git a/pandoc.cabal b/pandoc.cabal index 8f8195d67..88c31f41e 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -42,7 +42,7 @@ Data-Files: templates/man.template, templates/markdown.template, templates/rst.template, templates/plain.template, templates/mediawiki.template, templates/rtf.template, - templates/slidy.template, + templates/s5.template, templates/slidy.template, -- data for ODT writer reference.odt, -- stylesheet for EPUB writer diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index a4caf106d..f0d679dae 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -80,8 +80,6 @@ module Text.Pandoc , writeTexinfo , writeHtml , writeHtmlString - , writeS5 - , writeS5String , writeDocbook , writeOpenDocument , writeMan diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 372954ae3..c8ddc3abf 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -83,7 +83,6 @@ getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first -> String -- ^ Name of writer -> IO (Either E.IOException String) getDefaultTemplate _ "native" = return $ Right "" -getDefaultTemplate user "s5" = getDefaultTemplate user "html" getDefaultTemplate user "odt" = getDefaultTemplate user "opendocument" getDefaultTemplate user writer = do let format = takeWhile (/='+') writer -- strip off "+lhs" if present diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 09af03f4e..abe7e3a42 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -117,12 +117,10 @@ pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do (Header 1 _ : _) -> [] _ -> [RawHtml "<div class=\"slide\">\n"] blocks' <- liftM toHtmlFromList $ - case writerSlideVariant opts of - SlidySlides -> mapM (blockToHtml opts) $ - preamble ++ - cutUp blocks ++ - [RawHtml "</div>"] - _ -> mapM (elementToHtml opts) sects + if writerSlideVariant opts `elem` [SlidySlides, S5Slides] + then mapM (blockToHtml opts) $ preamble ++ + cutUp blocks ++ [RawHtml "</div>"] + else mapM (elementToHtml opts) sects st <- get let notes = reverse (stNotes st) let thebody = blocks' +++ footnoteSection notes diff --git a/src/Text/Pandoc/Writers/S5.hs b/src/Text/Pandoc/Writers/S5.hs index d2dab07a3..a439363f1 100644 --- a/src/Text/Pandoc/Writers/S5.hs +++ b/src/Text/Pandoc/Writers/S5.hs @@ -30,20 +30,13 @@ Definitions for creation of S5 powerpoint-like HTML. -} module Text.Pandoc.Writers.S5 ( -- * Header includes - s5HeaderIncludes, - s5Meta, - s5Links, - -- * Functions - writeS5, - writeS5String, - insertS5Structure + s5HeaderIncludes ) where import Text.Pandoc.Shared ( WriterOptions, readDataFile ) import Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString ) import Text.Pandoc.Definition import Text.XHtml.Strict import System.FilePath ( (</>) ) -import Data.List ( intercalate ) s5HeaderIncludes :: Maybe FilePath -> IO String s5HeaderIncludes datadir = do @@ -71,59 +64,3 @@ s5CSS datadir = do s5PrintCSS <- readDataFile datadir $ "s5" </> "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" - --- | Converts Pandoc document to an S5 HTML presentation (Html structure). -writeS5 :: WriterOptions -> Pandoc -> Html -writeS5 options = (writeHtml options) . insertS5Structure - --- | Converts Pandoc document to an S5 HTML presentation (string). -writeS5String :: WriterOptions -> Pandoc -> String -writeS5String options = (writeHtmlString options) . insertS5Structure - --- | Inserts HTML needed for an S5 presentation (e.g. around slides). -layoutDiv :: [Inline] -- ^ Title of document (for header or footer) - -> [Inline] -- ^ Date of document (for header or footer) - -> [Block] -- ^ List of block elements returned -layoutDiv title' date = [(RawHtml "<div class=\"layout\">\n<div id=\"controls\"></div>\n<div id=\"currentSlide\"></div>\n<div id=\"header\"></div>\n<div id=\"footer\">\n"), (Header 1 date), (Header 2 title'), (RawHtml "</div>\n</div>\n")] - -presentationStart :: Block -presentationStart = RawHtml "<div class=\"presentation\">\n\n" - -presentationEnd :: Block -presentationEnd = RawHtml "</div>\n" - -slideStart :: Block -slideStart = RawHtml "<div class=\"slide\">\n" - -slideEnd :: Block -slideEnd = RawHtml "</div>\n" - --- | Returns 'True' if block is a Header 1. -isH1 :: Block -> Bool -isH1 (Header 1 _) = True -isH1 _ = False - --- | Insert HTML around sections to make individual slides. -insertSlides :: Bool -> [Block] -> [Block] -insertSlides beginning blocks = - let (beforeHead, rest) = break isH1 blocks - in case rest of - [] -> beforeHead ++ [slideEnd | not beginning] - (h:t) -> beforeHead ++ [slideEnd | not beginning] ++ - (slideStart : h : insertSlides False t) - --- | Insert blocks into 'Pandoc' for slide structure. -insertS5Structure :: Pandoc -> Pandoc -insertS5Structure (Pandoc meta' []) = Pandoc meta' [] -insertS5Structure (Pandoc (Meta title' authors date) blocks) = - let slides = insertSlides True blocks - firstSlide = if not (null title') - then [slideStart, (Header 1 title'), - (Header 3 (intercalate [LineBreak] authors)), - (Header 4 date), slideEnd] - else [] - newBlocks = (layoutDiv title' date) ++ presentationStart:firstSlide ++ - slides ++ [presentationEnd] - in Pandoc (Meta title' authors date) newBlocks diff --git a/src/pandoc.hs b/src/pandoc.hs index b7ff42803..67e81d6fa 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -30,7 +30,7 @@ writers. -} module Main where import Text.Pandoc -import Text.Pandoc.Writers.S5 (s5HeaderIncludes, s5Links, s5Meta) +import Text.Pandoc.Writers.S5 (s5HeaderIncludes) import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile, headerShift ) #ifdef _HIGHLIGHTING @@ -105,7 +105,7 @@ writers :: [ ( String, WriterOptions -> Pandoc -> String ) ] writers = [("native" , writeNative) ,("html" , writeHtmlString) ,("html+lhs" , writeHtmlString) - ,("s5" , writeS5String) + ,("s5" , writeHtmlString) ,("slidy" , writeHtmlString) ,("docbook" , writeDocbook) ,("opendocument" , writeOpenDocument) @@ -746,10 +746,7 @@ main = do variables' <- case (writerName', standalone', offline) of ("s5", True, True) -> do inc <- s5HeaderIncludes datadir - return $ ("header-includes", inc) : variables - ("s5", True, False) -> - return $ ("header-includes", s5Meta ++ s5Links) : - variables + return $ ("s5includes", inc) : variables ("slidy", True, True) -> do slidyJs <- readDataFile datadir $ "slidy" </> "slidy.min.js" diff --git a/templates/s5.template b/templates/s5.template new file mode 100644 index 000000000..360135244 --- /dev/null +++ b/templates/s5.template @@ -0,0 +1,70 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml"> +<head> + <title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title> + <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> + <meta name="generator" content="pandoc" /> +$for(author)$ + <meta name="author" content="$author$" /> +$endfor$ +$if(date)$ + <meta name="date" content="$date$" /> +$endif$ + <!-- configuration parameters --> + <meta name="defaultView" content="slideshow" /> + <meta name="controlVis" content="hidden" /> +$if(highlighting-css)$ + <style type="text/css"> +$highlighting-css$ + </style> +$endif$ +$for(css)$ + <link rel="stylesheet" href="$css$" type="text/css" /> +$endfor$ +$if(s5includes)$ +$s5includes$ +$else$ + <!-- style sheet links --> + <link rel="stylesheet" href="ui/default/slides.css" type="text/css" media="projection" id="slideProj" /> + <link rel="stylesheet" href="ui/default/outline.css" type="text/css" media="screen" id="outlineStyle" /> + <link rel="stylesheet" href="ui/default/print.css" type="text/css" media="print" id="slidePrint" /> + <link rel="stylesheet" href="ui/default/opera.css" type="text/css" media="projection" id="operaFix" /> + <!-- S5 JS --> + <script src="ui/default/slides.js" type="text/javascript"></script> +$endif$ +$if(math)$ + $math$ +$endif$ +$for(header-includes)$ + $header-includes$ +$endfor$ +</head> +<body> +$for(include-before)$ +$include-before$ +$endfor$ +<h1 class="title">$title$</h1> +<div class="layout"> +<div id="controls"></div> +<div id="currentSlide"></div> +<div id="header"></div> +<div id="footer"> + <h1>$date$</h1> + <h2>$title$</h2> +</div> +</div> +<div class="presentation"> +$if(title)$ +<div class="slide"> + <h1>$title$</h1> + <h3>$for(author)$$author$$sep$<br/>$endfor$</h3> + <h4>$date$</h4> +</div> +$endif$ +$body$ +$for(include-after)$ +$include-after$ +$endfor$ +</div> +</body> +</html>