scalie/test/Test/Data/Map/Implicit.hs

37 lines
1.7 KiB
Haskell

{-# LANGUAGE Unsafe #-} -- unsafe: I am using TemplateHaskell from a dependency
{-# 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 (testGroup) where
import Test.QuickCheck.Roundtrip (roundtrips)
import Text.Show (show)
import Text.Read (read)
import Data.Map.Implicit (ImplicitMap)
import Data.Bool (Bool)
import Language.Scalie.Core.Definition (Definition)
import Data.Functor.Identity (Identity)
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)
import Test.Tasty.QuickCheck (QuickCheckMaxSize(QuickCheckMaxSize))
import Data.Function (($))
import Test.Tasty qualified as Tasty
-- | This is testworthy since I have somehow hand-hacked the read/show de/serialization of 'ImplicitMap'
prop_readShowIdentityRoundtrip :: ImplicitMap (Definition Identity) -> Bool
prop_readShowIdentityRoundtrip = roundtrips read show
prop_readShowMaybeRoundtrip :: ImplicitMap (Definition Maybe) -> Bool
prop_readShowMaybeRoundtrip = roundtrips read show
pure []
allTests :: [(String, Property)]
allTests = $allProperties
testGroup :: TestTree
testGroup = Tasty.localOption (QuickCheckMaxSize 25) -- it is necessary to restrain the size because the generated core would get veeeeeery big otherwise
$ Tasty.QuickCheck.testProperties "Data.Map.Implicit" allTests