"
s5CSS :: String
s5CSS = "\n\n\n\n"
s5Links :: String
s5Links = "\n\n\n\n\n\n\n"
-- | Converts 'Pandoc' to an S5 HTML presentation.
writeS5 :: WriterOptions -> Pandoc -> String
writeS5 options = writeHtml options . insertS5Structure
-- | Inserts HTML needed for an S5 presentation (e.g. around slides).
layoutDiv :: [Inline] -- ^ Title of document (for header or footer)
-> String -- ^ Date of document (for header or footer)
-> [Block] -- ^ List of block elements returned
layoutDiv title date = [(RawHtml "\n")]
presentationStart = (RawHtml "\n\n")
presentationEnd = (RawHtml "
\n")
slideStart = (RawHtml "\n")
slideEnd = (RawHtml "
\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
if (null rest) then
if beginning then
beforeHead
else
beforeHead ++ [slideEnd]
else
if beginning then
beforeHead ++ slideStart:(head rest):(insertSlides False (tail rest))
else
beforeHead ++ slideEnd:slideStart:(head rest):(insertSlides False (tail rest))
-- | 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 [Str (joinWithSep ", " authors)]), (Header 4 [Str date]), slideEnd] else [] in
let newBlocks = (layoutDiv title date) ++ presentationStart:firstSlide ++ slides ++ [presentationEnd] in
Pandoc (Meta title authors date) newBlocks