aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Gen.hs3
-rw-r--r--test/Tests/C.hs14
-rw-r--r--test/Util.hs1
3 files changed, 8 insertions, 10 deletions
diff --git a/test/Gen.hs b/test/Gen.hs
index 244c735..8099f0d 100644
--- a/test/Gen.hs
+++ b/test/Gen.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE NumericUnderscores #-}
-{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeAbstractions #-}
@@ -49,7 +48,7 @@ genLowBiased (lo, hi) = do
return (lo + x * x * x * (hi - lo))
shuffleShR :: IShR n -> Gen (IShR n)
-shuffleShR = \sh -> go (length (toList sh)) (toList sh) sh
+shuffleShR = \sh -> go (length sh) (toList sh) sh
where
go :: Int -> [Int] -> IShR n -> Gen (IShR n)
go _ _ ZSR = return ZSR
diff --git a/test/Tests/C.hs b/test/Tests/C.hs
index b10e66a..1480491 100644
--- a/test/Tests/C.hs
+++ b/test/Tests/C.hs
@@ -45,7 +45,7 @@ prop_sum_nonempty = property $ genRank $ \outrank@(SNat @n) -> do
let inrank = SNat @(n + 1)
sh <- forAll $ genShR inrank
-- traceM ("sh: " ++ show sh ++ " -> " ++ show (product sh))
- guard (all (> 0) (toList (shrTail sh))) -- only constrain the tail
+ guard (all (> 0) (shrTail sh)) -- only constrain the tail
arr <- forAllT $ OR.fromVector @Double @(n + 1) (toList sh) <$>
genStorables (Range.singleton (product sh))
(\w -> fromIntegral w / fromIntegral (maxBound :: Word64))
@@ -62,7 +62,7 @@ prop_sum_empty = property $ genRank $ \outrankm1@(SNat @nm1) -> do
sht <- shuffleShR (0 :$: shtt) -- n
n <- Gen.int (Range.linear 0 20)
return (n :$: sht) -- n + 1
- guard (any (== 0) (toList (shrTail sh)))
+ guard (elem 0 (toList (shrTail sh)))
-- traceM ("sh: " ++ show sh ++ " -> " ++ show (product sh))
let arr = OR.fromList @(n + 1) @Double (toList sh) []
let rarr = rfromOrthotope inrank arr
@@ -72,7 +72,7 @@ prop_sum_lasteq1 :: Property
prop_sum_lasteq1 = property $ genRank $ \outrank@(SNat @n) -> do
let inrank = SNat @(n + 1)
outsh <- forAll $ genShR outrank
- guard (all (> 0) (toList outsh))
+ guard (all (> 0) outsh)
let insh = shrAppend outsh (1 :$: ZSR)
arr <- forAllT $ OR.fromVector @Double @(n + 1) (toList insh) <$>
genStorables (Range.singleton (product insh))
@@ -89,7 +89,7 @@ prop_sum_replicated doTranspose = property $
LTI -> return Refl -- actually we only continue if m < n
_ -> discard
(sh1, sh2, sh3) <- forAll $ genReplicatedShR inrank1 inrank2
- guard (all (> 0) (toList sh3))
+ guard (all (> 0) sh3)
arr <- forAllT $
OR.stretch (toList sh3)
. OR.reshape (toList sh2)
@@ -111,7 +111,7 @@ prop_negate_with :: forall f b. Show b
prop_negate_with genRank' genB preproc = property $
genRank' $ \extra rank@(SNat @n) -> do
sh <- forAll $ genShR rank
- guard (all (> 0) (toList sh))
+ guard (all (> 0) sh)
arr <- forAllT $ OR.fromVector @Double @n (toList sh) <$>
genStorables (Range.singleton (product sh))
(\w -> fromIntegral w / fromIntegral (maxBound :: Word64))
@@ -140,7 +140,7 @@ tests = testGroup "C"
(\Refl (n :$: _) -> do lo <- Gen.integral (Range.constant 0 (n-1))
len <- Gen.integral (Range.constant 0 (n-lo))
return [(lo, len)])
- (\_ -> OR.slice)
+ (const OR.slice)
,testProperty "slice nD" $ prop_negate_with
(\k -> genRank (k (Const ())))
(\_ sh -> do let genPair n = do lo <- Gen.integral (Range.constant 0 (n-1))
@@ -148,6 +148,6 @@ tests = testGroup "C"
return (lo, len)
pairs <- mapM genPair (toList sh)
return pairs)
- (\_ -> OR.slice)
+ (const OR.slice)
]
]
diff --git a/test/Util.hs b/test/Util.hs
index 0273423..7c06b2f 100644
--- a/test/Util.hs
+++ b/test/Util.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-}
-{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}