{-# OPTIONS_GHC -fno-warn-orphans #-} module Data.PCGen.Tests ( pcgenTests ) where -- base import Data.Word -- hspec import Test.Hspec import Test.QuickCheck -- random import System.Random -- pcgen import Data.PCGen -- | This is an Orphan Instance, but that's totally alright pal, because we're -- only using this during a testing suite. instance Arbitrary PCGen where arbitrary = do w1 <- arbitrary return (mkPCGen (w1 :: Word)) propGenRange :: (RandomGen g) => g -> g -> Bool propGenRange = \rgenA rgenB -> genRange rgenA == genRange rgenB propNextInRange :: (RandomGen g) => g -> Bool propNextInRange = \randomGen -> let (i,g) = next randomGen (low, high) = genRange g in i >= low && i <= high propSplit :: (RandomGen g, Eq g) => g -> Bool propSplit = \randomGen -> let (genL, genR) = split randomGen in (genL /= randomGen) && (genR /= randomGen) && (genL /= genR) oddInc :: PCGen -> Bool oddInc gen = odd $ (read $ last $ words $ show $ gen :: Word64) pcgenTests :: Spec pcgenTests = describe "PCGen" $ do it "mkPCGen always results in an odd inc value" $ property $ \w -> oddInc $ mkPCGen (w::Word) it "mkPCGenDetailed always results in an odd inc value" $ property $ \w1 w2 -> oddInc $ mkPCGenDetailed w1 w2 it "genRange ignores the input generator given" $ property $ \genA genB -> propGenRange (genA::PCGen) (genB::PCGen) it "next is always within the bounds given by genRange" $ property $ \gen -> propNextInRange (gen::PCGen) it "split results are distinct from both the input and each other" $ property $ \gen -> propSplit (gen::PCGen) it "split results both have an odd inc value" $ property $ \gen -> let (a,b) = split (gen::PCGen) in oddInc a && oddInc b it "read.show == id" $ property $ \gen -> gen == (read (show (gen::PCGen)))