2017-12-28 16:39:47 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
|
|
|
module Tests.Writers.Powerpoint (tests) where
|
|
|
|
|
2017-12-28 21:06:38 +01:00
|
|
|
import Control.Exception (throwIO)
|
2017-12-28 16:39:47 +01:00
|
|
|
import Text.Pandoc
|
|
|
|
import Text.Pandoc.Builder
|
2017-12-29 15:18:54 +01:00
|
|
|
import Text.Pandoc.Arbitrary ()
|
|
|
|
import Text.Pandoc.Walk
|
2017-12-28 16:39:47 +01:00
|
|
|
import Test.Tasty
|
|
|
|
import Test.Tasty.HUnit
|
2017-12-29 15:18:54 +01:00
|
|
|
import Test.Tasty.QuickCheck
|
2017-12-28 16:39:47 +01:00
|
|
|
import Codec.Archive.Zip
|
2017-12-29 15:18:54 +01:00
|
|
|
import Text.XML.Light
|
|
|
|
import Data.List (isPrefixOf, isSuffixOf, sort)
|
|
|
|
import Data.Maybe (mapMaybe)
|
|
|
|
|
|
|
|
getPptxArchive :: WriterOptions -> Pandoc -> IO Archive
|
|
|
|
getPptxArchive opts pd = do
|
|
|
|
mbs <- runIO $
|
|
|
|
do setUserDataDir $ Just "../data"
|
|
|
|
writePowerpoint opts pd
|
|
|
|
case mbs of
|
|
|
|
Left e -> throwIO e
|
|
|
|
Right bs -> return $ toArchive bs
|
2017-12-28 16:39:47 +01:00
|
|
|
|
|
|
|
----- Number of Slides -----------
|
|
|
|
|
2017-12-28 21:06:38 +01:00
|
|
|
numberOfSlides :: WriterOptions -> Pandoc -> IO Int
|
2017-12-28 16:39:47 +01:00
|
|
|
numberOfSlides opts pd = do
|
2017-12-29 15:18:54 +01:00
|
|
|
archive <- getPptxArchive opts pd
|
|
|
|
return $
|
|
|
|
length $
|
|
|
|
filter (isSuffixOf ".xml") $
|
|
|
|
filter (isPrefixOf "ppt/slides/slide") $
|
|
|
|
filesInArchive archive
|
2017-12-28 16:39:47 +01:00
|
|
|
|
|
|
|
testNumberOfSlides :: TestName -> Int -> WriterOptions -> Pandoc -> TestTree
|
|
|
|
testNumberOfSlides name n opts pd =
|
2017-12-28 21:06:38 +01:00
|
|
|
testCase name $ do
|
|
|
|
n' <- numberOfSlides opts pd
|
|
|
|
n' @=? n
|
2017-12-28 16:39:47 +01:00
|
|
|
|
|
|
|
numSlideTests :: TestTree
|
|
|
|
numSlideTests = testGroup "Number of slides in output"
|
|
|
|
[ testNumberOfSlides
|
|
|
|
"simple one-slide deck" 1
|
|
|
|
def
|
|
|
|
(doc $ para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"with metadata (header slide)" 2
|
|
|
|
def
|
|
|
|
(setTitle "My Title" $ doc $ para "foo")
|
|
|
|
, testNumberOfSlides
|
2018-01-04 03:58:39 +01:00
|
|
|
"With h1 slide (using default slide-level)" 1
|
2017-12-28 16:39:47 +01:00
|
|
|
def
|
|
|
|
(doc $ header 1 "Header" <> para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"With h2 slide (using default slide-level)" 2
|
|
|
|
def
|
|
|
|
(doc $ header 1 "Header" <> header 2 "subeader" <> para "foo")
|
|
|
|
, testNumberOfSlides
|
2017-12-29 12:36:23 +01:00
|
|
|
"With h1 slide (using slide-level 3)" 2
|
|
|
|
def {writerSlideLevel= Just 3}
|
2017-12-28 16:39:47 +01:00
|
|
|
(doc $ header 1 "Header" <> para "foo")
|
|
|
|
, testNumberOfSlides
|
2017-12-29 12:36:23 +01:00
|
|
|
"With h2 slide (using slide-level 3)" 3
|
|
|
|
def {writerSlideLevel= Just 3}
|
2017-12-28 16:39:47 +01:00
|
|
|
(doc $ header 1 "Header" <> header 2 "subeader" <> para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"With image slide, no header" 3
|
|
|
|
def
|
|
|
|
(doc $
|
|
|
|
para "first slide" <>
|
2018-01-20 06:25:24 +01:00
|
|
|
para (image "lalune.jpg" "" "") <>
|
2017-12-28 16:39:47 +01:00
|
|
|
para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"With image slide, header" 3
|
|
|
|
def
|
|
|
|
(doc $
|
|
|
|
para "first slide" <>
|
|
|
|
header 2 "image header" <>
|
2018-01-20 06:25:24 +01:00
|
|
|
para (image "lalune.jpg" "" "") <>
|
2017-12-28 16:39:47 +01:00
|
|
|
para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"With table, no header" 3
|
|
|
|
def
|
|
|
|
(doc $
|
|
|
|
para "first slide" <>
|
2018-01-20 06:25:24 +01:00
|
|
|
simpleTable [para "foo" <> para "bar"] [[para "this" <> para "that"]] <>
|
2017-12-28 16:39:47 +01:00
|
|
|
para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"With table, header" 3
|
|
|
|
def
|
|
|
|
(doc $
|
|
|
|
para "first slide" <>
|
|
|
|
header 2 "table header" <>
|
2018-01-20 06:25:24 +01:00
|
|
|
simpleTable [para "foo" <> para "bar"] [[para "this" <> para "that"]] <>
|
2017-12-28 16:39:47 +01:00
|
|
|
para "foo")
|
|
|
|
, testNumberOfSlides
|
|
|
|
"hrule" 2
|
|
|
|
def
|
|
|
|
(doc $
|
|
|
|
para "first slide" <> horizontalRule <> para "last slide")
|
2017-12-29 12:36:23 +01:00
|
|
|
, testNumberOfSlides
|
|
|
|
"with notes slide" 2
|
|
|
|
def
|
|
|
|
(doc $
|
|
|
|
para $ text "Foo" <> note (para "note text"))
|
2017-12-28 16:39:47 +01:00
|
|
|
]
|
|
|
|
|
2017-12-29 15:18:54 +01:00
|
|
|
----- Content Types -----------
|
|
|
|
|
|
|
|
|
|
|
|
contentTypesFileExists :: WriterOptions -> Pandoc -> TestTree
|
|
|
|
contentTypesFileExists opts pd =
|
|
|
|
testCase "Existence of [Content_Types].xml file" $
|
|
|
|
do archive <- getPptxArchive opts pd
|
|
|
|
assertBool "Missing [Content_Types].xml file" $
|
2018-01-20 06:25:24 +01:00
|
|
|
"[Content_Types].xml" `elem` filesInArchive archive
|
2017-12-29 15:18:54 +01:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
-- We want an "Override" entry for each xml file under ppt/.
|
|
|
|
prop_ContentOverrides :: Pandoc -> IO Bool
|
|
|
|
prop_ContentOverrides pd = do
|
|
|
|
-- remove Math to avoid warnings
|
|
|
|
let go :: Inline -> Inline
|
|
|
|
go (Math _ _) = Str "Math"
|
|
|
|
go i = i
|
|
|
|
pd' = walk go pd
|
|
|
|
archive <- getPptxArchive def pd'
|
|
|
|
let xmlFiles = filter ("[Content_Types].xml" /=) $
|
|
|
|
filter (isSuffixOf ".xml") $
|
|
|
|
filesInArchive archive
|
|
|
|
contentTypes <- case findEntryByPath "[Content_Types].xml" archive of
|
|
|
|
Just ent -> return $ fromEntry ent
|
|
|
|
Nothing -> throwIO $
|
|
|
|
PandocSomeError "Missing [Content_Types].xml file"
|
|
|
|
typesElem <- case parseXMLDoc contentTypes of
|
2018-01-20 06:25:24 +01:00
|
|
|
Just element -> return element
|
2017-12-29 15:18:54 +01:00
|
|
|
Nothing -> throwIO $
|
|
|
|
PandocSomeError "[Content_Types].xml cannot be parsed"
|
|
|
|
let ns = findAttr (QName "xmlns" Nothing Nothing) typesElem
|
|
|
|
overrides = findChildren (QName "Override" ns Nothing) typesElem
|
|
|
|
partNames = mapMaybe (findAttr (QName "PartName" Nothing Nothing)) overrides
|
|
|
|
-- files in content_types are absolute
|
|
|
|
absXmlFiles = map (\fp -> case fp of
|
|
|
|
('/':_) -> fp
|
|
|
|
_ -> '/': fp
|
|
|
|
)
|
|
|
|
xmlFiles
|
|
|
|
return $ sort absXmlFiles == sort partNames
|
|
|
|
|
|
|
|
contentOverridesTests :: TestTree
|
|
|
|
contentOverridesTests = localOption (QuickCheckTests 20) $
|
|
|
|
testProperty "Content Overrides for each XML file" $
|
|
|
|
\x -> ioProperty $ prop_ContentOverrides (x :: Pandoc)
|
|
|
|
|
|
|
|
contentTypeTests :: TestTree
|
|
|
|
contentTypeTests = testGroup "[Content_Types].xml file"
|
|
|
|
[ contentTypesFileExists def (doc $ para "foo")
|
|
|
|
, contentOverridesTests
|
|
|
|
]
|
2017-12-28 16:39:47 +01:00
|
|
|
|
|
|
|
tests :: [TestTree]
|
2017-12-29 15:18:54 +01:00
|
|
|
tests = [ numSlideTests
|
|
|
|
, contentTypeTests
|
|
|
|
]
|