Add tests for idempotency of makeSections.

See #7950.
This commit is contained in:
John MacFarlane 2022-03-08 09:53:57 -08:00
parent 0adfc6e58e
commit 82d9f5eb8b

View file

@ -15,6 +15,7 @@ module Tests.Shared (tests) where
import System.FilePath.Posix (joinPath) import System.FilePath.Posix (joinPath)
import Test.Tasty import Test.Tasty
import Text.Pandoc.Arbitrary () import Text.Pandoc.Arbitrary ()
import Test.Tasty.QuickCheck (testProperty)
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Test.Tasty.HUnit import Test.Tasty.HUnit
@ -33,7 +34,21 @@ tests = [ testGroup "compactifyDL"
, testGroup "collapseFilePath" testCollapse , testGroup "collapseFilePath" testCollapse
, testGroup "toLegacyTable" testLegacyTable , testGroup "toLegacyTable" testLegacyTable
, testGroup "table of contents" testTOC , testGroup "table of contents" testTOC
, testGroup "makeSections"
[ testProperty "makeSections is idempotent" makeSectionsIsIdempotent
, testCase "makeSections is idempotent for test case" $
let d = header 1 "H1" <> header 2 "H2" <> header 3 "H3" <>
header 2 "H2a" <> header 4 "H4" <> header 1 "H1a"
d' = makeSections False Nothing $ toList d
in assertBool "makeSections is idempotent for test case"
(makeSections False Nothing d' == d')
] ]
]
makeSectionsIsIdempotent :: [Block] -> Bool
makeSectionsIsIdempotent d =
let d' = makeSections False Nothing d
in d' == makeSections False Nothing d'
givesTOC :: String -> (Blocks, Blocks) -> TestTree givesTOC :: String -> (Blocks, Blocks) -> TestTree
givesTOC desc (blocks, toc) = test (toTableOfContents def) desc (toList blocks, head . toList $ toc) givesTOC desc (blocks, toc) = test (toTableOfContents def) desc (toList blocks, head . toList $ toc)