feat[tests]: Use tasty for hierarchical tests

This commit is contained in:
vegowotenks 2025-08-14 10:45:08 +02:00
parent 0d8470a87f
commit 766528677f
4 changed files with 25 additions and 9 deletions

View file

@ -2,7 +2,7 @@
{-# LANGUAGE TemplateHaskell #-} -- for 'quickCheckAll'
{-# OPTIONS_GHC -Wno-all-missed-specialisations #-} -- a lot of warnings for unspecialized 'read' and 'show', which I cannot specialize
-- I wouldn't know how at least, they're not my datatypes, I cannot use the hint and add an 'INLINABLE' pragma
module Test.Data.Map.Implicit (prop_readShowIdentityRoundtrip, prop_readShowMaybeRoundtrip, runTests) where
module Test.Data.Map.Implicit (testGroup) where
import Test.QuickCheck.Roundtrip (roundtrips)
import Text.Show (show)
import Text.Read (read)
@ -10,10 +10,12 @@ import Data.Map.Implicit (ImplicitMap)
import Data.Bool (Bool)
import Language.Scalie.Ast.Definition (Definition)
import Data.Functor.Identity (Identity)
import Test.QuickCheck.All (quickCheckAll)
import System.IO (IO)
import Test.QuickCheck (Property, allProperties)
import Data.String (String)
import Control.Applicative (pure)
import Data.Maybe (Maybe)
import Test.Tasty.QuickCheck qualified as Tasty.QuickCheck
import Test.Tasty (TestTree)
-- | This is testworthy since I have somehow hand-hacked the read/show de/serialization of 'ImplicitMap'
@ -24,5 +26,8 @@ prop_readShowMaybeRoundtrip :: ImplicitMap (Definition Maybe) -> Bool
prop_readShowMaybeRoundtrip = roundtrips read show
pure []
runTests :: IO Bool
runTests = $quickCheckAll
allTests :: [(String, Property)]
allTests = $allProperties
testGroup :: TestTree
testGroup = Tasty.QuickCheck.testProperties "Data.Map.Implicit" allTests