pandoc/test/Tests/Readers/EPUB.hs
Albert Krewinkel 37a82b0b11 Add missing copyright notices and remove license boilerplate (#5112)
Quite a few modules were missing copyright notices.

This commit adds copyright notices everywhere via haddock module
headers.  The old license boilerplate comment is redundant with this and has
been removed.

Update copyright years to 2019.

Closes #4592.
2019-02-04 13:52:31 -08:00

53 lines
1.4 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Readers.EPUB
Copyright : © 2006-2019 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.eu>
Stability : alpha
Portability : portable
Tests for the EPUB mediabag.
-}
module Tests.Readers.EPUB (tests) where
import Prelude
import qualified Data.ByteString.Lazy as BL
import Test.Tasty
import Test.Tasty.HUnit
import qualified Text.Pandoc.Class as P
import Text.Pandoc.MediaBag (MediaBag, mediaDirectory)
import Text.Pandoc.Options
import Text.Pandoc.Readers.EPUB
getMediaBag :: FilePath -> IO MediaBag
getMediaBag fp = do
bs <- BL.readFile fp
P.runIOorExplode $ do
readEPUB def bs
P.getMediaBag
testMediaBag :: FilePath -> [(String, String, Int)] -> IO ()
testMediaBag fp bag = do
actBag <- mediaDirectory <$> getMediaBag fp
assertBool (show "MediaBag did not match:\nExpected: "
++ show bag
++ "\nActual: "
++ show actBag)
(actBag == bag)
featuresBag :: [(String, String, Int)]
featuresBag = [("img/check.gif","image/gif",1340)
,("img/check.jpg","image/jpeg",2661)
,("img/check.png","image/png",2815)
,("img/multiscripts_and_greek_alphabet.png","image/png",10060)
]
tests :: [TestTree]
tests =
[ testGroup "EPUB Mediabag"
[ testCase "features bag"
(testMediaBag "epub/img.epub" featuresBag)
]
]