Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Test.Tensor
Description
Tensors (n-dimensional arrays)
This is an implementation of tensors that emphasizes simplicify above all; it is meant for use in QuickCheck tests.
Intended for qualified import.
import Test.Tensor (Tensor) import Test.Tensor qualified as Tensor
Synopsis
- data Tensor n a where
- getScalar :: Tensor Z a -> a
- getTensor :: Tensor (S n) a -> [Tensor n a]
- scalar :: a -> Tensor Nat0 a
- dim1 :: [a] -> Tensor Nat1 a
- dim2 :: [[a]] -> Tensor Nat2 a
- dim3 :: [[[a]]] -> Tensor Nat3 a
- dim4 :: [[[[a]]]] -> Tensor Nat4 a
- dim5 :: [[[[[a]]]]] -> Tensor Nat5 a
- dim6 :: [[[[[[a]]]]]] -> Tensor Nat6 a
- dim7 :: [[[[[[[a]]]]]]] -> Tensor Nat7 a
- dim8 :: [[[[[[[[a]]]]]]]] -> Tensor Nat8 a
- dim9 :: [[[[[[[[[a]]]]]]]]] -> Tensor Nat9 a
- type Size n = Vec n Int
- size :: Tensor n a -> Size n
- sizeAtLeast :: Size n -> Tensor n a -> Bool
- zipWith :: (a -> b -> c) -> Tensor n a -> Tensor n b -> Tensor n c
- replicate :: Size n -> a -> Tensor n a
- rotate :: Tensor n a -> Tensor n a
- distrib :: [Tensor n a] -> Tensor n [a]
- transpose :: Tensor Nat2 a -> Tensor Nat2 a
- foreach :: Tensor (S n) a -> (Tensor n a -> Tensor m b) -> Tensor (S m) b
- foreachWith :: Tensor (S n) a -> [x] -> (Tensor n a -> x -> Tensor m b) -> Tensor (S m) b
- subs :: SNatI n => Size n -> Tensor n a -> Tensor n (Tensor n a)
- subsWithStride :: Vec n Int -> Size n -> Tensor n a -> Tensor n (Tensor n a)
- convolve :: (SNatI n, Num a) => Tensor n a -> Tensor n a -> Tensor n a
- convolveWithStride :: forall n a. Num a => Vec n Int -> Tensor n a -> Tensor n a -> Tensor n a
- padWith :: SNatI n => a -> Int -> Tensor n a -> Tensor n a
- padWith' :: forall n a. a -> Vec n (Int, Int) -> Tensor n a -> Tensor n a
- type family Lists n a where ...
- toLists :: Tensor n a -> Lists n a
- fromLists :: SNatI n => Lists n a -> Tensor n a
- fromList :: forall n a. Size n -> [a] -> Tensor n a
- arbitraryOfSize :: Size n -> Gen a -> Gen (Tensor n a)
- shrinkWith :: Maybe (Zero a) -> (a -> [a]) -> Tensor n a -> [Tensor n a]
- shrinkWith' :: forall n a. [Axe n] -> Maybe (Zero a) -> (a -> [a]) -> Tensor n a -> [Tensor n a]
- shrinkElem :: forall n a. Maybe (Zero a) -> (a -> [a]) -> Tensor n a -> [Tensor n a]
- data Axe (n :: Nat) where
- allAxes :: Size n -> [Axe n]
- axeWith :: Axe n -> Tensor n a -> Tensor n a
- axeSize :: Size n -> Axe n -> Int
- data Zero a where
- zero :: (Num a, Eq a) => Zero a
- zeroWith :: forall n a. Zero a -> Axe n -> Tensor n a -> Maybe (Tensor n a)
- toStorable :: Storable a => Tensor n a -> Vector a
- fromStorable :: (HasCallStack, Storable a) => Size n -> Vector a -> Tensor n a
- unsafeWithCArray :: Storable a => Tensor n a -> (Ptr a -> IO r) -> IO r
- unsafeFromCArray :: Storable a => Size n -> ForeignPtr a -> Tensor n a
- unsafeFromPrealloc :: Storable a => Size n -> (Ptr a -> IO r) -> IO (Tensor n a, r)
- unsafeFromPrealloc_ :: Storable a => Size n -> (Ptr a -> IO ()) -> IO (Tensor n a)
Definition
data Tensor n a where Source #
Instances
SNatI n => Arbitrary1 (Tensor n) Source # | Lift generators and shrinkers NOTE: Since we cannot put any constraints on the type of the elements here,
we cannot use any zero elements. Using |
Defined in Test.Tensor Methods liftArbitrary :: Gen a -> Gen (Tensor n a) # liftShrink :: (a -> [a]) -> Tensor n a -> [Tensor n a] # | |
Foldable (Tensor n) Source # | |
Defined in Test.Tensor Methods fold :: Monoid m => Tensor n m -> m # foldMap :: Monoid m => (a -> m) -> Tensor n a -> m # foldMap' :: Monoid m => (a -> m) -> Tensor n a -> m # foldr :: (a -> b -> b) -> b -> Tensor n a -> b # foldr' :: (a -> b -> b) -> b -> Tensor n a -> b # foldl :: (b -> a -> b) -> b -> Tensor n a -> b # foldl' :: (b -> a -> b) -> b -> Tensor n a -> b # foldr1 :: (a -> a -> a) -> Tensor n a -> a # foldl1 :: (a -> a -> a) -> Tensor n a -> a # elem :: Eq a => a -> Tensor n a -> Bool # maximum :: Ord a => Tensor n a -> a # minimum :: Ord a => Tensor n a -> a # | |
Traversable (Tensor n) Source # | |
Functor (Tensor n) Source # | |
(SNatI n, Arbitrary a, Num a, Eq a) => Arbitrary (Tensor n a) Source # | |
Show a => Show (Tensor n a) Source # | |
Eq a => Eq (Tensor n a) Source # | |
Convenience constructors
Size
sizeAtLeast :: Size n -> Tensor n a -> Bool Source #
Check that each dimension has at least the specified size
Standard operations
rotate :: Tensor n a -> Tensor n a Source #
Analogue of reverse
This amounts to a 180 degrees rotation of the tensor.
distrib :: [Tensor n a] -> Tensor n [a] Source #
Distribute '[]' over Tensor
Collects values in corresponding in all tensors.
transpose :: Tensor Nat2 a -> Tensor Nat2 a Source #
Transpose
This is essentially a special case of distrib
.
foreach :: Tensor (S n) a -> (Tensor n a -> Tensor m b) -> Tensor (S m) b Source #
Map element over the first dimension of the tensor
foreachWith :: Tensor (S n) a -> [x] -> (Tensor n a -> x -> Tensor m b) -> Tensor (S m) b Source #
Variation of foreach
with an auxiliary list
Subtensors
subs :: SNatI n => Size n -> Tensor n a -> Tensor n (Tensor n a) Source #
Subtensors of the specified size
subsWithStride :: Vec n Int -> Size n -> Tensor n a -> Tensor n (Tensor n a) Source #
Generalization of subs
with non-default stride
Convolution
See padWith
for adjusting boundary conditions.
Generalization of convolve
when using a non-default stride
padWith' :: forall n a. a -> Vec n (Int, Int) -> Tensor n a -> Tensor n a Source #
Generalization of padWith
with different padding per dimension
Conversions
fromList :: forall n a. Size n -> [a] -> Tensor n a Source #
Inverse to toList
Throws a pure exception if the list does not contain enough elements.
QuickCheck support
Generation
Shrinking
Arguments
:: Maybe (Zero a) | Optional zero element (see |
-> (a -> [a]) | Shrink individual elements |
-> Tensor n a | |
-> [Tensor n a] |
Shrink tensor
Arguments
:: forall n a. [Axe n] | Shrink the size of the tensor (see |
-> Maybe (Zero a) | Optional zero element (see |
-> (a -> [a]) | Shrink elements of the tensor |
-> Tensor n a | |
-> [Tensor n a] |
Generalization of shrinkWith
Arguments
:: forall n a. Maybe (Zero a) | Optional zero element |
-> (a -> [a]) | Shrink individual elements |
-> Tensor n a | |
-> [Tensor n a] |
Shrink an element of the tensor, leaving the size of the tensor unchanged
If a zero element is specified, we will first try to replace entire regions of the tensor by zeroes; this can dramatically speed up shrinking.
Axes
data Axe (n :: Nat) where Source #
Constructors
AxeHere :: (Int, Int) -> Axe (S n) | Axe some elements from the current dimension We record which elements to drop as an |
AxeNested :: Axe n -> Axe (S n) | Axe some elements from a nested dimension In order to keep the tensor square, we must apply the same axe for every element of the current dimension |
allAxes :: Size n -> [Axe n] Source #
All possible ways to axe some elements
This is adopted from the implementation of shrinkList
(in a way, an Axe
is an explanation of the decisions made by shrinkList
, generalized to
multiple dimensions).
Axes are sorted to remove as many elements as early as possible.
axeWith :: Axe n -> Tensor n a -> Tensor n a Source #
Remove elements from the tensor (shrink dimensions)
axeSize :: Size n -> Axe n -> Int Source #
How many elements are removed by this axe?
Examples:
axeSize (2 ::: 100 ::: VNil) (AxeHere (0, 1)) == 100 axeSize (2 ::: 100 ::: VNil) (AxeNested (AxeHere (0, 99))) == 198
Zeroing
zeroWith :: forall n a. Zero a -> Axe n -> Tensor n a -> Maybe (Tensor n a) Source #
Zero elements in the tensor (leaving dimensions the same)
Returns Nothing
if the specified region was already zero everywhere.
FFI
toStorable :: Storable a => Tensor n a -> Vector a Source #
Translate to storable vector
The tensor is laid out in order specified (outer dimensions before inner).
fromStorable :: (HasCallStack, Storable a) => Size n -> Vector a -> Tensor n a Source #
Translate from storable vector
Throws an exception if the vector does not contain enough elements.
unsafeWithCArray :: Storable a => Tensor n a -> (Ptr a -> IO r) -> IO r Source #
Get pointer to elements of the tensor
See toStorable
for discussion of the layout.
The data should not be modified through the pointer, and the pointer should not be used outside its scope.
unsafeFromCArray :: Storable a => Size n -> ForeignPtr a -> Tensor n a Source #
Construct tensor from C array
The data should not be modified through the pointer after the tensor has been constructed.
unsafeFromPrealloc :: Storable a => Size n -> (Ptr a -> IO r) -> IO (Tensor n a, r) Source #
Construct tensor from preallocated C array
Allocates sufficient memory to hold the elements of the tensor; writing more data will result in invalid memory access. The pointer should not be used outside its scope.
unsafeFromPrealloc_ :: Storable a => Size n -> (Ptr a -> IO ()) -> IO (Tensor n a) Source #
Like unsafeFromPrealloc
but without an additional return value