{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Test.Massiv.Core.Index (
DimIx (..),
SzNE (..),
SzIx (..),
SzTiny (..),
ixToList,
arbitraryIx1,
toIx,
specIx1,
ixSpec,
ix2UpSpec,
ixNumSpec,
szNumSpec,
szSpec,
module Data.Massiv.Core.Index,
) where
import Control.DeepSeq
import Control.Exception (throw)
import Control.Monad
import Data.Foldable as F
import Data.Functor.Identity
import Data.IORef
import Data.Massiv.Array.Unsafe (Sz (SafeSz))
import Data.Massiv.Core.Index
import Data.Proxy
import Data.Typeable
import GHC.Exception (ErrorCall (ErrorCall))
import Test.Massiv.Utils
newtype DimIx ix = DimIx Dim deriving (Ix1 -> DimIx ix -> ShowS
[DimIx ix] -> ShowS
DimIx ix -> String
(Ix1 -> DimIx ix -> ShowS)
-> (DimIx ix -> String) -> ([DimIx ix] -> ShowS) -> Show (DimIx ix)
forall ix. Ix1 -> DimIx ix -> ShowS
forall ix. [DimIx ix] -> ShowS
forall ix. DimIx ix -> String
forall a.
(Ix1 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ix. Ix1 -> DimIx ix -> ShowS
showsPrec :: Ix1 -> DimIx ix -> ShowS
$cshow :: forall ix. DimIx ix -> String
show :: DimIx ix -> String
$cshowList :: forall ix. [DimIx ix] -> ShowS
showList :: [DimIx ix] -> ShowS
Show)
deriving instance Arbitrary Dim
newtype SzNE ix = SzNE
{ forall ix. SzNE ix -> Sz ix
unSzNE :: Sz ix
}
deriving (Ix1 -> SzNE ix -> ShowS
[SzNE ix] -> ShowS
SzNE ix -> String
(Ix1 -> SzNE ix -> ShowS)
-> (SzNE ix -> String) -> ([SzNE ix] -> ShowS) -> Show (SzNE ix)
forall ix. Index ix => Ix1 -> SzNE ix -> ShowS
forall ix. Index ix => [SzNE ix] -> ShowS
forall ix. Index ix => SzNE ix -> String
forall a.
(Ix1 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ix. Index ix => Ix1 -> SzNE ix -> ShowS
showsPrec :: Ix1 -> SzNE ix -> ShowS
$cshow :: forall ix. Index ix => SzNE ix -> String
show :: SzNE ix -> String
$cshowList :: forall ix. Index ix => [SzNE ix] -> ShowS
showList :: [SzNE ix] -> ShowS
Show)
data SzIx ix = SzIx (Sz ix) ix deriving (Ix1 -> SzIx ix -> ShowS
[SzIx ix] -> ShowS
SzIx ix -> String
(Ix1 -> SzIx ix -> ShowS)
-> (SzIx ix -> String) -> ([SzIx ix] -> ShowS) -> Show (SzIx ix)
forall ix. Index ix => Ix1 -> SzIx ix -> ShowS
forall ix. Index ix => [SzIx ix] -> ShowS
forall ix. Index ix => SzIx ix -> String
forall a.
(Ix1 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ix. Index ix => Ix1 -> SzIx ix -> ShowS
showsPrec :: Ix1 -> SzIx ix -> ShowS
$cshow :: forall ix. Index ix => SzIx ix -> String
show :: SzIx ix -> String
$cshowList :: forall ix. Index ix => [SzIx ix] -> ShowS
showList :: [SzIx ix] -> ShowS
Show)
instance (Index ix, Arbitrary ix) => Arbitrary (Sz ix) where
arbitrary :: Gen (Sz ix)
arbitrary = do
Sz ix
sz <- ix -> Sz ix
forall ix. Index ix => ix -> Sz ix
Sz (ix -> Sz ix) -> (ix -> ix) -> ix -> Sz ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex Ix1 -> Ix1
forall a. Num a => a -> a
abs (ix -> Sz ix) -> Gen ix -> Gen (Sz ix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ix
forall a. Arbitrary a => Gen a
arbitrary
if Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
> Ix1
50000
then Gen (Sz ix)
forall a. Arbitrary a => Gen a
arbitrary
else Sz ix -> Gen (Sz ix)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return Sz ix
sz
instance (Index ix, Arbitrary ix) => Arbitrary (SzNE ix) where
arbitrary :: Gen (SzNE ix)
arbitrary = Sz ix -> SzNE ix
forall ix. Sz ix -> SzNE ix
SzNE (Sz ix -> SzNE ix) -> (Sz ix -> Sz ix) -> Sz ix -> SzNE ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ix -> Sz ix
forall ix. Index ix => ix -> Sz ix
Sz (ix -> Sz ix) -> (Sz ix -> ix) -> Sz ix -> Sz ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
1) (ix -> ix) -> (Sz ix -> ix) -> Sz ix -> ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sz ix -> ix
forall ix. Sz ix -> ix
unSz (Sz ix -> SzNE ix) -> Gen (Sz ix) -> Gen (SzNE ix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Sz ix)
forall a. Arbitrary a => Gen a
arbitrary
instance (Index ix, Arbitrary ix) => Arbitrary (Stride ix) where
arbitrary :: Gen (Stride ix)
arbitrary = do
Positive (Small Ix1
x) <- Gen (Positive (Small Ix1))
forall a. Arbitrary a => Gen a
arbitrary
ix -> Stride ix
forall ix. Index ix => ix -> Stride ix
Stride (ix -> Stride ix) -> (ix -> ix) -> ix -> Stride ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex ((Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
1) (Ix1 -> Ix1) -> (Ix1 -> Ix1) -> Ix1 -> Ix1
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ix1 -> Ix1 -> Ix1
forall a. Integral a => a -> a -> a
`mod` Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
min Ix1
6 Ix1
x)) (ix -> Stride ix) -> Gen ix -> Gen (Stride ix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ix
forall a. Arbitrary a => Gen a
arbitrary
instance (Index ix, Arbitrary ix) => Arbitrary (SzIx ix) where
arbitrary :: Gen (SzIx ix)
arbitrary = do
SzNE Sz ix
sz <- Gen (SzNE ix)
forall a. Arbitrary a => Gen a
arbitrary
Sz ix -> ix -> SzIx ix
forall ix. Sz ix -> ix -> SzIx ix
SzIx Sz ix
sz (ix -> SzIx ix) -> (ix -> ix) -> ix -> SzIx ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ix -> ix -> ix) -> ix -> ix -> ix
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
liftIndex2 Ix1 -> Ix1 -> Ix1
forall a. Integral a => a -> a -> a
mod) (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz) (ix -> SzIx ix) -> Gen ix -> Gen (SzIx ix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ix
forall a. Arbitrary a => Gen a
arbitrary
newtype SzTiny ix = SzTiny {forall ix. SzTiny ix -> Sz ix
unSzTiny :: Sz ix}
deriving (Ix1 -> SzTiny ix -> ShowS
[SzTiny ix] -> ShowS
SzTiny ix -> String
(Ix1 -> SzTiny ix -> ShowS)
-> (SzTiny ix -> String)
-> ([SzTiny ix] -> ShowS)
-> Show (SzTiny ix)
forall ix. Index ix => Ix1 -> SzTiny ix -> ShowS
forall ix. Index ix => [SzTiny ix] -> ShowS
forall ix. Index ix => SzTiny ix -> String
forall a.
(Ix1 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall ix. Index ix => Ix1 -> SzTiny ix -> ShowS
showsPrec :: Ix1 -> SzTiny ix -> ShowS
$cshow :: forall ix. Index ix => SzTiny ix -> String
show :: SzTiny ix -> String
$cshowList :: forall ix. Index ix => [SzTiny ix] -> ShowS
showList :: [SzTiny ix] -> ShowS
Show, SzTiny ix -> SzTiny ix -> Bool
(SzTiny ix -> SzTiny ix -> Bool)
-> (SzTiny ix -> SzTiny ix -> Bool) -> Eq (SzTiny ix)
forall ix. Eq ix => SzTiny ix -> SzTiny ix -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall ix. Eq ix => SzTiny ix -> SzTiny ix -> Bool
== :: SzTiny ix -> SzTiny ix -> Bool
$c/= :: forall ix. Eq ix => SzTiny ix -> SzTiny ix -> Bool
/= :: SzTiny ix -> SzTiny ix -> Bool
Eq)
instance (Arbitrary ix, Index ix) => Arbitrary (SzTiny ix) where
arbitrary :: Gen (SzTiny ix)
arbitrary = Sz ix -> SzTiny ix
forall ix. Sz ix -> SzTiny ix
SzTiny (Sz ix -> SzTiny ix) -> (Sz ix -> Sz ix) -> Sz ix -> SzTiny ix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ix1 -> Ix1) -> Sz ix -> Sz ix
forall ix. Index ix => (Ix1 -> Ix1) -> Sz ix -> Sz ix
liftSz (Ix1 -> Ix1 -> Ix1
forall a. Integral a => a -> a -> a
`mod` Ix1
10) (Sz ix -> SzTiny ix) -> Gen (Sz ix) -> Gen (SzTiny ix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Sz ix)
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary e => Arbitrary (Border e) where
arbitrary :: Gen (Border e)
arbitrary =
[Gen (Border e)] -> Gen (Border e)
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ e -> Border e
forall e. e -> Border e
Fill (e -> Border e) -> Gen e -> Gen (Border e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen e
forall a. Arbitrary a => Gen a
arbitrary
, Border e -> Gen (Border e)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return Border e
forall e. Border e
Wrap
, Border e -> Gen (Border e)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return Border e
forall e. Border e
Edge
, Border e -> Gen (Border e)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return Border e
forall e. Border e
Reflect
, Border e -> Gen (Border e)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return Border e
forall e. Border e
Continue
]
instance Index ix => Arbitrary (DimIx ix) where
arbitrary :: Gen (DimIx ix)
arbitrary = do
Ix1
n <- Gen Ix1
forall a. Arbitrary a => Gen a
arbitrary
DimIx ix -> Gen (DimIx ix)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (DimIx ix -> Gen (DimIx ix)) -> DimIx ix -> Gen (DimIx ix)
forall a b. (a -> b) -> a -> b
$ Dim -> DimIx ix
forall ix. Dim -> DimIx ix
DimIx (Dim
1 Dim -> Dim -> Dim
forall a. Num a => a -> a -> a
+ (Ix1 -> Dim
Dim Ix1
n Dim -> Dim -> Dim
forall a. Integral a => a -> a -> a
`mod` Proxy ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (Proxy ix
forall {k} (t :: k). Proxy t
Proxy :: Proxy ix)))
arbitraryIx1 :: Gen Int
arbitraryIx1 :: Gen Ix1
arbitraryIx1 = (Ix1 -> Gen Ix1) -> Gen Ix1
forall a. (Ix1 -> Gen a) -> Gen a
sized (\Ix1
s -> Ix1 -> Gen Ix1 -> Gen Ix1
forall a. HasCallStack => Ix1 -> Gen a -> Gen a
resize (Double -> Ix1
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double -> Ix1) -> Double -> Ix1
forall a b. (a -> b) -> a -> b
$ (Double -> Double
forall a. Floating a => a -> a
sqrt :: Double -> Double) (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Ix1 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Ix1
s) Gen Ix1
forall a. Arbitrary a => Gen a
arbitrary)
ixToList :: Index ix => ix -> [Int]
ixToList :: forall ix. Index ix => ix -> [Ix1]
ixToList = [Ix1] -> [Ix1]
forall a. [a] -> [a]
reverse ([Ix1] -> [Ix1]) -> (ix -> [Ix1]) -> ix -> [Ix1]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Ix1] -> Ix1 -> [Ix1]) -> [Ix1] -> ix -> [Ix1]
forall ix a. Index ix => (a -> Ix1 -> a) -> a -> ix -> a
forall a. (a -> Ix1 -> a) -> a -> ix -> a
foldlIndex ((Ix1 -> [Ix1] -> [Ix1]) -> [Ix1] -> Ix1 -> [Ix1]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:)) []
toIx
:: forall ix' ix
. (Dimensions ix' ~ Dimensions ix, Index ix', Index ix)
=> ix
-> ix'
toIx :: forall ix' ix.
(Dimensions ix' ~ Dimensions ix, Index ix', Index ix) =>
ix -> ix'
toIx ix
ix = (ix' -> Dim -> ix') -> ix' -> [Dim] -> ix'
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' ix' -> Dim -> ix'
setEachIndex ix'
forall ix. Index ix => ix
zeroIndex [Dim
1 .. Sz ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Sz ix
forall ix. Index ix => ix -> Sz ix
Sz ix
ix)]
where
setEachIndex :: ix' -> Dim -> ix'
setEachIndex ix'
ix' Dim
d = ix' -> Dim -> Ix1 -> ix'
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Ix1 -> ix
setDim' ix'
ix' Dim
d (ix -> Dim -> Ix1
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Ix1
getDim' ix
ix Dim
d)
instance Arbitrary Ix0 where
arbitrary :: Gen Ix0
arbitrary = Ix0 -> Gen Ix0
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ix0
Ix0
instance Arbitrary Ix2 where
arbitrary :: Gen Ix2
arbitrary = Ix1 -> Ix1 -> Ix2
(:.) (Ix1 -> Ix1 -> Ix2) -> Gen Ix1 -> Gen (Ix1 -> Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Ix1
arbitraryIx1 Gen (Ix1 -> Ix2) -> Gen Ix1 -> Gen Ix2
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Ix1
arbitraryIx1
instance Arbitrary Ix3 where
arbitrary :: Gen Ix3
arbitrary = Ix1 -> Ix (3 - 1) -> Ix3
Ix1 -> Ix2 -> Ix3
forall (n :: Nat). Ix1 -> Ix (n - 1) -> IxN n
(:>) (Ix1 -> Ix2 -> Ix3) -> Gen Ix1 -> Gen (Ix2 -> Ix3)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Ix1
arbitraryIx1 Gen (Ix2 -> Ix3) -> Gen Ix2 -> Gen Ix3
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Ix1 -> Ix1 -> Ix2
(:.) (Ix1 -> Ix1 -> Ix2) -> Gen Ix1 -> Gen (Ix1 -> Ix2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Ix1
arbitraryIx1 Gen (Ix1 -> Ix2) -> Gen Ix1 -> Gen Ix2
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Ix1
arbitraryIx1)
instance Arbitrary Ix4 where
arbitrary :: Gen Ix4
arbitrary = Ix1 -> Ix (4 - 1) -> Ix4
Ix1 -> Ix3 -> Ix4
forall (n :: Nat). Ix1 -> Ix (n - 1) -> IxN n
(:>) (Ix1 -> Ix3 -> Ix4) -> Gen Ix1 -> Gen (Ix3 -> Ix4)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Ix1
arbitraryIx1 Gen (Ix3 -> Ix4) -> Gen Ix3 -> Gen Ix4
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Ix3
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary Ix5 where
arbitrary :: Gen Ix5
arbitrary = Ix1 -> Ix (5 - 1) -> Ix5
Ix1 -> Ix4 -> Ix5
forall (n :: Nat). Ix1 -> Ix (n - 1) -> IxN n
(:>) (Ix1 -> Ix4 -> Ix5) -> Gen Ix1 -> Gen (Ix4 -> Ix5)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Ix1
arbitraryIx1 Gen (Ix4 -> Ix5) -> Gen Ix4 -> Gen Ix5
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Ix4
forall a. Arbitrary a => Gen a
arbitrary
instance CoArbitrary Ix2 where
coarbitrary :: forall b. Ix2 -> Gen b -> Gen b
coarbitrary (Ix1
i :. Ix1
j) = Ix1 -> Gen b -> Gen b
forall b. Ix1 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Ix1
i (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ix1 -> Gen b -> Gen b
forall b. Ix1 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Ix1
j
instance CoArbitrary Ix3 where
coarbitrary :: forall b. Ix3 -> Gen b -> Gen b
coarbitrary (Ix1
i :> Ix (3 - 1)
ix) = Ix1 -> Gen b -> Gen b
forall b. Ix1 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Ix1
i (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ix2 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Ix2 -> Gen b -> Gen b
coarbitrary Ix (3 - 1)
Ix2
ix
instance CoArbitrary Ix4 where
coarbitrary :: forall b. Ix4 -> Gen b -> Gen b
coarbitrary (Ix1
i :> Ix (4 - 1)
ix) = Ix1 -> Gen b -> Gen b
forall b. Ix1 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Ix1
i (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ix3 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Ix3 -> Gen b -> Gen b
coarbitrary Ix (4 - 1)
Ix3
ix
instance CoArbitrary Ix5 where
coarbitrary :: forall b. Ix5 -> Gen b -> Gen b
coarbitrary (Ix1
i :> Ix (5 - 1)
ix) = Ix1 -> Gen b -> Gen b
forall b. Ix1 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Ix1
i (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ix4 -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Ix4 -> Gen b -> Gen b
coarbitrary Ix (5 - 1)
Ix4
ix
instance Function Ix2 where
function :: forall b. (Ix2 -> b) -> Ix2 :-> b
function = (Ix2 -> Ix2T) -> (Ix2T -> Ix2) -> (Ix2 -> b) -> Ix2 :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Ix2 -> Ix2T
fromIx2 Ix2T -> Ix2
toIx2
instance Function Ix3 where
function :: forall b. (Ix3 -> b) -> Ix3 :-> b
function = (Ix3 -> Ix3T) -> (Ix3T -> Ix3) -> (Ix3 -> b) -> Ix3 :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Ix3 -> Ix3T
fromIx3 Ix3T -> Ix3
toIx3
instance Function Ix4 where
function :: forall b. (Ix4 -> b) -> Ix4 :-> b
function = (Ix4 -> Ix4T) -> (Ix4T -> Ix4) -> (Ix4 -> b) -> Ix4 :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Ix4 -> Ix4T
fromIx4 Ix4T -> Ix4
toIx4
instance Function Ix5 where
function :: forall b. (Ix5 -> b) -> Ix5 :-> b
function = (Ix5 -> Ix5T) -> (Ix5T -> Ix5) -> (Ix5 -> b) -> Ix5 :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Ix5 -> Ix5T
fromIx5 Ix5T -> Ix5
toIx5
prop_IsSafeIndex :: Index ix => SzIx ix -> Bool
prop_IsSafeIndex :: forall ix. Index ix => SzIx ix -> Bool
prop_IsSafeIndex (SzIx Sz ix
sz ix
ix) = Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
ix
prop_RepairSafeIx :: Index ix => SzIx ix -> Property
prop_RepairSafeIx :: forall ix. Index ix => SzIx ix -> Property
prop_RepairSafeIx (SzIx Sz ix
sz ix
ix) =
ix
ix ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Sz ix
-> ix -> (Sz Ix1 -> Ix1 -> Ix1) -> (Sz Ix1 -> Ix1 -> Ix1) -> ix
forall ix.
Index ix =>
Sz ix
-> ix -> (Sz Ix1 -> Ix1 -> Ix1) -> (Sz Ix1 -> Ix1 -> Ix1) -> ix
repairIndex Sz ix
sz ix
ix (String -> Sz Ix1 -> Ix1 -> Ix1
forall {a} {a} {a}. (Show a, Show a) => String -> a -> a -> a
errorImpossible String
"below zero") (String -> Sz Ix1 -> Ix1 -> Ix1
forall {a} {a} {a}. (Show a, Show a) => String -> a -> a -> a
errorImpossible String
"above zero")
where
errorImpossible :: String -> a -> a -> a
errorImpossible String
msg a
sz1 a
ix1 =
String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Impossible <" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
sz1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" and " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
ix1
prop_UnconsCons :: Index ix => ix -> Property
prop_UnconsCons :: forall ix. Index ix => ix -> Property
prop_UnconsCons ix
ix = ix
ix ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Ix1 -> Lower ix -> ix) -> (Ix1, Lower ix) -> ix
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Ix1 -> Lower ix -> ix
forall ix. Index ix => Ix1 -> Lower ix -> ix
consDim (ix -> (Ix1, Lower ix)
forall ix. Index ix => ix -> (Ix1, Lower ix)
unconsDim ix
ix)
prop_UnsnocSnoc :: Index ix => ix -> Property
prop_UnsnocSnoc :: forall ix. Index ix => ix -> Property
prop_UnsnocSnoc ix
ix = ix
ix ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Lower ix -> Ix1 -> ix) -> (Lower ix, Ix1) -> ix
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Lower ix -> Ix1 -> ix
forall ix. Index ix => Lower ix -> Ix1 -> ix
snocDim (ix -> (Lower ix, Ix1)
forall ix. Index ix => ix -> (Lower ix, Ix1)
unsnocDim ix
ix)
prop_ToFromLinearIndex :: Index ix => SzIx ix -> Property
prop_ToFromLinearIndex :: forall ix. Index ix => SzIx ix -> Property
prop_ToFromLinearIndex (SzIx Sz ix
sz ix
ix) =
Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
ix Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> ix
ix ix -> ix -> Bool
forall a. Eq a => a -> a -> Bool
== Sz ix -> Ix1 -> ix
forall ix. Index ix => Sz ix -> Ix1 -> ix
fromLinearIndex Sz ix
sz (Sz ix -> ix -> Ix1
forall ix. Index ix => Sz ix -> ix -> Ix1
toLinearIndex Sz ix
sz ix
ix)
prop_FromToLinearIndex :: Index ix => SzNE ix -> NonNegative Int -> Property
prop_FromToLinearIndex :: forall ix. Index ix => SzNE ix -> NonNegative Ix1 -> Property
prop_FromToLinearIndex (SzNE Sz ix
sz) (NonNegative Ix1
i) =
Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
>= Ix1
i Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> Ix1
i Ix1 -> Ix1 -> Bool
forall a. Eq a => a -> a -> Bool
== Sz ix -> ix -> Ix1
forall ix. Index ix => Sz ix -> ix -> Ix1
toLinearIndex Sz ix
sz (Sz ix -> Ix1 -> ix
forall ix. Index ix => Sz ix -> Ix1 -> ix
fromLinearIndex Sz ix
sz Ix1
i)
prop_CountElements :: Index ix => Int -> Sz ix -> Property
prop_CountElements :: forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_CountElements Ix1
thresh Sz ix
sz =
Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz
Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
thresh
Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz
Ix1 -> Ix1 -> Bool
forall a. Eq a => a -> a -> Bool
== ix
-> ix
-> ix
-> (Ix1 -> Ix1 -> Bool)
-> Ix1
-> (ix -> Ix1 -> Ix1)
-> Ix1
forall ix a.
Index ix =>
ix -> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> a) -> a
iter ix
forall ix. Index ix => ix
zeroIndex (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz) (Ix1 -> ix
forall ix. Index ix => Ix1 -> ix
pureIndex Ix1
1) Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(<) Ix1
0 ((Ix1 -> Ix1) -> ix -> Ix1 -> Ix1
forall a b. a -> b -> a
const (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
1))
prop_IterMonotonic :: Index ix => Int -> Sz ix -> Property
prop_IterMonotonic :: forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonic Ix1
thresh Sz ix
sz =
(Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
thresh)
Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (Bool, ix) -> Bool
forall a b. (a, b) -> a
fst (ix
-> ix
-> ix
-> (Ix1 -> Ix1 -> Bool)
-> (Bool, ix)
-> (ix -> (Bool, ix) -> (Bool, ix))
-> (Bool, ix)
forall ix a.
Index ix =>
ix -> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> a) -> a
iter ((Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex Ix1 -> Ix1
forall a. Enum a => a -> a
succ ix
forall ix. Index ix => ix
zeroIndex) (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz) (Ix1 -> ix
forall ix. Index ix => Ix1 -> ix
pureIndex Ix1
1) Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(<) (Bool
True, ix
forall ix. Index ix => ix
zeroIndex) ix -> (Bool, ix) -> (Bool, ix)
forall {b}. Ord b => b -> (Bool, b) -> (Bool, b)
mono)
where
mono :: b -> (Bool, b) -> (Bool, b)
mono b
curIx (Bool
prevMono, b
prevIx) =
let isMono :: Bool
isMono = Bool
prevMono Bool -> Bool -> Bool
&& b
prevIx b -> b -> Bool
forall a. Ord a => a -> a -> Bool
< b
curIx
in Bool
isMono Bool -> (Bool, b) -> (Bool, b)
forall a b. a -> b -> b
`seq` (Bool
isMono, b
curIx)
prop_IterMonotonicM :: Index ix => Int -> Sz ix -> Property
prop_IterMonotonicM :: forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonicM Ix1
thresh Sz ix
sz =
(Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
thresh)
Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (Bool, ix) -> Bool
forall a b. (a, b) -> a
fst
((Bool, ix) -> Bool) -> (Bool, ix) -> Bool
forall a b. (a -> b) -> a -> b
$ Identity (Bool, ix) -> (Bool, ix)
forall a. Identity a -> a
runIdentity
(Identity (Bool, ix) -> (Bool, ix))
-> Identity (Bool, ix) -> (Bool, ix)
forall a b. (a -> b) -> a -> b
$ ix
-> ix
-> ix
-> (Ix1 -> Ix1 -> Bool)
-> (Bool, ix)
-> (ix -> (Bool, ix) -> Identity (Bool, ix))
-> Identity (Bool, ix)
forall ix (m :: * -> *) a.
(Index ix, Monad m) =>
ix
-> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> m a) -> m a
forall (m :: * -> *) a.
Monad m =>
ix
-> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> m a) -> m a
iterM ((Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex Ix1 -> Ix1
forall a. Enum a => a -> a
succ ix
forall ix. Index ix => ix
zeroIndex) (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz) (Ix1 -> ix
forall ix. Index ix => Ix1 -> ix
pureIndex Ix1
1) Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(<) (Bool
True, ix
forall ix. Index ix => ix
zeroIndex) ix -> (Bool, ix) -> Identity (Bool, ix)
forall {b} {m :: * -> *}.
(Ord b, Monad m) =>
b -> (Bool, b) -> m (Bool, b)
mono
where
mono :: b -> (Bool, b) -> m (Bool, b)
mono b
curIx (Bool
prevMono, b
prevIx) =
let isMono :: Bool
isMono = Bool
prevMono Bool -> Bool -> Bool
&& b
prevIx b -> b -> Bool
forall a. Ord a => a -> a -> Bool
< b
curIx
in (Bool, b) -> m (Bool, b)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool, b) -> m (Bool, b)) -> (Bool, b) -> m (Bool, b)
forall a b. (a -> b) -> a -> b
$ Bool
isMono Bool -> (Bool, b) -> (Bool, b)
forall a b. a -> b -> b
`seq` (Bool
isMono, b
curIx)
prop_IterMonotonicBackwards :: Index ix => Int -> Sz ix -> Property
prop_IterMonotonicBackwards :: forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonicBackwards Ix1
thresh sz :: Sz ix
sz@(Sz ix
szix) =
(Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
thresh)
Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (Bool, ix) -> Bool
forall a b. (a, b) -> a
fst (ix
-> ix
-> ix
-> (Ix1 -> Ix1 -> Bool)
-> (Bool, ix)
-> (ix -> (Bool, ix) -> (Bool, ix))
-> (Bool, ix)
forall ix a.
Index ix =>
ix -> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> a) -> a
iter ((Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex Ix1 -> Ix1
forall a. Enum a => a -> a
pred ix
szix) ix
forall ix. Index ix => ix
zeroIndex (Ix1 -> ix
forall ix. Index ix => Ix1 -> ix
pureIndex (-Ix1
1)) Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(>=) (Bool
True, ix
szix) ix -> (Bool, ix) -> (Bool, ix)
forall {b}. Ord b => b -> (Bool, b) -> (Bool, b)
mono)
where
mono :: b -> (Bool, b) -> (Bool, b)
mono b
curIx (Bool
prevMono, b
prevIx) =
let isMono :: Bool
isMono = Bool
prevMono Bool -> Bool -> Bool
&& b
prevIx b -> b -> Bool
forall a. Ord a => a -> a -> Bool
> b
curIx
in Bool
isMono Bool -> (Bool, b) -> (Bool, b)
forall a b. a -> b -> b
`seq` (Bool
isMono, b
curIx)
prop_IterMonotonicBackwardsM :: Index ix => Int -> Sz ix -> Property
prop_IterMonotonicBackwardsM :: forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonicBackwardsM Ix1
thresh sz :: Sz ix
sz@(Sz ix
szix) =
(Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
thresh)
Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (Bool, ix) -> Bool
forall a b. (a, b) -> a
fst
((Bool, ix) -> Bool) -> (Bool, ix) -> Bool
forall a b. (a -> b) -> a -> b
$ Identity (Bool, ix) -> (Bool, ix)
forall a. Identity a -> a
runIdentity
(Identity (Bool, ix) -> (Bool, ix))
-> Identity (Bool, ix) -> (Bool, ix)
forall a b. (a -> b) -> a -> b
$ ix
-> ix
-> ix
-> (Ix1 -> Ix1 -> Bool)
-> (Bool, ix)
-> (ix -> (Bool, ix) -> Identity (Bool, ix))
-> Identity (Bool, ix)
forall ix (m :: * -> *) a.
(Index ix, Monad m) =>
ix
-> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> m a) -> m a
forall (m :: * -> *) a.
Monad m =>
ix
-> ix -> ix -> (Ix1 -> Ix1 -> Bool) -> a -> (ix -> a -> m a) -> m a
iterM ((Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex Ix1 -> Ix1
forall a. Enum a => a -> a
pred ix
szix) ix
forall ix. Index ix => ix
zeroIndex (Ix1 -> ix
forall ix. Index ix => Ix1 -> ix
pureIndex (-Ix1
1)) Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(>=) (Bool
True, ix
szix) ix -> (Bool, ix) -> Identity (Bool, ix)
forall {b} {m :: * -> *}.
(Ord b, Monad m) =>
b -> (Bool, b) -> m (Bool, b)
mono
where
mono :: b -> (Bool, b) -> m (Bool, b)
mono b
curIx (Bool
prevMono, b
prevIx) =
let isMono :: Bool
isMono = Bool
prevMono Bool -> Bool -> Bool
&& b
prevIx b -> b -> Bool
forall a. Ord a => a -> a -> Bool
> b
curIx
in (Bool, b) -> m (Bool, b)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool, b) -> m (Bool, b)) -> (Bool, b) -> m (Bool, b)
forall a b. (a -> b) -> a -> b
$ Bool
isMono Bool -> (Bool, b) -> (Bool, b)
forall a b. a -> b -> b
`seq` (Bool
isMono, b
curIx)
prop_LiftLift2 :: Index ix => ix -> Int -> Bool
prop_LiftLift2 :: forall ix. Index ix => ix -> Ix1 -> Bool
prop_LiftLift2 ix
ix Ix1
delta =
(Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
liftIndex2 Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
(+) ix
ix ((Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
delta) ix
forall ix. Index ix => ix
zeroIndex)
ix -> ix -> Bool
forall a. Eq a => a -> a -> Bool
== (Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
delta) ix
ix
prop_BorderRepairSafe :: Index ix => Border ix -> SzNE ix -> ix -> Property
prop_BorderRepairSafe :: forall ix. Index ix => Border ix -> SzNE ix -> ix -> Property
prop_BorderRepairSafe border :: Border ix
border@(Fill ix
defIx) (SzNE Sz ix
sz) ix
ix =
Bool -> Bool
not (Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
ix) Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> Border ix -> Sz ix -> (ix -> ix) -> ix -> ix
forall ix e. Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex Border ix
border Sz ix
sz ix -> ix
forall a. a -> a
id ix
ix ix -> ix -> Bool
forall a. Eq a => a -> a -> Bool
== ix
defIx
prop_BorderRepairSafe Border ix
border (SzNE Sz ix
sz) ix
ix =
Bool -> Bool
not (Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz ix
ix) Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> Sz ix -> ix -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz ix
sz (Border ix -> Sz ix -> (ix -> ix) -> ix -> ix
forall ix e. Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex Border ix
border Sz ix
sz ix -> ix
forall a. a -> a
id ix
ix)
prop_GetDropInsert :: Index ix => DimIx ix -> ix -> Property
prop_GetDropInsert :: forall ix. Index ix => DimIx ix -> ix -> Property
prop_GetDropInsert (DimIx Dim
dim) ix
ix =
Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$
(IO ix -> ix -> Expectation) -> ix -> IO ix -> Expectation
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO ix -> ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
shouldReturn ix
ix (IO ix -> Expectation) -> IO ix -> Expectation
forall a b. (a -> b) -> a -> b
$ do
Ix1
i <- ix -> Dim -> IO Ix1
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Ix1
forall (m :: * -> *). MonadThrow m => ix -> Dim -> m Ix1
getDimM ix
ix Dim
dim
Lower ix
ixL <- ix -> Dim -> IO (Lower ix)
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
ix -> Dim -> m (Lower ix)
dropDimM ix
ix Dim
dim
Lower ix -> Dim -> Ix1 -> IO ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
Lower ix -> Dim -> Ix1 -> m ix
forall (m :: * -> *).
MonadThrow m =>
Lower ix -> Dim -> Ix1 -> m ix
insertDimM Lower ix
ixL Dim
dim Ix1
i
prop_PullOutInsert :: Index ix => DimIx ix -> ix -> Property
prop_PullOutInsert :: forall ix. Index ix => DimIx ix -> ix -> Property
prop_PullOutInsert (DimIx Dim
dim) ix
ix =
Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$
(IO ix -> ix -> Expectation) -> ix -> IO ix -> Expectation
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO ix -> ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
shouldReturn ix
ix (IO ix -> Expectation) -> IO ix -> Expectation
forall a b. (a -> b) -> a -> b
$ do
(Ix1
i, Lower ix
ixL) <- ix -> Dim -> IO (Ix1, Lower ix)
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m (Ix1, Lower ix)
forall (m :: * -> *).
MonadThrow m =>
ix -> Dim -> m (Ix1, Lower ix)
pullOutDimM ix
ix Dim
dim
Lower ix -> Dim -> Ix1 -> IO ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
Lower ix -> Dim -> Ix1 -> m ix
forall (m :: * -> *).
MonadThrow m =>
Lower ix -> Dim -> Ix1 -> m ix
insertDimM Lower ix
ixL Dim
dim Ix1
i
prop_getDimException :: (Typeable ix, Index ix) => Dim -> ix -> Property
prop_getDimException :: forall ix. (Typeable ix, Index ix) => Dim -> ix -> Property
prop_getDimException Dim
d ix
ix =
(Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
<= Dim
0 Bool -> Bool -> Bool
|| Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
> Maybe ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Maybe ix
forall a. a -> Maybe a
Just ix
ix))
Bool -> Property -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (IndexException -> Bool) -> IO Ix1 -> Property
forall a exc.
(NFData a, Exception exc) =>
(exc -> Bool) -> IO a -> Property
assertDeepExceptionIO (IndexException -> IndexException -> Bool
forall a. Eq a => a -> a -> Bool
== ix -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException ix
ix Dim
d) (ix -> Dim -> IO Ix1
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Ix1
forall (m :: * -> *). MonadThrow m => ix -> Dim -> m Ix1
getDimM ix
ix Dim
d)
prop_setDimException :: (Typeable ix, Index ix) => Dim -> ix -> Int -> Property
prop_setDimException :: forall ix. (Typeable ix, Index ix) => Dim -> ix -> Ix1 -> Property
prop_setDimException Dim
d ix
ix Ix1
i =
(Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
<= Dim
0 Bool -> Bool -> Bool
|| Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
> Maybe ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Maybe ix
forall a. a -> Maybe a
Just ix
ix))
Bool -> Property -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (IndexException -> Bool) -> IO ix -> Property
forall a exc.
(NFData a, Exception exc) =>
(exc -> Bool) -> IO a -> Property
assertDeepExceptionIO (IndexException -> IndexException -> Bool
forall a. Eq a => a -> a -> Bool
== ix -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException ix
ix Dim
d) (ix -> Dim -> Ix1 -> IO ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> Ix1 -> m ix
forall (m :: * -> *). MonadThrow m => ix -> Dim -> Ix1 -> m ix
setDimM ix
ix Dim
d Ix1
i)
prop_PullOutDimException :: (Typeable ix, Index ix) => Dim -> ix -> Property
prop_PullOutDimException :: forall ix. (Typeable ix, Index ix) => Dim -> ix -> Property
prop_PullOutDimException Dim
d ix
ix =
(Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
<= Dim
0 Bool -> Bool -> Bool
|| Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
> Maybe ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Maybe ix
forall a. a -> Maybe a
Just ix
ix))
Bool -> Property -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (IndexException -> Bool) -> IO (Ix1, Lower ix) -> Property
forall a exc.
(NFData a, Exception exc) =>
(exc -> Bool) -> IO a -> Property
assertDeepExceptionIO (IndexException -> IndexException -> Bool
forall a. Eq a => a -> a -> Bool
== ix -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException ix
ix Dim
d) (ix -> Dim -> IO (Ix1, Lower ix)
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m (Ix1, Lower ix)
forall (m :: * -> *).
MonadThrow m =>
ix -> Dim -> m (Ix1, Lower ix)
pullOutDimM ix
ix Dim
d)
prop_InsertDimException
:: forall ix
. (Typeable (Lower ix), Index ix)
=> Dim
-> Lower ix
-> Int
-> Property
prop_InsertDimException :: forall ix.
(Typeable (Lower ix), Index ix) =>
Dim -> Lower ix -> Ix1 -> Property
prop_InsertDimException Dim
d Lower ix
ix Ix1
i =
(Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
<= Dim
0 Bool -> Bool -> Bool
|| Dim
d Dim -> Dim -> Bool
forall a. Ord a => a -> a -> Bool
> IO ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions IO ix
resIO) Bool -> Property -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (IndexException -> Bool) -> IO ix -> Property
forall a exc.
(NFData a, Exception exc) =>
(exc -> Bool) -> IO a -> Property
assertDeepExceptionIO (IndexException -> IndexException -> Bool
forall a. Eq a => a -> a -> Bool
== Lower ix -> Dim -> IndexException
forall ix.
(NFData ix, Eq ix, Show ix, Typeable ix) =>
ix -> Dim -> IndexException
IndexDimensionException Lower ix
ix Dim
d) IO ix
resIO
where
resIO :: IO ix
resIO = Lower ix -> Dim -> Ix1 -> IO ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
Lower ix -> Dim -> Ix1 -> m ix
forall (m :: * -> *).
MonadThrow m =>
Lower ix -> Dim -> Ix1 -> m ix
insertDimM Lower ix
ix Dim
d Ix1
i :: IO ix
prop_UnconsGetDrop :: (Index (Lower ix), Index ix) => ix -> Property
prop_UnconsGetDrop :: forall ix. (Index (Lower ix), Index ix) => ix -> Property
prop_UnconsGetDrop ix
ix =
Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$
(IO (Ix1, Lower ix) -> (Ix1, Lower ix) -> Expectation)
-> (Ix1, Lower ix) -> IO (Ix1, Lower ix) -> Expectation
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Ix1, Lower ix) -> (Ix1, Lower ix) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
shouldReturn (ix -> (Ix1, Lower ix)
forall ix. Index ix => ix -> (Ix1, Lower ix)
unconsDim ix
ix) (IO (Ix1, Lower ix) -> Expectation)
-> IO (Ix1, Lower ix) -> Expectation
forall a b. (a -> b) -> a -> b
$ do
Ix1
i <- ix -> Dim -> IO Ix1
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Ix1
forall (m :: * -> *). MonadThrow m => ix -> Dim -> m Ix1
getDimM ix
ix (Maybe ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Maybe ix
forall a. a -> Maybe a
Just ix
ix))
Lower ix
ixL <- ix -> Dim -> IO (Lower ix)
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
ix -> Dim -> m (Lower ix)
dropDimM ix
ix (Maybe ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Maybe ix
forall a. a -> Maybe a
Just ix
ix))
(Ix1, Lower ix) -> IO (Ix1, Lower ix)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ix1
i, Lower ix
ixL)
prop_UnsnocGetDrop :: (Index (Lower ix), Index ix) => ix -> Property
prop_UnsnocGetDrop :: forall ix. (Index (Lower ix), Index ix) => ix -> Property
prop_UnsnocGetDrop ix
ix =
Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$
(IO (Lower ix, Ix1) -> (Lower ix, Ix1) -> Expectation)
-> (Lower ix, Ix1) -> IO (Lower ix, Ix1) -> Expectation
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO (Lower ix, Ix1) -> (Lower ix, Ix1) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
shouldReturn (ix -> (Lower ix, Ix1)
forall ix. Index ix => ix -> (Lower ix, Ix1)
unsnocDim ix
ix) (IO (Lower ix, Ix1) -> Expectation)
-> IO (Lower ix, Ix1) -> Expectation
forall a b. (a -> b) -> a -> b
$ do
Ix1
i <- ix -> Dim -> IO Ix1
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Ix1
forall (m :: * -> *). MonadThrow m => ix -> Dim -> m Ix1
getDimM ix
ix Dim
1
Lower ix
ixL <- ix -> Dim -> IO (Lower ix)
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
ix -> Dim -> m (Lower ix)
dropDimM ix
ix Dim
1
(Lower ix, Ix1) -> IO (Lower ix, Ix1)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Lower ix
ixL, Ix1
i)
prop_SetAll :: Index ix => ix -> Property
prop_SetAll :: forall ix. Index ix => ix -> Property
prop_SetAll ix
ix = Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$ do
[Dim] -> IO ix
replaceDims [Dim]
dims IO ix -> ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
`shouldReturn` ix
ix
[Dim] -> IO ix
replaceDims ([Dim] -> [Dim]
forall a. [a] -> [a]
reverse [Dim]
dims) IO ix -> ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
`shouldReturn` ix
ix
where
replaceDims :: [Dim] -> IO ix
replaceDims = (ix -> Dim -> IO ix) -> ix -> [Dim] -> IO ix
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\ix
cix Dim
d -> ix -> Dim -> IO Ix1
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> m Ix1
forall (m :: * -> *). MonadThrow m => ix -> Dim -> m Ix1
getDimM ix
ix Dim
d IO Ix1 -> (Ix1 -> IO ix) -> IO ix
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ix -> Dim -> Ix1 -> IO ix
forall ix (m :: * -> *).
(Index ix, MonadThrow m) =>
ix -> Dim -> Ix1 -> m ix
forall (m :: * -> *). MonadThrow m => ix -> Dim -> Ix1 -> m ix
setDimM ix
cix Dim
d) ix
forall ix. Index ix => ix
zeroIndex
dims :: [Dim]
dims = [Dim
1 .. Maybe ix -> Dim
forall ix (proxy :: * -> *). Index ix => proxy ix -> Dim
forall (proxy :: * -> *). proxy ix -> Dim
dimensions (ix -> Maybe ix
forall a. a -> Maybe a
Just ix
ix)] :: [Dim]
prop_SetGet :: Index ix => ix -> DimIx ix -> Int -> Property
prop_SetGet :: forall ix. Index ix => ix -> DimIx ix -> Ix1 -> Property
prop_SetGet ix
ix (DimIx Dim
dim) Ix1
n = Ix1
n Ix1 -> Ix1 -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dim -> Ix1
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Ix1
getDim' (ix -> Dim -> Ix1 -> ix
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Ix1 -> ix
setDim' ix
ix Dim
dim Ix1
n) Dim
dim
prop_BorderIx1 :: Positive Int -> Border Char -> Fun Ix1 Char -> SzNE Ix1 -> Ix1 -> Property
prop_BorderIx1 :: Positive Ix1
-> Border Char -> Fun Ix1 Char -> SzNE Ix1 -> Ix1 -> Property
prop_BorderIx1 (Positive Ix1
period) Border Char
border Fun Ix1 Char
getVal (SzNE Sz Ix1
sz) Ix1
ix =
if Sz Ix1 -> Ix1 -> Bool
forall ix. Index ix => Sz ix -> ix -> Bool
isSafeIndex Sz Ix1
sz Ix1
ix
then Char
val Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal Ix1
ix
else case Border Char
border of
Fill Char
defVal -> Char
val Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Char
defVal
Border Char
Wrap ->
Char
val
Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Border Char -> Sz Ix1 -> (Ix1 -> Char) -> Ix1 -> Char
forall ix e. Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex
Border Char
border
Sz Ix1
sz
(Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal)
((Ix1 -> Ix1 -> Ix1) -> Ix1 -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
liftIndex2 Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
(+) ((Ix1 -> Ix1) -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
* Ix1
period) (Sz Ix1 -> Ix1
forall ix. Sz ix -> ix
unSz Sz Ix1
sz)) Ix1
ix)
Border Char
Edge ->
if Ix1
ix Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
0
then Char
val Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal ((Ix1 -> Ix1) -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
max Ix1
0) Ix1
ix)
else Char
val Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal ((Ix1 -> Ix1 -> Ix1) -> Ix1 -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
liftIndex2 Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
min ((Ix1 -> Ix1) -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
subtract Ix1
1) (Sz Ix1 -> Ix1
forall ix. Sz ix -> ix
unSz Sz Ix1
sz)) Ix1
ix)
Border Char
Reflect ->
Char
val
Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Border Char -> Sz Ix1 -> (Ix1 -> Char) -> Ix1 -> Char
forall ix e. Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex
Border Char
border
Sz Ix1
sz
(Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal)
((Ix1 -> Ix1 -> Ix1) -> Ix1 -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1 -> Ix1) -> ix -> ix -> ix
liftIndex2 Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
(+) ((Ix1 -> Ix1) -> Ix1 -> Ix1
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
* (Ix1
2 Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
* Ix1 -> Ix1
forall a. Num a => a -> a
signum Ix1
ix Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
* Ix1
period)) (Sz Ix1 -> Ix1
forall ix. Sz ix -> ix
unSz Sz Ix1
sz)) Ix1
ix)
Border Char
Continue ->
Char
val
Char -> Char -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Border Char -> Sz Ix1 -> (Ix1 -> Char) -> Ix1 -> Char
forall ix e. Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex
Border Char
forall e. Border e
Reflect
Sz Ix1
sz
(Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal)
( if Ix1
ix Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
< Ix1
0
then Ix1
ix Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
- Ix1
1
else Ix1
ix Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
1
)
where
val :: Char
val = Border Char -> Sz Ix1 -> (Ix1 -> Char) -> Ix1 -> Char
forall ix e. Index ix => Border e -> Sz ix -> (ix -> e) -> ix -> e
handleBorderIndex Border Char
border Sz Ix1
sz (Fun Ix1 Char -> Ix1 -> Char
forall a b. Fun a b -> a -> b
apply Fun Ix1 Char
getVal) Ix1
ix
prop_BinaryNumIx
:: (Num ix, Index ix) => (forall n. Num n => n -> n -> n) -> ix -> ix -> Property
prop_BinaryNumIx :: forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> ix -> ix -> Property
prop_BinaryNumIx forall a. Num a => a -> a -> a
f ix
ix1 ix
ix2 = (Ix1 -> Ix1 -> Ix1) -> [Ix1] -> [Ix1] -> [Ix1]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
f (ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList ix
ix1) (ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList ix
ix2) [Ix1] -> [Ix1] -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (ix -> ix -> ix
forall a. Num a => a -> a -> a
f ix
ix1 ix
ix2)
prop_UnaryNumIx
:: (Num ix, Index ix) => (forall n. Num n => n -> n) -> ix -> Property
prop_UnaryNumIx :: forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> ix -> Property
prop_UnaryNumIx forall a. Num a => a -> a
f ix
ix = (Ix1 -> Ix1) -> [Ix1] -> [Ix1]
forall a b. (a -> b) -> [a] -> [b]
map Ix1 -> Ix1
forall a. Num a => a -> a
f (ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList ix
ix) [Ix1] -> [Ix1] -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (ix -> ix
forall a. Num a => a -> a
f ix
ix)
prop_BinaryNumSz
:: (Num ix, Index ix) => (forall n. Num n => n -> n -> n) -> Sz ix -> Sz ix -> Property
prop_BinaryNumSz :: forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> Sz ix -> Sz ix -> Property
prop_BinaryNumSz forall a. Num a => a -> a -> a
f Sz ix
sz1 Sz ix
sz2 =
(Ix1 -> Ix1 -> Ix1) -> [Ix1] -> [Ix1] -> [Ix1]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Ix1 -> Ix1 -> Ix1
f' (ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz1)) (ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz2)) [Ix1] -> [Ix1] -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (Sz ix -> ix
forall ix. Sz ix -> ix
unSz (Sz ix -> Sz ix -> Sz ix
forall a. Num a => a -> a -> a
f Sz ix
sz1 Sz ix
sz2))
where
f' :: Ix1 -> Ix1 -> Ix1
f' Ix1
x Ix1
y = Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
max Ix1
0 (Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
f Ix1
x Ix1
y)
prop_UnaryNumSz
:: (Num ix, Index ix) => (forall n. Num n => n -> n) -> Sz ix -> Property
prop_UnaryNumSz :: forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> Sz ix -> Property
prop_UnaryNumSz forall a. Num a => a -> a
f Sz ix
sz = (Ix1 -> Ix1) -> [Ix1] -> [Ix1]
forall a b. (a -> b) -> [a] -> [b]
map Ix1 -> Ix1
f' (ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz)) [Ix1] -> [Ix1] -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> [Ix1]
forall ix. Index ix => ix -> [Ix1]
ixToList (Sz ix -> ix
forall ix. Sz ix -> ix
unSz (Sz ix -> Sz ix
forall a. Num a => a -> a
f Sz ix
sz))
where
f' :: Ix1 -> Ix1
f' = Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
max Ix1
0 (Ix1 -> Ix1) -> (Ix1 -> Ix1) -> Ix1 -> Ix1
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ix1 -> Ix1
forall a. Num a => a -> a
f
prop_IterLinearM :: Index ix => Sz ix -> NonNegative Int -> Positive Int -> Property
prop_IterLinearM :: forall ix.
Index ix =>
Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property
prop_IterLinearM Sz ix
sz (NonNegative Ix1
start) (Positive Ix1
increment) = Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$ do
[Ix1]
xs <- Sz ix
-> Ix1
-> Ix1
-> Ix1
-> (Ix1 -> Ix1 -> Bool)
-> [Ix1]
-> (Ix1 -> ix -> [Ix1] -> IO [Ix1])
-> IO [Ix1]
forall ix (m :: * -> *) a.
(Index ix, Monad m) =>
Sz ix
-> Ix1
-> Ix1
-> Ix1
-> (Ix1 -> Ix1 -> Bool)
-> a
-> (Ix1 -> ix -> a -> m a)
-> m a
iterLinearM Sz ix
sz Ix1
start (Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz) Ix1
increment Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(<) [] ((Ix1 -> ix -> [Ix1] -> IO [Ix1]) -> IO [Ix1])
-> (Ix1 -> ix -> [Ix1] -> IO [Ix1]) -> IO [Ix1]
forall a b. (a -> b) -> a -> b
$ \Ix1
i ix
ix [Ix1]
acc -> do
Sz ix -> ix -> Ix1
forall ix. Index ix => Sz ix -> ix -> Ix1
toLinearIndex Sz ix
sz ix
ix Ix1 -> Ix1 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Ix1
i
[Ix1] -> IO [Ix1]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ix1
i Ix1 -> [Ix1] -> [Ix1]
forall a. a -> [a] -> [a]
: [Ix1]
acc)
[Ix1] -> [Ix1]
forall a. [a] -> [a]
reverse [Ix1]
xs [Ix1] -> [Ix1] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [Ix1
start, Ix1
start Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
increment .. Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
- Ix1
1]
prop_IterLinearM_ :: Index ix => Sz ix -> NonNegative Int -> Positive Int -> Property
prop_IterLinearM_ :: forall ix.
Index ix =>
Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property
prop_IterLinearM_ Sz ix
sz (NonNegative Ix1
start) (Positive Ix1
increment) = Expectation -> Property
forall prop. Testable prop => prop -> Property
property (Expectation -> Property) -> Expectation -> Property
forall a b. (a -> b) -> a -> b
$ do
IORef [Ix1]
ref <- [Ix1] -> IO (IORef [Ix1])
forall a. a -> IO (IORef a)
newIORef []
Sz ix
-> Ix1
-> Ix1
-> Ix1
-> (Ix1 -> Ix1 -> Bool)
-> (Ix1 -> ix -> Expectation)
-> Expectation
forall ix (m :: * -> *).
(Index ix, Monad m) =>
Sz ix
-> Ix1
-> Ix1
-> Ix1
-> (Ix1 -> Ix1 -> Bool)
-> (Ix1 -> ix -> m ())
-> m ()
iterLinearM_ Sz ix
sz Ix1
start (Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz) Ix1
increment Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
(<) ((Ix1 -> ix -> Expectation) -> Expectation)
-> (Ix1 -> ix -> Expectation) -> Expectation
forall a b. (a -> b) -> a -> b
$ \Ix1
i ix
ix -> do
Sz ix -> ix -> Ix1
forall ix. Index ix => Sz ix -> ix -> Ix1
toLinearIndex Sz ix
sz ix
ix Ix1 -> Ix1 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Ix1
i
IORef [Ix1] -> ([Ix1] -> [Ix1]) -> Expectation
forall a. IORef a -> (a -> a) -> Expectation
modifyIORef' IORef [Ix1]
ref (Ix1
i Ix1 -> [Ix1] -> [Ix1]
forall a. a -> [a] -> [a]
:)
[Ix1]
xs <- IORef [Ix1] -> IO [Ix1]
forall a. IORef a -> IO a
readIORef IORef [Ix1]
ref
[Ix1] -> [Ix1]
forall a. [a] -> [a]
reverse [Ix1]
xs [Ix1] -> [Ix1] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [Ix1
start, Ix1
start Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
+ Ix1
increment .. Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
- Ix1
1]
specIx1 :: Spec
specIx1 :: Spec
specIx1 = String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Ix1" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
forall ix.
(Typeable (Lower ix), Arbitrary (Lower ix), Typeable ix, Index ix,
Arbitrary ix, IsIndexDimension ix (Dimensions ix)) =>
Spec
ixSpec @Ix1
forall ix. (Typeable ix, Num ix, Index ix, Arbitrary ix) => Spec
ixNumSpec @Ix1
String -> Property -> SpecM (Arg Property) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Border" (Property -> SpecM (Arg Property) ())
-> Property -> SpecM (Arg Property) ()
forall a b. (a -> b) -> a -> b
$ (Positive Ix1
-> Border Char -> Fun Ix1 Char -> SzNE Ix1 -> Ix1 -> Property)
-> Property
forall prop. Testable prop => prop -> Property
property Positive Ix1
-> Border Char -> Fun Ix1 Char -> SzNE Ix1 -> Ix1 -> Property
prop_BorderIx1
ixSpec
:: forall ix
. ( Typeable (Lower ix)
, Arbitrary (Lower ix)
, Typeable ix
, Index ix
, Arbitrary ix
, IsIndexDimension ix (Dimensions ix)
)
=> Spec
ixSpec :: forall ix.
(Typeable (Lower ix), Arbitrary (Lower ix), Typeable ix, Index ix,
Arbitrary ix, IsIndexDimension ix (Dimensions ix)) =>
Spec
ixSpec = do
let threshold :: Ix1
threshold = Ix1
50000
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Safety" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (SzIx ix -> Bool) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"IsSafeIndex" ((SzIx ix -> Bool) -> Spec) -> (SzIx ix -> Bool) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => SzIx ix -> Bool
prop_IsSafeIndex @ix
String -> (SzIx ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"RepairSafeIx" ((SzIx ix -> Property) -> Spec) -> (SzIx ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => SzIx ix -> Property
prop_RepairSafeIx @ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Lifting" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (ix -> Ix1 -> Bool) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Lift/Lift2" ((ix -> Ix1 -> Bool) -> Spec) -> (ix -> Ix1 -> Bool) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => ix -> Ix1 -> Bool
prop_LiftLift2 @ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Linear" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (SzIx ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"ToFromLinearIndex" ((SzIx ix -> Property) -> Spec) -> (SzIx ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => SzIx ix -> Property
prop_ToFromLinearIndex @ix
String -> (SzNE ix -> NonNegative Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"FromToLinearIndex" ((SzNE ix -> NonNegative Ix1 -> Property) -> Spec)
-> (SzNE ix -> NonNegative Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => SzNE ix -> NonNegative Ix1 -> Property
prop_FromToLinearIndex @ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Iterator" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"CountElements" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_CountElements @ix Ix1
threshold
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Monotonic" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonic @ix Ix1
threshold
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"MonotonicBackwards" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonicBackwards @ix Ix1
threshold
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"MonotonicM" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonicM @ix Ix1
threshold
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"MonotonicBackwardsM" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => Ix1 -> Sz ix -> Property
prop_IterMonotonicBackwardsM @ix Ix1
threshold
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Border" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Border ix -> SzNE ix -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"BorderRepairSafe" ((Border ix -> SzNE ix -> ix -> Property) -> Spec)
-> (Border ix -> SzNE ix -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => Border ix -> SzNE ix -> ix -> Property
prop_BorderRepairSafe @ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"SetGetDrop" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SetAll" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => ix -> Property
prop_SetAll @ix
String -> (ix -> DimIx ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SetGet" ((ix -> DimIx ix -> Ix1 -> Property) -> Spec)
-> (ix -> DimIx ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => ix -> DimIx ix -> Ix1 -> Property
prop_SetGet @ix
String -> (DimIx ix -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"GetDropInsert" ((DimIx ix -> ix -> Property) -> Spec)
-> (DimIx ix -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => DimIx ix -> ix -> Property
prop_GetDropInsert @ix
String -> (DimIx ix -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"PullOutInsert" ((DimIx ix -> ix -> Property) -> Spec)
-> (DimIx ix -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => DimIx ix -> ix -> Property
prop_PullOutInsert @ix
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"UnconsCons" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => ix -> Property
prop_UnconsCons @ix
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"UnsnocSnoc" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => ix -> Property
prop_UnsnocSnoc @ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"IndexDimensionException" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Dim -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"getDimException" ((Dim -> ix -> Property) -> Spec)
-> (Dim -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. (Typeable ix, Index ix) => Dim -> ix -> Property
prop_getDimException @ix
String -> (Dim -> ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"setDimException" ((Dim -> ix -> Ix1 -> Property) -> Spec)
-> (Dim -> ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. (Typeable ix, Index ix) => Dim -> ix -> Ix1 -> Property
prop_setDimException @ix
String -> (Dim -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"PullOutDimException" ((Dim -> ix -> Property) -> Spec)
-> (Dim -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. (Typeable ix, Index ix) => Dim -> ix -> Property
prop_PullOutDimException @ix
String -> (Dim -> Lower ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"InsertDimException" ((Dim -> Lower ix -> Ix1 -> Property) -> Spec)
-> (Dim -> Lower ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Typeable (Lower ix), Index ix) =>
Dim -> Lower ix -> Ix1 -> Property
prop_InsertDimException @ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Dimension" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"GetInnerDimension" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(ix
ix :: ix) -> ix -> Ix1
forall ix. Index ix => ix -> Ix1
lastDim ix
ix Ix1 -> Ix1 -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension 1 -> Ix1
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> Ix1
getDimension ix
ix Dimension 1
Dim1
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"GetOuterDimension" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(ix
ix :: ix) -> ix -> Ix1
forall ix. Index ix => ix -> Ix1
headDim ix
ix Ix1 -> Ix1 -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension (Dimensions ix) -> Ix1
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> Ix1
getDimension ix
ix (Dimension (Dimensions ix)
forall (n :: Nat). (1 <= n, KnownNat n) => Dimension n
DimN :: Dimension (Dimensions ix))
String -> (ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SetInnerDimension" ((ix -> Ix1 -> Property) -> Spec)
-> (ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(ix
ix :: ix) Ix1
i -> Lower ix -> Ix1 -> ix
forall ix. Index ix => Lower ix -> Ix1 -> ix
snocDim (ix -> Lower ix
forall ix. Index ix => ix -> Lower ix
initDim ix
ix) Ix1
i ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension 1 -> Ix1 -> ix
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> Ix1 -> ix
setDimension ix
ix Dimension 1
Dim1 Ix1
i
String -> (ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SetOuterDimension" ((ix -> Ix1 -> Property) -> Spec)
-> (ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(ix
ix :: ix) Ix1
i ->
Ix1 -> Lower ix -> ix
forall ix. Index ix => Ix1 -> Lower ix -> ix
consDim Ix1
i (ix -> Lower ix
forall ix. Index ix => ix -> Lower ix
tailDim ix
ix)
ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension (Dimensions ix) -> Ix1 -> ix
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> Ix1 -> ix
setDimension ix
ix (Dimension (Dimensions ix)
forall (n :: Nat). (1 <= n, KnownNat n) => Dimension n
DimN :: Dimension (Dimensions ix)) Ix1
i
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"DropInnerDimension" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(ix
ix :: ix) -> ix -> Lower ix
forall ix. Index ix => ix -> Lower ix
initDim ix
ix Lower ix -> Lower ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension 1 -> Lower ix
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> Lower ix
dropDimension ix
ix Dimension 1
Dim1
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"DropOuterDimension" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(ix
ix :: ix) -> ix -> Lower ix
forall ix. Index ix => ix -> Lower ix
tailDim ix
ix Lower ix -> Lower ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension (Dimensions ix) -> Lower ix
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> Lower ix
dropDimension ix
ix (Dimension (Dimensions ix)
forall (n :: Nat). (1 <= n, KnownNat n) => Dimension n
DimN :: Dimension (Dimensions ix))
String -> (Lower ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"InsertInnerDimension" ((Lower ix -> Ix1 -> Property) -> Spec)
-> (Lower ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(Lower ix
ixl :: Lower ix) Ix1
i -> (Lower ix -> Ix1 -> ix
forall ix. Index ix => Lower ix -> Ix1 -> ix
snocDim Lower ix
ixl Ix1
i :: ix) ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Lower ix -> Dimension 1 -> Ix1 -> ix
forall ix (n :: Nat).
IsIndexDimension ix n =>
Lower ix -> Dimension n -> Ix1 -> ix
insertDimension Lower ix
ixl Dimension 1
Dim1 Ix1
i
String -> (Lower ix -> Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"InsertOuterDimension" ((Lower ix -> Ix1 -> Property) -> Spec)
-> (Lower ix -> Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(Lower ix
ixl :: Lower ix) Ix1
i ->
(Ix1 -> Lower ix -> ix
forall ix. Index ix => Ix1 -> Lower ix -> ix
consDim Ix1
i Lower ix
ixl :: ix)
ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Lower ix -> Dimension (Dimensions ix) -> Ix1 -> ix
forall ix (n :: Nat).
IsIndexDimension ix n =>
Lower ix -> Dimension n -> Ix1 -> ix
insertDimension Lower ix
ixl (Dimension (Dimensions ix)
forall (n :: Nat). (1 <= n, KnownNat n) => Dimension n
DimN :: Dimension (Dimensions ix)) Ix1
i
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"PullOutInnerDimension" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(ix
ix :: ix) -> ix -> (Lower ix, Ix1)
forall ix. Index ix => ix -> (Lower ix, Ix1)
unsnocDim ix
ix (Lower ix, Ix1) -> (Lower ix, Ix1) -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Ix1 -> Lower ix -> (Lower ix, Ix1))
-> (Ix1, Lower ix) -> (Lower ix, Ix1)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Lower ix -> Ix1 -> (Lower ix, Ix1))
-> Ix1 -> Lower ix -> (Lower ix, Ix1)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,)) (ix -> Dimension 1 -> (Ix1, Lower ix)
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> (Ix1, Lower ix)
pullOutDimension ix
ix Dimension 1
Dim1)
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"PullInnerOuterDimension" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(ix
ix :: ix) ->
ix -> (Ix1, Lower ix)
forall ix. Index ix => ix -> (Ix1, Lower ix)
unconsDim ix
ix
(Ix1, Lower ix) -> (Ix1, Lower ix) -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Dimension (Dimensions ix) -> (Ix1, Lower ix)
forall ix (n :: Nat).
IsIndexDimension ix n =>
ix -> Dimension n -> (Ix1, Lower ix)
pullOutDimension ix
ix (Dimension (Dimensions ix)
forall (n :: Nat). (1 <= n, KnownNat n) => Dimension n
DimN :: Dimension (Dimensions ix))
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"NFData" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Property -> SpecM (Arg Property) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"rnf" (Property -> SpecM (Arg Property) ())
-> Property -> SpecM (Arg Property) ()
forall a b. (a -> b) -> a -> b
$ (ix -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((ix -> Expectation) -> Property)
-> (ix -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(ix
ix :: ix) -> ix -> ()
forall a. NFData a => a -> ()
rnf ix
ix () -> () -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ()
String -> Property -> SpecM (Arg Property) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"throws exception" (Property -> SpecM (Arg Property) ())
-> Property -> SpecM (Arg Property) ()
forall a b. (a -> b) -> a -> b
$ (DimIx ix -> ix -> Property) -> Property
forall prop. Testable prop => prop -> Property
property ((DimIx ix -> ix -> Property) -> Property)
-> (DimIx ix -> ix -> Property) -> Property
forall a b. (a -> b) -> a -> b
$ \(DimIx Dim
d :: DimIx ix) (ix
ix :: ix) ->
(ExpectedException -> Bool) -> ix -> Property
forall a exc.
(NFData a, Exception exc) =>
(exc -> Bool) -> a -> Property
assertDeepException (ExpectedException -> ExpectedException -> Bool
forall a. Eq a => a -> a -> Bool
== ExpectedException
ExpectedException) (ix -> Dim -> Ix1 -> ix
forall ix. (HasCallStack, Index ix) => ix -> Dim -> Ix1 -> ix
setDim' ix
ix Dim
d (ExpectedException -> Ix1
forall a e. Exception e => e -> a
throw ExpectedException
ExpectedException))
ix2UpSpec
:: forall ix
. (Index ix, Index (Lower ix), Arbitrary ix, Arbitrary (Lower ix), Typeable (Lower ix))
=> Spec
ix2UpSpec :: forall ix.
(Index ix, Index (Lower ix), Arbitrary ix, Arbitrary (Lower ix),
Typeable (Lower ix)) =>
Spec
ix2UpSpec =
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Higher/Lower" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"UnconsGetDrop" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. (Index (Lower ix), Index ix) => ix -> Property
prop_UnconsGetDrop @ix
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"UnsnocGetDrop" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. (Index (Lower ix), Index ix) => ix -> Property
prop_UnsnocGetDrop @ix
ixNumSpec :: forall ix. (Typeable ix, Num ix, Index ix, Arbitrary ix) => Spec
ixNumSpec :: forall ix. (Typeable ix, Num ix, Index ix, Arbitrary ix) => Spec
ixNumSpec = do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe (String
"Num (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ forall t. Typeable t => ShowS
showsType @ix String
")") (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (ix -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"(+)" ((ix -> ix -> Property) -> Spec) -> (ix -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> ix -> ix -> Property
prop_BinaryNumIx @ix n -> n -> n
forall a. Num a => a -> a -> a
(+)
String -> (ix -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"(-)" ((ix -> ix -> Property) -> Spec) -> (ix -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> ix -> ix -> Property
prop_BinaryNumIx @ix (-)
String -> (ix -> ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"(*)" ((ix -> ix -> Property) -> Spec) -> (ix -> ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> ix -> ix -> Property
prop_BinaryNumIx @ix n -> n -> n
forall a. Num a => a -> a -> a
(*)
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"negate" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> ix -> Property
prop_UnaryNumIx @ix n -> n
forall a. Num a => a -> a
negate
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"abs" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> ix -> Property
prop_UnaryNumIx @ix n -> n
forall a. Num a => a -> a
abs
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"signum" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> ix -> Property
prop_UnaryNumIx @ix n -> n
forall a. Num a => a -> a
signum
String -> (Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"fromInteger" ((Ix1 -> Property) -> Spec) -> (Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(Ix1
i :: Int) ->
(Ix1 -> ix
forall a b. (Integral a, Num b) => a -> b
fromIntegral Ix1
i :: ix) ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a b. a -> b -> a
const Ix1
i) ix
forall ix. Index ix => ix
zeroIndex
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Constants" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"zeroIndex" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ (ix
forall ix. Index ix => ix
zeroIndex :: ix) ix -> ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ix
0
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"oneIndex" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ (ix
forall ix. Index ix => ix
oneIndex :: ix) ix -> ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ix
1
szNumSpec :: forall ix. (Typeable ix, Num ix, Index ix, Arbitrary ix) => Spec
szNumSpec :: forall ix. (Typeable ix, Num ix, Index ix, Arbitrary ix) => Spec
szNumSpec = do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe (String
"Num (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ forall t. Typeable t => ShowS
showsType @(Sz ix) String
")") (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Sz ix -> Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"(+)" ((Sz ix -> Sz ix -> Property) -> Spec)
-> (Sz ix -> Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> Sz ix -> Sz ix -> Property
prop_BinaryNumSz @ix n -> n -> n
forall a. Num a => a -> a -> a
(+)
String -> (Sz ix -> Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"(-)" ((Sz ix -> Sz ix -> Property) -> Spec)
-> (Sz ix -> Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> Sz ix -> Sz ix -> Property
prop_BinaryNumSz @ix (-)
String -> (Sz ix -> Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"(*)" ((Sz ix -> Sz ix -> Property) -> Spec)
-> (Sz ix -> Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a -> a) -> Sz ix -> Sz ix -> Property
prop_BinaryNumSz @ix n -> n -> n
forall a. Num a => a -> a -> a
(*)
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"negate (throws error on non-zero)" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \Sz ix
sz ->
Sz ix
sz
Sz ix -> Sz ix -> Bool
forall a. Eq a => a -> a -> Bool
/= Sz ix
forall ix. Index ix => Sz ix
zeroSz
Bool -> Property -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (ErrorCall -> Bool) -> Sz ix -> Property
forall a exc.
(NFData a, Exception exc) =>
(exc -> Bool) -> a -> Property
assertDeepException
(\(ErrorCall String
err) -> String
err String -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq` Bool
True)
(Sz ix -> Sz ix
forall a. Num a => a -> a
negate Sz ix
sz :: Sz ix)
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"abs" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> Sz ix -> Property
prop_UnaryNumSz @ix n -> n
forall a. Num a => a -> a
abs
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"signum" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
(Num ix, Index ix) =>
(forall a. Num a => a -> a) -> Sz ix -> Property
prop_UnaryNumSz @ix n -> n
forall a. Num a => a -> a
signum
String -> (Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"fromInteger" ((Ix1 -> Property) -> Spec) -> (Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(Ix1
i :: Int) ->
(Ix1 -> Sz ix
forall a b. (Integral a, Num b) => a -> b
fromIntegral Ix1
i :: Sz ix) Sz ix -> Sz ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== ix -> Sz ix
forall ix. ix -> Sz ix
SafeSz (Ix1 -> ix
forall ix. Index ix => Ix1 -> ix
pureIndex (Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
max Ix1
0 Ix1
i))
String -> (ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"fromIx" ((ix -> Property) -> Spec) -> (ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(ix
ix :: ix) -> Sz ix -> ix
forall ix. Sz ix -> ix
unSz (ix -> Sz ix
forall ix. Index ix => ix -> Sz ix
Sz ix
ix) ix -> ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Ix1 -> Ix1) -> ix -> ix
forall ix. Index ix => (Ix1 -> Ix1) -> ix -> ix
liftIndex (Ix1 -> Ix1 -> Ix1
forall a. Ord a => a -> a -> a
max Ix1
0) ix
ix
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Constants" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"zeroSz" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ (Sz ix
forall ix. Index ix => Sz ix
zeroSz :: Sz ix) Sz ix -> Sz ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Sz ix
0
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"oneSz" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ (Sz ix
forall ix. Index ix => Sz ix
oneSz :: Sz ix) Sz ix -> Sz ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Sz ix
1
prop_PullOutInsertSize :: Index ix => DimIx ix -> Sz ix -> Property
prop_PullOutInsertSize :: forall ix. Index ix => DimIx ix -> Sz ix -> Property
prop_PullOutInsertSize (DimIx Dim
dim) Sz ix
sz =
(SomeException -> Property)
-> (Sz ix -> Property) -> Either SomeException (Sz ix) -> Property
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either SomeException -> Property
forall a e. Exception e => e -> a
throw (Sz ix
sz Sz ix -> Sz ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
===) (Either SomeException (Sz ix) -> Property)
-> Either SomeException (Sz ix) -> Property
forall a b. (a -> b) -> a -> b
$ do
(Sz Ix1
i, Sz (Lower ix)
szL) <- Sz ix -> Dim -> Either SomeException (Sz Ix1, Sz (Lower ix))
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
Sz ix -> Dim -> m (Sz Ix1, Sz (Lower ix))
pullOutSzM Sz ix
sz Dim
dim
Sz (Lower ix) -> Dim -> Sz Ix1 -> Either SomeException (Sz ix)
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
Sz (Lower ix) -> Dim -> Sz Ix1 -> m (Sz ix)
insertSzM Sz (Lower ix)
szL Dim
dim Sz Ix1
i
szSpec
:: forall ix
. (Index ix, Arbitrary ix)
=> Spec
szSpec :: forall ix. (Index ix, Arbitrary ix) => Spec
szSpec = do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Higher/Lower" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"LiftSzNegate" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(Sz ix
sz :: Sz ix) -> (Ix1 -> Ix1) -> Sz ix -> Sz ix
forall ix. Index ix => (Ix1 -> Ix1) -> Sz ix -> Sz ix
liftSz Ix1 -> Ix1
forall a. Num a => a -> a
negate Sz ix
sz Sz ix -> Sz ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Sz ix
forall ix. Index ix => Sz ix
zeroSz
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"UnconsCons" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(Sz ix
sz :: Sz ix) -> Sz ix
sz Sz ix -> Sz ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Sz Ix1 -> Sz (Lower ix) -> Sz ix)
-> (Sz Ix1, Sz (Lower ix)) -> Sz ix
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Sz Ix1 -> Sz (Lower ix) -> Sz ix
forall ix. Index ix => Sz Ix1 -> Sz (Lower ix) -> Sz ix
consSz (Sz ix -> (Sz Ix1, Sz (Lower ix))
forall ix. Index ix => Sz ix -> (Sz Ix1, Sz (Lower ix))
unconsSz Sz ix
sz)
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"UnsnocSnoc" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ \(Sz ix
sz :: Sz ix) -> Sz ix
sz Sz ix -> Sz ix -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Sz (Lower ix) -> Sz Ix1 -> Sz ix)
-> (Sz (Lower ix), Sz Ix1) -> Sz ix
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Sz (Lower ix) -> Sz Ix1 -> Sz ix
forall ix. Index ix => Sz (Lower ix) -> Sz Ix1 -> Sz ix
snocSz (Sz ix -> (Sz (Lower ix), Sz Ix1)
forall ix. Index ix => Sz ix -> (Sz (Lower ix), Sz Ix1)
unsnocSz Sz ix
sz)
String -> (DimIx ix -> Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"PullOutInsert" ((DimIx ix -> Sz ix -> Property) -> Spec)
-> (DimIx ix -> Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix. Index ix => DimIx ix -> Sz ix -> Property
prop_PullOutInsertSize @ix
String -> (Sz ix -> Sz Ix1 -> Expectation) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SetSzInnerSnoc" ((Sz ix -> Sz Ix1 -> Expectation) -> Spec)
-> (Sz ix -> Sz Ix1 -> Expectation) -> Spec
forall a b. (a -> b) -> a -> b
$
\(Sz ix
sz :: Sz ix) Sz Ix1
i -> Sz ix -> Dim -> Sz Ix1 -> IO (Sz ix)
forall (m :: * -> *) ix.
(MonadThrow m, Index ix) =>
Sz ix -> Dim -> Sz Ix1 -> m (Sz ix)
setSzM Sz ix
sz Dim
1 Sz Ix1
i IO (Sz ix) -> Sz ix -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
`shouldReturn` Sz (Lower ix) -> Sz Ix1 -> Sz ix
forall ix. Index ix => Sz (Lower ix) -> Sz Ix1 -> Sz ix
snocSz ((Sz (Lower ix), Sz Ix1) -> Sz (Lower ix)
forall a b. (a, b) -> a
fst ((Sz (Lower ix), Sz Ix1) -> Sz (Lower ix))
-> (Sz (Lower ix), Sz Ix1) -> Sz (Lower ix)
forall a b. (a -> b) -> a -> b
$ Sz ix -> (Sz (Lower ix), Sz Ix1)
forall ix. Index ix => Sz ix -> (Sz (Lower ix), Sz Ix1)
unsnocSz Sz ix
sz) Sz Ix1
i
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Number of Elements" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"TotalElem" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(Sz ix
sz :: Sz ix) -> Sz ix -> Ix1
forall ix. Index ix => Sz ix -> Ix1
totalElem Sz ix
sz Ix1 -> Ix1 -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Ix1 -> Ix1 -> Ix1) -> Ix1 -> ix -> Ix1
forall ix a. Index ix => (a -> Ix1 -> a) -> a -> ix -> a
forall a. (a -> Ix1 -> a) -> a -> ix -> a
foldlIndex Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
(*) Ix1
1 (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz)
String -> (Sz ix -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"IsNonZeroSz" ((Sz ix -> Property) -> Spec) -> (Sz ix -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
\(Sz ix
sz :: Sz ix) -> Sz ix -> Bool
forall ix. Index ix => Sz ix -> Bool
isNotZeroSz Sz ix
sz Bool -> Bool -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== (Bool -> Ix1 -> Bool) -> Bool -> ix -> Bool
forall ix a. Index ix => (a -> Ix1 -> a) -> a -> ix -> a
forall a. (a -> Ix1 -> a) -> a -> ix -> a
foldlIndex (\Bool
a Ix1
x -> Bool
a Bool -> Bool -> Bool
&& Ix1
x Ix1 -> Ix1 -> Bool
forall a. Ord a => a -> a -> Bool
> Ix1
0) Bool
True (Sz ix -> ix
forall ix. Sz ix -> ix
unSz Sz ix
sz)
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Iterators" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String
-> (Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"IterLinearM" ((Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property) -> Spec)
-> (Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
Index ix =>
Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property
prop_IterLinearM @ix
String
-> (Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"IterLinearM_" ((Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property) -> Spec)
-> (Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall ix.
Index ix =>
Sz ix -> NonNegative Ix1 -> Positive Ix1 -> Property
prop_IterLinearM_ @ix