pandoc/test/Tests/Readers/FB2.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

39 lines
1.2 KiB
Haskell

{-# 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"
]