b35fae6511
* Require recent doctemplates. It is more flexible and supports partials. * Changed type of writerTemplate to Maybe Template instead of Maybe String. * Remove code from the LaTeX, Docbook, and JATS writers that looked in the template for strings to determine whether it is a book or an article, or whether csquotes is used. This was always kludgy and unreliable. To use csquotes for LaTeX, set `csquotes` in your variables or metadata. It is no longer sufficient to put `\usepackage{csquotes}` in your template or header includes. To specify a book style, use the `documentclass` variable or `--top-level-division`. * Change template code to use new API for doctemplates.
24 lines
689 B
Haskell
24 lines
689 B
Haskell
{-# LANGUAGE NoImplicitPrelude #-}
|
|
module Tests.Writers.Native (tests) where
|
|
|
|
import Prelude
|
|
import Data.Text (unpack)
|
|
import Test.Tasty
|
|
import Test.Tasty.QuickCheck
|
|
import Tests.Helpers
|
|
import Text.Pandoc
|
|
import Text.Pandoc.Arbitrary ()
|
|
|
|
p_write_rt :: Pandoc -> Bool
|
|
p_write_rt d =
|
|
read (unpack $ purely (writeNative def{ writerTemplate = Just mempty }) d) == d
|
|
|
|
p_write_blocks_rt :: [Block] -> Bool
|
|
p_write_blocks_rt bs =
|
|
read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs
|
|
|
|
tests :: [TestTree]
|
|
tests = [ testProperty "p_write_rt" p_write_rt
|
|
, testProperty "p_write_blocks_rt" $ mapSize
|
|
(\x -> if x > 3 then 3 else x) p_write_blocks_rt
|
|
]
|