about summary refs log tree commit diff
path: root/users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs
diff options
context:
space:
mode:
Diffstat (limited to 'users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs')
-rw-r--r--users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs23
1 files changed, 15 insertions, 8 deletions
diff --git a/users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs b/users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs
index c82c385987..cdfadc06f5 100644
--- a/users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs
+++ b/users/glittershark/xanthous/test/Xanthous/Generators/UtilSpec.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE PackageImports #-}
-
+--------------------------------------------------------------------------------
 module Xanthous.Generators.UtilSpec (main, test) where
-
+--------------------------------------------------------------------------------
 import Test.Prelude
 import System.Random (mkStdGen)
 import Control.Monad.Random (runRandT)
@@ -11,18 +11,23 @@ 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
+instance (Ix a, Arbitrary a, CoArbitrary a, Arbitrary b)
+       => Arbitrary (GenArray a b) where
   arbitrary = GenArray <$> do
     (mkElem :: a -> b) <- arbitrary
     minDims <- arbitrary
@@ -33,16 +38,18 @@ instance (Ix a, Arbitrary a, CoArbitrary a, Arbitrary b) => Arbitrary (GenArray
 test :: TestTree
 test = testGroup "Xanthous.Generators.Util"
   [ testGroup "randInitialize"
-    [ testProperty "returns an array of the correct dimensions" $ \dims seed aliveChance ->
+    [ 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, 0), (dims ^. width, dims ^. height))
+        in bounds res === (0, V2 (dims ^. width) (dims ^. height))
     ]
   , testGroup "numAliveNeighborsM"
-    [ testProperty "maxes out at 8" $ \(GenArray (arr :: Array (Word, Word) Bool)) loc ->
+    [ testProperty "maxes out at 8"
+      $ \(GenArray (arr :: Array (V2 Word) Bool)) loc ->
         let
           act :: forall s. ST s Word
           act = do
@@ -53,7 +60,7 @@ test = testGroup "Xanthous.Generators.Util"
     ]
   , testGroup "numAliveNeighbors"
     [ testProperty "is equivalient to runST . numAliveNeighborsM . thaw" $
-      \(GenArray (arr :: Array (Word, Word) Bool)) loc ->
+      \(GenArray (arr :: Array (V2 Word) Bool)) loc ->
         let
           act :: forall s. ST s Word
           act = do