pandoc/test/Tests/Readers/FB2.hs

42 lines
1.3 KiB
Haskell
Raw Normal View History

2018-04-26 21:33:18 +02:00
{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Readers.FB2
Copyright : © 2018-2019 Alexander Krotov
License : GNU GPL, version 2 or above
2018-04-26 21:33:18 +02:00
Maintainer : © 2018-2019 Alexander Krotov <ilabdsf@gmail.com>
Stability : alpha
Portability : portable
Tests for the EPUB mediabag.
-}
2018-04-26 21:33:18 +02:00
module Tests.Readers.FB2 (tests) where
import Prelude
import Test.Tasty
import Tests.Helpers
import Test.Tasty.Golden (goldenVsString)
2018-04-26 21:33:18 +02:00
import qualified Data.ByteString as BS
import Text.Pandoc
import Text.Pandoc.UTF8 (toText, fromStringLazy)
import Data.Text (Text, unpack)
2018-04-26 21:33:18 +02:00
import System.FilePath (replaceExtension)
fb2ToNative :: Text -> Text
fb2ToNative = purely (writeNative def{ writerTemplate = Just mempty }) . purely (readFB2 def)
2018-04-26 21:33:18 +02:00
fb2Test :: TestName -> FilePath -> TestTree
fb2Test name path = goldenVsString name native
(fromStringLazy . filter (/='\r') . unpack . fb2ToNative . toText
<$> BS.readFile path)
2018-04-26 21:33:18 +02:00
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"
2019-05-11 12:35:03 +02:00
, fb2Test "Notes" "fb2/reader/notes.fb2"
2018-04-26 21:33:18 +02:00
]