{-# LANGUAGE TypeFamilies #-} module Data.Array.Comfort.Shape.Test (tests) where import qualified Data.Array.Comfort.Shape as Shape import Data.Tuple.HT (mapSnd) import qualified Test.QuickCheck as QC uncheckedSize :: (Shape.C sh) => sh -> Bool uncheckedSize :: sh -> Bool uncheckedSize sh sh = sh -> Int forall sh. C sh => sh -> Int Shape.size sh sh Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == sh -> Int forall sh. C sh => sh -> Int Shape.uncheckedSize sh sh inBounds :: (Shape.Indexed sh) => sh -> Bool inBounds :: sh -> Bool inBounds sh sh = (Index sh -> Bool) -> [Index sh] -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool all (sh -> Index sh -> Bool forall sh. Indexed sh => sh -> Index sh -> Bool Shape.inBounds sh sh) ([Index sh] -> Bool) -> [Index sh] -> Bool forall a b. (a -> b) -> a -> b $ sh -> [Index sh] forall sh. Indexed sh => sh -> [Index sh] Shape.indices sh sh forAllIndices :: (Shape.Indexed sh, Shape.Index sh ~ ix, Show ix, QC.Testable prop) => sh -> (ix -> prop) -> QC.Property forAllIndices :: sh -> (ix -> prop) -> Property forAllIndices sh sh ix -> prop f = let ixs :: [Index sh] ixs = sh -> [Index sh] forall sh. Indexed sh => sh -> [Index sh] Shape.indices sh sh in Bool -> Bool not ([ix] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool null [ix] [Index sh] ixs) Bool -> Property -> Property forall prop. Testable prop => Bool -> prop -> Property QC.==> Gen ix -> (ix -> prop) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll ([ix] -> Gen ix forall a. [a] -> Gen a QC.elements [ix] [Index sh] ixs) ix -> prop f sizeOffset :: (Shape.Indexed sh, Shape.Index sh ~ ix, Show ix) => sh -> QC.Property sizeOffset :: sh -> Property sizeOffset sh sh = sh -> (ix -> Bool) -> Property forall sh ix prop. (Indexed sh, Index sh ~ ix, Show ix, Testable prop) => sh -> (ix -> prop) -> Property forAllIndices sh sh ((ix -> Bool) -> Property) -> (ix -> Bool) -> Property forall a b. (a -> b) -> a -> b $ \ix ix -> ((ix -> Int) -> Int) -> (Int, ix -> Int) -> (Int, Int) forall b c a. (b -> c) -> (a, b) -> (a, c) mapSnd ((ix -> Int) -> ix -> Int forall a b. (a -> b) -> a -> b $ix ix) (sh -> (Int, Index sh -> Int) forall sh. Indexed sh => sh -> (Int, Index sh -> Int) Shape.sizeOffset sh sh) (Int, Int) -> (Int, Int) -> Bool forall a. Eq a => a -> a -> Bool == (sh -> Int forall sh. C sh => sh -> Int Shape.size sh sh, sh -> Index sh -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.offset sh sh ix Index sh ix) uncheckedSizeOffset :: (Shape.Indexed sh, Shape.Index sh ~ ix, Show ix) => sh -> QC.Property uncheckedSizeOffset :: sh -> Property uncheckedSizeOffset sh sh = sh -> (ix -> Bool) -> Property forall sh ix prop. (Indexed sh, Index sh ~ ix, Show ix, Testable prop) => sh -> (ix -> prop) -> Property forAllIndices sh sh ((ix -> Bool) -> Property) -> (ix -> Bool) -> Property forall a b. (a -> b) -> a -> b $ \ix ix -> ((ix -> Int) -> Int) -> (Int, ix -> Int) -> (Int, Int) forall b c a. (b -> c) -> (a, b) -> (a, c) mapSnd ((ix -> Int) -> ix -> Int forall a b. (a -> b) -> a -> b $ix ix) (sh -> (Int, Index sh -> Int) forall sh. Indexed sh => sh -> (Int, Index sh -> Int) Shape.uncheckedSizeOffset sh sh) (Int, Int) -> (Int, Int) -> Bool forall a. Eq a => a -> a -> Bool == (sh -> Int forall sh. C sh => sh -> Int Shape.uncheckedSize sh sh, sh -> Index sh -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.uncheckedOffset sh sh ix Index sh ix) uncheckedOffset :: (Shape.Indexed sh, Shape.Index sh ~ ix, Show ix) => sh -> QC.Property uncheckedOffset :: sh -> Property uncheckedOffset sh sh = sh -> (ix -> Bool) -> Property forall sh ix prop. (Indexed sh, Index sh ~ ix, Show ix, Testable prop) => sh -> (ix -> prop) -> Property forAllIndices sh sh ((ix -> Bool) -> Property) -> (ix -> Bool) -> Property forall a b. (a -> b) -> a -> b $ \ix ix -> sh -> Index sh -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.offset sh sh ix Index sh ix Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == sh -> Index sh -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.uncheckedOffset sh sh ix Index sh ix lengthIndices :: (Shape.Indexed sh) => sh -> Bool lengthIndices :: sh -> Bool lengthIndices sh sh = [Index sh] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length (sh -> [Index sh] forall sh. Indexed sh => sh -> [Index sh] Shape.indices sh sh) Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == sh -> Int forall sh. C sh => sh -> Int Shape.size sh sh indexOffsets :: (Shape.Indexed sh) => sh -> Bool indexOffsets :: sh -> Bool indexOffsets sh sh = (Index sh -> Int) -> [Index sh] -> [Int] forall a b. (a -> b) -> [a] -> [b] map (sh -> Index sh -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.offset sh sh) (sh -> [Index sh] forall sh. Indexed sh => sh -> [Index sh] Shape.indices sh sh) [Int] -> [Int] -> Bool forall a. Eq a => a -> a -> Bool == Int -> [Int] -> [Int] forall a. Int -> [a] -> [a] take (sh -> Int forall sh. C sh => sh -> Int Shape.size sh sh) [Int 0..] invIndices :: (Shape.InvIndexed sh, Shape.Index sh ~ ix, Eq ix) => sh -> Bool invIndices :: sh -> Bool invIndices sh sh = sh -> [Index sh] forall sh. Indexed sh => sh -> [Index sh] Shape.indices sh sh [ix] -> [ix] -> Bool forall a. Eq a => a -> a -> Bool == (Int -> ix) -> [Int] -> [ix] forall a b. (a -> b) -> [a] -> [b] map (sh -> Int -> Index sh forall sh. InvIndexed sh => sh -> Int -> Index sh Shape.indexFromOffset sh sh) (Int -> [Int] -> [Int] forall a. Int -> [a] -> [a] take (sh -> Int forall sh. C sh => sh -> Int Shape.size sh sh) [Int 0..]) uncheckedInvIndices :: (Shape.InvIndexed sh, Shape.Index sh ~ ix, Eq ix) => sh -> Bool uncheckedInvIndices :: sh -> Bool uncheckedInvIndices sh sh = sh -> [Index sh] forall sh. Indexed sh => sh -> [Index sh] Shape.indices sh sh [ix] -> [ix] -> Bool forall a. Eq a => a -> a -> Bool == (Int -> ix) -> [Int] -> [ix] forall a b. (a -> b) -> [a] -> [b] map (sh -> Int -> Index sh forall sh. InvIndexed sh => sh -> Int -> Index sh Shape.uncheckedIndexFromOffset sh sh) (Int -> [Int] -> [Int] forall a. Int -> [a] -> [a] take (sh -> Int forall sh. C sh => sh -> Int Shape.size sh sh) [Int 0..]) tests :: (Shape.InvIndexed sh, Show sh, Shape.Index sh ~ ix, Eq ix, Show ix) => QC.Gen sh -> [(String, QC.Property)] tests :: Gen sh -> [(String, Property)] tests Gen sh gen = (String "uncheckedSize", Gen sh -> (sh -> Bool) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Bool forall sh. C sh => sh -> Bool uncheckedSize) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "inBounds", Gen sh -> (sh -> Bool) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Bool forall sh. Indexed sh => sh -> Bool inBounds) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "sizeOffset", Gen sh -> (sh -> Property) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Property forall sh ix. (Indexed sh, Index sh ~ ix, Show ix) => sh -> Property sizeOffset) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "uncheckedSizeOffset", Gen sh -> (sh -> Property) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Property forall sh ix. (Indexed sh, Index sh ~ ix, Show ix) => sh -> Property uncheckedSizeOffset) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "uncheckedOffset", Gen sh -> (sh -> Property) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Property forall sh ix. (Indexed sh, Index sh ~ ix, Show ix) => sh -> Property uncheckedOffset) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "lengthIndices", Gen sh -> (sh -> Bool) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Bool forall sh. Indexed sh => sh -> Bool lengthIndices) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "indexOffsets", Gen sh -> (sh -> Bool) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Bool forall sh. Indexed sh => sh -> Bool indexOffsets) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "invIndices", Gen sh -> (sh -> Bool) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Bool forall sh ix. (InvIndexed sh, Index sh ~ ix, Eq ix) => sh -> Bool invIndices) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : (String "uncheckedInvIndices", Gen sh -> (sh -> Bool) -> Property forall a prop. (Show a, Testable prop) => Gen a -> (a -> prop) -> Property QC.forAll Gen sh gen sh -> Bool forall sh ix. (InvIndexed sh, Index sh ~ ix, Eq ix) => sh -> Bool uncheckedInvIndices) (String, Property) -> [(String, Property)] -> [(String, Property)] forall a. a -> [a] -> [a] : []