From 006e5231e526b3b1e9d06644bd1d2de9d5decb1e Mon Sep 17 00:00:00 2001 From: Griffin Smith Date: Sat, 12 Jun 2021 14:57:30 -0400 Subject: refactor(xanthous): Generators -> Generators.Level I'm going to start adding generators for things like text soon, so it makes sense to specifically sequester level generators as their own thing Change-Id: I175025375204fab7d75eba67dd06dab9bd2939d3 Reviewed-on: https://cl.tvl.fyi/c/depot/+/3201 Reviewed-by: grfn Tested-by: BuildkiteCI --- .../test/Xanthous/Generators/Level/UtilSpec.hs | 84 ++++++++++++++++++++++ .../xanthous/test/Xanthous/Generators/UtilSpec.hs | 84 ---------------------- 2 files changed, 84 insertions(+), 84 deletions(-) create mode 100644 users/grfn/xanthous/test/Xanthous/Generators/Level/UtilSpec.hs delete mode 100644 users/grfn/xanthous/test/Xanthous/Generators/UtilSpec.hs (limited to 'users/grfn/xanthous/test/Xanthous') diff --git a/users/grfn/xanthous/test/Xanthous/Generators/Level/UtilSpec.hs b/users/grfn/xanthous/test/Xanthous/Generators/Level/UtilSpec.hs new file mode 100644 index 0000000000..2d70a55e88 --- /dev/null +++ b/users/grfn/xanthous/test/Xanthous/Generators/Level/UtilSpec.hs @@ -0,0 +1,84 @@ +{-# LANGUAGE PackageImports #-} +-------------------------------------------------------------------------------- +module Xanthous.Generators.Level.UtilSpec (main, test) where +-------------------------------------------------------------------------------- +import Test.Prelude +import System.Random (mkStdGen) +import Control.Monad.Random (runRandT) +import Data.Array.ST (STUArray, runSTUArray, thaw) +import Data.Array.IArray (bounds) +import Data.Array.MArray (newArray, readArray, writeArray) +import Data.Array (Array, range, listArray, Ix) +import Control.Monad.ST (ST, runST) +import "checkers" Test.QuickCheck.Instances.Array () +import Linear.V2 +-------------------------------------------------------------------------------- +import Xanthous.Util +import Xanthous.Data (width, height) +import Xanthous.Generators.Level.Util +-------------------------------------------------------------------------------- + +main :: IO () +main = defaultMain test + +-------------------------------------------------------------------------------- + +newtype GenArray a b = GenArray (Array a b) + deriving stock (Show, Eq) + +instance (Ix a, Arbitrary a, CoArbitrary a, Arbitrary b) + => Arbitrary (GenArray a b) where + arbitrary = GenArray <$> do + (mkElem :: a -> b) <- arbitrary + minDims <- arbitrary + maxDims <- arbitrary + let bnds = (minDims, maxDims) + pure $ listArray bnds $ mkElem <$> range bnds + +test :: TestTree +test = testGroup "Xanthous.Generators.Util" + [ testGroup "randInitialize" + [ testProperty "returns an array of the correct dimensions" + $ \dims seed aliveChance -> + let gen = mkStdGen seed + res = runSTUArray + $ fmap fst + $ flip runRandT gen + $ randInitialize dims aliveChance + in bounds res === (0, V2 (dims ^. width) (dims ^. height)) + ] + , testGroup "numAliveNeighborsM" + [ testProperty "maxes out at 8" + $ \(GenArray (arr :: Array (V2 Word) Bool)) loc -> + let + act :: forall s. ST s Word + act = do + mArr <- thaw @_ @_ @_ @(STUArray s) arr + numAliveNeighborsM mArr loc + res = runST act + in counterexample (show res) $ between 0 8 res + ] + , testGroup "numAliveNeighbors" + [ testProperty "is equivalient to runST . numAliveNeighborsM . thaw" $ + \(GenArray (arr :: Array (V2 Word) Bool)) loc -> + let + act :: forall s. ST s Word + act = do + mArr <- thaw @_ @_ @_ @(STUArray s) arr + numAliveNeighborsM mArr loc + res = runST act + in numAliveNeighbors arr loc === res + ] + , testGroup "cloneMArray" + [ testCase "clones the array" $ runST $ + let + go :: forall s. ST s Assertion + go = do + arr <- newArray @(STUArray s) (0 :: Int, 5) (1 :: Int) + arr' <- cloneMArray @_ @(STUArray s) arr + writeArray arr' 0 1234 + x <- readArray arr 0 + pure $ x @?= 1 + in go + ] + ] diff --git a/users/grfn/xanthous/test/Xanthous/Generators/UtilSpec.hs b/users/grfn/xanthous/test/Xanthous/Generators/UtilSpec.hs deleted file mode 100644 index cdfadc06f5..0000000000 --- a/users/grfn/xanthous/test/Xanthous/Generators/UtilSpec.hs +++ /dev/null @@ -1,84 +0,0 @@ -{-# LANGUAGE PackageImports #-} --------------------------------------------------------------------------------- -module Xanthous.Generators.UtilSpec (main, test) where --------------------------------------------------------------------------------- -import Test.Prelude -import System.Random (mkStdGen) -import Control.Monad.Random (runRandT) -import Data.Array.ST (STUArray, runSTUArray, thaw) -import Data.Array.IArray (bounds) -import Data.Array.MArray (newArray, readArray, writeArray) -import Data.Array (Array, range, listArray, Ix) -import Control.Monad.ST (ST, runST) -import "checkers" Test.QuickCheck.Instances.Array () -import Linear.V2 --------------------------------------------------------------------------------- -import Xanthous.Util -import Xanthous.Data (width, height) -import Xanthous.Generators.Util --------------------------------------------------------------------------------- - -main :: IO () -main = defaultMain test - --------------------------------------------------------------------------------- - -newtype GenArray a b = GenArray (Array a b) - deriving stock (Show, Eq) - -instance (Ix a, Arbitrary a, CoArbitrary a, Arbitrary b) - => Arbitrary (GenArray a b) where - arbitrary = GenArray <$> do - (mkElem :: a -> b) <- arbitrary - minDims <- arbitrary - maxDims <- arbitrary - let bnds = (minDims, maxDims) - pure $ listArray bnds $ mkElem <$> range bnds - -test :: TestTree -test = testGroup "Xanthous.Generators.Util" - [ testGroup "randInitialize" - [ testProperty "returns an array of the correct dimensions" - $ \dims seed aliveChance -> - let gen = mkStdGen seed - res = runSTUArray - $ fmap fst - $ flip runRandT gen - $ randInitialize dims aliveChance - in bounds res === (0, V2 (dims ^. width) (dims ^. height)) - ] - , testGroup "numAliveNeighborsM" - [ testProperty "maxes out at 8" - $ \(GenArray (arr :: Array (V2 Word) Bool)) loc -> - let - act :: forall s. ST s Word - act = do - mArr <- thaw @_ @_ @_ @(STUArray s) arr - numAliveNeighborsM mArr loc - res = runST act - in counterexample (show res) $ between 0 8 res - ] - , testGroup "numAliveNeighbors" - [ testProperty "is equivalient to runST . numAliveNeighborsM . thaw" $ - \(GenArray (arr :: Array (V2 Word) Bool)) loc -> - let - act :: forall s. ST s Word - act = do - mArr <- thaw @_ @_ @_ @(STUArray s) arr - numAliveNeighborsM mArr loc - res = runST act - in numAliveNeighbors arr loc === res - ] - , testGroup "cloneMArray" - [ testCase "clones the array" $ runST $ - let - go :: forall s. ST s Assertion - go = do - arr <- newArray @(STUArray s) (0 :: Int, 5) (1 :: Int) - arr' <- cloneMArray @_ @(STUArray s) arr - writeArray arr' 0 1234 - x <- readArray arr 0 - pure $ x @?= 1 - in go - ] - ] -- cgit 1.4.1