aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Shared.hs15
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs16
-rw-r--r--src/pandoc.hs16
3 files changed, 33 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 025b54b93..ac1cf7373 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -66,6 +66,7 @@ module Text.Pandoc.Shared (
-- * Writer options
HTMLMathMethod (..),
ObfuscationMethod (..),
+ HTMLSlideVariant (..),
WriterOptions (..),
defaultWriterOptions,
-- * File handling
@@ -466,6 +467,12 @@ data ObfuscationMethod = NoObfuscation
| JavascriptObfuscation
deriving (Show, Read, Eq)
+-- | Varieties of HTML slide shows.
+data HTMLSlideVariant = S5Slides
+ | SlidySlides
+ | NoSlides
+ deriving (Show, Read, Eq)
+
-- | Options for writers
data WriterOptions = WriterOptions
{ writerStandalone :: Bool -- ^ Include header and footer
@@ -474,11 +481,11 @@ data WriterOptions = WriterOptions
, writerEPUBMetadata :: String -- ^ Metadata to include in EPUB
, writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs
, writerTableOfContents :: Bool -- ^ Include table of contents
- , writerS5 :: Bool -- ^ We're writing S5
+ , writerSlideVariant :: HTMLSlideVariant -- ^ Are we writing S5 or Slidy?
+ , writerIncremental :: Bool -- ^ True if lists should be incremental
, writerXeTeX :: Bool -- ^ Create latex suitable for use by xetex
, 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
, writerStrictMarkdown :: Bool -- ^ Use strict markdown syntax
, writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
@@ -499,11 +506,11 @@ defaultWriterOptions =
, writerEPUBMetadata = ""
, writerTabStop = 4
, writerTableOfContents = False
- , writerS5 = False
+ , writerSlideVariant = NoSlides
+ , writerIncremental = False
, writerXeTeX = False
, writerHTMLMathMethod = PlainMath
, writerIgnoreNotes = False
- , writerIncremental = False
, writerNumberSections = False
, writerStrictMarkdown = False
, writerReferenceLinks = False
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 08cd18ad0..cd03a51b5 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -197,10 +197,16 @@ elementToHtml opts (Sec level num id' title' elements) = do
innerContents <- mapM (elementToHtml opts) elements
modify $ \st -> st{stSecNum = num} -- update section number
header' <- blockToHtml opts (Header level title')
- return $ if writerS5 opts || (writerStrictMarkdown opts && not (writerTableOfContents opts))
- -- S5 gets confused by the extra divs around sections
- then toHtmlFromList (header' : innerContents)
- else thediv ! [prefixedId opts id'] << (header' : innerContents)
+ let stuff = header' : innerContents
+ return $ case writerSlideVariant opts of
+ SlidySlides | level == 1 ->
+ thediv ! [prefixedId opts id', theclass "slide"] << stuff
+ S5Slides -> toHtmlFromList stuff
+ -- S5 gets confused by the extra divs around sections
+ _ | (writerStrictMarkdown opts &&
+ not (writerTableOfContents opts)) ->
+ toHtmlFromList stuff
+ _ -> thediv ! [prefixedId opts id'] << stuff
-- | Convert list of Note blocks to a footnote <div>.
-- Assumes notes are sorted.
@@ -296,7 +302,7 @@ blockToHtml opts (BlockQuote blocks) =
-- in S5, treat list in blockquote specially
-- if default is incremental, make it nonincremental;
-- otherwise incremental
- if writerS5 opts
+ if writerSlideVariant opts /= NoSlides
then let inc = not (writerIncremental opts) in
case blocks of
[BulletList lst] -> blockToHtml (opts {writerIncremental = inc})
diff --git a/src/pandoc.hs b/src/pandoc.hs
index a2be60d52..38db4c6df 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -32,7 +32,7 @@ module Main where
import Text.Pandoc
import Text.Pandoc.Writers.S5 (s5HeaderIncludes)
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
- headerShift )
+ headerShift, HTMLSlideVariant(..) )
#ifdef _HIGHLIGHTING
import Text.Pandoc.Highlighting ( languages )
#endif
@@ -107,6 +107,7 @@ writers = [("native" , writeNative)
,("html" , writeHtmlString)
,("html+lhs" , writeHtmlString)
,("s5" , writeS5String)
+ ,("slidy" , writeHtmlString)
,("docbook" , writeDocbook)
,("opendocument" , writeOpenDocument)
,("odt" , \_ _ -> "")
@@ -142,7 +143,7 @@ data Opt = Opt
, optVariables :: [(String,String)] -- ^ Template variables to set
, optOutputFile :: String -- ^ Name of output file
, optNumberSections :: Bool -- ^ Number sections in LaTeX
- , optIncremental :: Bool -- ^ Use incremental lists in S5
+ , optIncremental :: Bool -- ^ Use incremental lists in Slidy/S5
, optXeTeX :: Bool -- ^ Format latex for xetex
, optSmart :: Bool -- ^ Use smart typography
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
@@ -300,7 +301,7 @@ options =
, Option "i" ["incremental"]
(NoArg
(\opt -> return opt { optIncremental = True }))
- "" -- "Make list items display incrementally in S5"
+ "" -- "Make list items display incrementally in Slidy/S5"
, Option "" ["xetex"]
(NoArg
@@ -733,6 +734,11 @@ main = do
then "."
else takeDirectory (head sources)
+ let slideVariant = case writerName' of
+ "s5" -> S5Slides
+ "slidy" -> SlidySlides
+ _ -> NoSlides
+
let startParserState =
defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop,
@@ -759,10 +765,10 @@ main = do
writerTableOfContents = toc &&
writerName' /= "s5",
writerHTMLMathMethod = mathMethod,
- writerS5 = (writerName' == "s5"),
+ writerSlideVariant = slideVariant,
+ writerIncremental = incremental,
writerXeTeX = xetex,
writerIgnoreNotes = False,
- writerIncremental = incremental,
writerNumberSections = numberSections,
writerStrictMarkdown = strict,
writerReferenceLinks = referenceLinks,