aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Readers/FB2.hs
blob: 71443176d448e729222379836404ec8f832b4df9 (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
{-# LANGUAGE NoImplicitPrelude #-}
{- |
   Module      : Tests.Readers.FB2
   Copyright   : © 2018-2019 Alexander Krotov
   License     : GNU GPL, version 2 or above

   Maintainer  : © 2018-2019 Alexander Krotov <ilabdsf@gmail.com>
   Stability   : alpha
   Portability : portable

Tests for the EPUB mediabag.
-}
module Tests.Readers.FB2 (tests) where

import Prelude
import Test.Tasty
import Tests.Helpers
import Test.Tasty.Golden (goldenVsString)
import qualified Data.ByteString as BS
import Text.Pandoc
import Text.Pandoc.UTF8 (toText, fromTextLazy)
import Data.Text (Text)
import Data.Text.Lazy (fromStrict)
import System.FilePath (replaceExtension)

fb2ToNative :: Text -> Text
fb2ToNative = purely (writeNative def{ writerTemplate = Just "" }) . purely (readFB2 def)

fb2Test :: TestName -> FilePath -> TestTree
fb2Test name path = goldenVsString name native (fromTextLazy . fromStrict . fb2ToNative . toText <$> BS.readFile path)
  where native = replaceExtension path ".native"

tests :: [TestTree]
tests = [ fb2Test "Emphasis" "fb2/reader/emphasis.fb2"
        , fb2Test "Titles" "fb2/reader/titles.fb2"
        , fb2Test "Epigraph" "fb2/reader/epigraph.fb2"
        , fb2Test "Poem" "fb2/reader/poem.fb2"
        , fb2Test "Meta" "fb2/reader/meta.fb2"
        ]