aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers/Powerpoint.hs
blob: 1390810133cec000824d5dcdd979a35f7cec234d (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
{-# LANGUAGE PatternGuards     #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiWayIf        #-}

module Tests.Writers.Powerpoint (tests) where

-- import Control.Exception (throwIO)
import Text.Pandoc
import Test.Tasty
import Test.Tasty.HUnit
import Codec.Archive.Zip
import Text.XML.Light
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text.IO as T
import Data.List (isPrefixOf, isSuffixOf, sort, (\\), intercalate)
import Data.Maybe (fromJust, isNothing)
import Tests.Helpers
import Data.Algorithm.Diff
import Control.Monad (when)


getPptxBytes :: WriterOptions
             -> FilePath
             -> FilePath
             -> IO (BL.ByteString, BL.ByteString)
getPptxBytes opts nativeFp pptxFp = do
  ntvTxt <- T.readFile nativeFp
  ntv <- runIOorExplode $ readNative def ntvTxt
  myPptxBs <- runIOorExplode $ writePowerpoint opts ntv
  goodPptxBs <- BL.readFile pptxFp
  return (myPptxBs, goodPptxBs)


assertSameFileList :: Archive -> Archive -> FilePath -> Assertion
assertSameFileList myArch goodArch pptxFp = do
  let filesMy = filesInArchive myArch
      filesGood = filesInArchive goodArch
      diffMyGood = filesMy \\ filesGood
      diffGoodMy = filesGood \\ filesMy
  if | null diffMyGood && null diffGoodMy -> return ()
     | null diffMyGood ->
         assertFailure $
         "Files in " ++ pptxFp ++ " but not in generated archive:\n" ++
         intercalate ", " diffGoodMy
     | null diffGoodMy ->
         assertFailure $
         "Files in generated archive but not in " ++ pptxFp ++ ":\n" ++
         intercalate ", " diffMyGood
     | otherwise ->
         assertFailure $
         "Files in " ++ pptxFp ++ " but not in generated archive:\n" ++
         intercalate ", " diffGoodMy ++
         "\n" ++
         "Files in generated archive but not in " ++ pptxFp ++ ":\n" ++
         intercalate ", " diffMyGood

compareXMLBool :: Content -> Content -> Bool
-- We make a special exception for times at the moment, and just pass
-- them because we can't control the utctime when running IO. Besides,
-- so long as we have two times, we're okay.
compareXMLBool (Elem myElem) (Elem goodElem)
  | (QName "created" _ (Just "dcterms")) <- elName myElem
  , (QName "created" _ (Just "dcterms")) <- elName goodElem =
      True
compareXMLBool (Elem myElem) (Elem goodElem)
  | (QName "modified" _ (Just "dcterms")) <- elName myElem
  , (QName "modified" _ (Just "dcterms")) <- elName goodElem =
      True
compareXMLBool (Elem myElem) (Elem goodElem) =
  and [ elName myElem == elName goodElem
      , elAttribs myElem == elAttribs goodElem
      , and $
        map (uncurry compareXMLBool) $
        zip (elContent myElem) (elContent goodElem)
      ]
compareXMLBool (Text myCData) (Text goodCData) =
  and [ cdVerbatim myCData == cdVerbatim goodCData
      , cdData myCData == cdData goodCData
      , cdLine myCData == cdLine goodCData
      ]
compareXMLBool (CRef myStr) (CRef goodStr) =
  myStr == goodStr
compareXMLBool _ _ = False

displayDiff :: Content -> Content -> String
displayDiff elemA elemB =
  showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB)

compareXMLFile :: FilePath -> Archive -> Archive -> Assertion
compareXMLFile fp myArch goodArch = do
  let mbMyEntry = findEntryByPath fp myArch
  when (isNothing mbMyEntry)
    (assertFailure $
    "Can't extract " ++ fp ++ " from generated archive")
  let mbMyXMLDoc = parseXMLDoc $ fromEntry $ fromJust mbMyEntry
  when (isNothing mbMyXMLDoc)
    (assertFailure $
    "Can't parse xml in  " ++ fp ++ " from generated archive")
  let myContent = Elem $ fromJust mbMyXMLDoc

  let mbGoodEntry = findEntryByPath fp goodArch
  when (isNothing mbGoodEntry)
    (assertFailure $
    "Can't extract " ++ fp ++ " from archive in stored pptx file")
  let mbGoodXMLDoc = parseXMLDoc $ fromEntry $ fromJust mbGoodEntry
  when (isNothing mbGoodXMLDoc)
    (assertFailure $
    "Can't parse xml in  " ++ fp ++ " from archive in stored pptx file")
  let goodContent = Elem $ fromJust mbGoodXMLDoc

  assertBool
    ("Non-matching xml in " ++ fp ++ ":\n" ++ displayDiff myContent goodContent)
    (compareXMLBool myContent goodContent)

compareBinaryFile :: FilePath -> Archive -> Archive -> Assertion
compareBinaryFile fp myArch goodArch = do
  let mbMyEntry = findEntryByPath fp myArch
  when (isNothing mbMyEntry)
    (assertFailure $
    "Can't extract " ++ fp ++ " from generated archive")
  let myBytes = fromEntry $ fromJust mbMyEntry

  let mbGoodEntry = findEntryByPath fp goodArch
  when (isNothing mbGoodEntry)
    (assertFailure $
    "Can't extract " ++ fp ++ " from archive in stored pptx file")
  let goodBytes = fromEntry $ fromJust mbGoodEntry

  assertBool (fp ++ " doesn't match") (myBytes == goodBytes)

testSameFileList :: WriterOptions -> FilePath -> FilePath -> TestTree
testSameFileList opts myFp goodFp =
  testCase ("Identical file list in archives") $ do
  (myBS, goodBS) <- getPptxBytes opts myFp goodFp
  let myArch = toArchive myBS
      goodArch = toArchive goodBS
  (assertSameFileList myArch goodArch goodFp)

testSameXML :: WriterOptions -> FilePath -> FilePath -> TestTree
testSameXML opts myFp goodFp = testCaseSteps "Comparing extracted xml files" $
  \step -> do
    (myBS, goodBS) <- getPptxBytes opts myFp goodFp
    let myArch = toArchive myBS
        goodArch = toArchive goodBS

    let xmlFileList = sort $
          filter (\fp -> ".xml" `isSuffixOf` fp || ".rels" `isSuffixOf` fp)
          (filesInArchive myArch)
    mapM_
      (\fp -> step ("- " ++ fp) >> compareXMLFile fp myArch goodArch)
      xmlFileList

testSameMedia :: WriterOptions -> FilePath -> FilePath -> TestTree
testSameMedia opts myFp goodFp = testCaseSteps "Comparing media files" $
  \step -> do
    (myBS, goodBS) <- getPptxBytes opts myFp goodFp
    let myArch = toArchive myBS
        goodArch = toArchive goodBS

    let mediaFileList = sort $
          filter (\fp -> "ppt/media/" `isPrefixOf` fp)
          (filesInArchive myArch)

    mapM_
      (\fp -> step ("- " ++ fp) >> compareBinaryFile fp myArch goodArch)
      mediaFileList

testCompareWithOpts :: String -> WriterOptions ->FilePath -> FilePath -> TestTree
testCompareWithOpts testName opts nativeFp pptxFp =
  testGroup testName [ testSameFileList opts nativeFp pptxFp
                     , testSameXML opts nativeFp pptxFp
                     , testSameMedia opts nativeFp pptxFp
                     ]


testCompare :: String -> FilePath -> FilePath -> TestTree
testCompare testName nativeFp pptxFp =
  testCompareWithOpts testName def nativeFp pptxFp

--------------------------------------------------------------

tests :: [TestTree]
tests = [ testCompare
          "Inline formatting"
          "pptx/inline_formatting.native"
          "pptx/inline_formatting.pptx"
        , testCompare
          "slide breaks (default slide-level)"
          "pptx/slide_breaks.native"
          "pptx/slide_breaks.pptx"
        , testCompareWithOpts
          "slide breaks (slide-level set to 1)"
          def{writerSlideLevel=Just 1}
          "pptx/slide_breaks.native"
          "pptx/slide_breaks_slide_level_1.pptx"
        ]