2012-01-22 19:58:45 -08:00
|
|
|
{-
|
|
|
|
Copyright (C) 2012 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.Slides
|
|
|
|
Copyright : Copyright (C) 2012 John MacFarlane
|
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Utility functions for splitting documents into slides for slide
|
|
|
|
show formats (dzslides, s5, slidy, beamer).
|
|
|
|
-}
|
2012-01-23 13:25:55 -08:00
|
|
|
module Text.Pandoc.Slides ( toSlideElements, SlideElement(..) ) where
|
2012-01-22 21:31:10 -08:00
|
|
|
import Text.Pandoc.Definition
|
|
|
|
import Text.ParserCombinators.Parsec
|
|
|
|
import Text.Parsec.Pos (initialPos)
|
2012-01-22 23:53:19 -08:00
|
|
|
import Control.Monad
|
2012-01-22 19:58:45 -08:00
|
|
|
|
2012-01-22 23:53:19 -08:00
|
|
|
data SlideElement = SectionSlide Int [Inline]
|
2012-01-23 13:25:55 -08:00
|
|
|
| ContentSlide [Inline] [Block] -- title - contents
|
2012-01-22 21:31:10 -08:00
|
|
|
deriving (Read, Show)
|
2012-01-22 19:58:45 -08:00
|
|
|
|
2012-01-22 21:31:10 -08:00
|
|
|
toSlideElements :: [Block] -> [SlideElement]
|
|
|
|
toSlideElements bs =
|
|
|
|
case parse (pElements $ getSlideLevel bs) "blocks" bs of
|
2012-01-23 21:05:43 -08:00
|
|
|
Left err -> error $ "toSlideElements: " ++ show err -- should never happen
|
2012-01-22 21:31:10 -08:00
|
|
|
Right res -> res
|
2012-01-22 19:58:45 -08:00
|
|
|
|
2012-01-22 21:31:10 -08:00
|
|
|
satisfies :: (Block -> Bool) -> GenParser Block () Block
|
|
|
|
satisfies f = token show (const $ initialPos "blocks")
|
|
|
|
(\x -> if f x then Just x else Nothing)
|
|
|
|
|
|
|
|
pElements :: Int -> GenParser Block () [SlideElement]
|
|
|
|
pElements slideLevel = do
|
2012-01-22 23:53:19 -08:00
|
|
|
res <- many (pSectionSlide slideLevel <|> pContentSlide slideLevel)
|
2012-01-22 21:31:10 -08:00
|
|
|
eof
|
|
|
|
return res
|
|
|
|
|
2012-01-22 23:53:19 -08:00
|
|
|
pContentSlide :: Int -> GenParser Block () SlideElement
|
|
|
|
pContentSlide slideLevel = try $ do
|
|
|
|
hrs <- many $ satisfies (== HorizontalRule)
|
|
|
|
Header _ tit <- option (Header 1 []) $ satisfies (isHeader (== slideLevel))
|
|
|
|
xs <- many $ try $ notFollowedBy (satisfies (== HorizontalRule)) >>
|
|
|
|
notFollowedBy (satisfies (isHeader (<= slideLevel))) >>
|
2012-01-23 13:25:55 -08:00
|
|
|
anyToken
|
|
|
|
guard $ not (null hrs && null tit && null xs) -- make sure we can't match empty
|
|
|
|
return $ ContentSlide tit xs
|
2012-01-22 21:31:10 -08:00
|
|
|
|
2012-01-22 23:53:19 -08:00
|
|
|
pSectionSlide :: Int -> GenParser Block () SlideElement
|
|
|
|
pSectionSlide slideLevel = try $ do
|
|
|
|
skipMany $ satisfies (== HorizontalRule)
|
|
|
|
Header lvl txt <- satisfies (isHeader (< slideLevel))
|
|
|
|
return $ SectionSlide lvl txt
|
|
|
|
|
|
|
|
isHeader :: (Int -> Bool) -> Block -> Bool
|
|
|
|
isHeader f (Header n _) = f n
|
|
|
|
isHeader _ _ = False
|
2012-01-22 21:31:10 -08:00
|
|
|
|
|
|
|
-- | Find level of header that starts slides (defined as the least header
|
|
|
|
-- level that occurs before a non-header/non-hrule in the blocks).
|
|
|
|
getSlideLevel :: [Block] -> Int
|
|
|
|
getSlideLevel = go 6
|
|
|
|
where go least (Header n _ : x : xs)
|
|
|
|
| n < least && nonHOrHR x = go n xs
|
|
|
|
| otherwise = go least (x:xs)
|
2012-01-23 13:25:55 -08:00
|
|
|
go least (_ : xs) = go least xs
|
2012-01-22 21:31:10 -08:00
|
|
|
go least [] = least
|
|
|
|
nonHOrHR (Header _ _) = False
|
|
|
|
nonHOrHR (HorizontalRule) = False
|
|
|
|
nonHOrHR _ = True
|