{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.FB2 (tests) where import Prelude import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder fb2 :: String -> String fb2 x = "\n" ++ "unrecognisedpandoc<p />
" ++ x ++ "
" infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> TestTree (=:) = test (purely (writeFB2 def) . toPandoc) tests :: [TestTree] tests = [ testGroup "block elements" ["para" =: para "Lorem ipsum cetera." =?> fb2 "

Lorem ipsum cetera.

" ] , testGroup "inlines" [ "Emphasis" =: para (emph "emphasized") =?> fb2 "

emphasized

" ] , "bullet list" =: bulletList [ plain $ text "first" , plain $ text "second" , plain $ text "third" ] =?> fb2 "

\x2022 first

\x2022 second

\x2022 third

" ]