testing-tensor-0.1.0: Pure implementation of tensors, for use in tests.
Safe HaskellSafe-Inferred
LanguageGHC2021

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

Definition

data Tensor n a where Source #

Constructors

Scalar :: a -> Tensor Z a 
Tensor :: [Tensor n a] -> Tensor (S n) a 

Instances

Instances details
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 shrink (or shrinkWith directly) might result in faster shrinking.

Instance details

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 # 
Instance details

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 #

toList :: Tensor n a -> [a] #

null :: Tensor n a -> Bool #

length :: Tensor n a -> Int #

elem :: Eq a => a -> Tensor n a -> Bool #

maximum :: Ord a => Tensor n a -> a #

minimum :: Ord a => Tensor n a -> a #

sum :: Num a => Tensor n a -> a #

product :: Num a => Tensor n a -> a #

Traversable (Tensor n) Source # 
Instance details

Defined in Test.Tensor

Methods

traverse :: Applicative f => (a -> f b) -> Tensor n a -> f (Tensor n b) #

sequenceA :: Applicative f => Tensor n (f a) -> f (Tensor n a) #

mapM :: Monad m => (a -> m b) -> Tensor n a -> m (Tensor n b) #

sequence :: Monad m => Tensor n (m a) -> m (Tensor n a) #

Functor (Tensor n) Source # 
Instance details

Defined in Test.Tensor

Methods

fmap :: (a -> b) -> Tensor n a -> Tensor n b #

(<$) :: a -> Tensor n b -> Tensor n a #

(SNatI n, Arbitrary a, Num a, Eq a) => Arbitrary (Tensor n a) Source # 
Instance details

Defined in Test.Tensor

Methods

arbitrary :: Gen (Tensor n a) #

shrink :: Tensor n a -> [Tensor n a] #

Show a => Show (Tensor n a) Source # 
Instance details

Defined in Test.Tensor

Methods

showsPrec :: Int -> Tensor n a -> ShowS #

show :: Tensor n a -> String #

showList :: [Tensor n a] -> ShowS #

Eq a => Eq (Tensor n a) Source # 
Instance details

Defined in Test.Tensor

Methods

(==) :: Tensor n a -> Tensor n a -> Bool #

(/=) :: Tensor n a -> Tensor n a -> Bool #

getTensor :: Tensor (S n) a -> [Tensor n a] Source #

Convenience constructors

dim1 :: [a] -> Tensor Nat1 a Source #

dim2 :: [[a]] -> Tensor Nat2 a Source #

dim3 :: [[[a]]] -> Tensor Nat3 a Source #

dim4 :: [[[[a]]]] -> Tensor Nat4 a Source #

dim5 :: [[[[[a]]]]] -> Tensor Nat5 a Source #

dim6 :: [[[[[[a]]]]]] -> Tensor Nat6 a Source #

dim7 :: [[[[[[[a]]]]]]] -> Tensor Nat7 a Source #

dim8 :: [[[[[[[[a]]]]]]]] -> Tensor Nat8 a Source #

dim9 :: [[[[[[[[[a]]]]]]]]] -> Tensor Nat9 a Source #

Size

type Size n = Vec n Int Source #

size :: Tensor n a -> Size n Source #

Analogue of length

sizeAtLeast :: Size n -> Tensor n a -> Bool Source #

Check that each dimension has at least the specified size

Standard operations

zipWith :: (a -> b -> c) -> Tensor n a -> Tensor n b -> Tensor n c Source #

Analogue of zipWith

replicate :: Size n -> a -> Tensor n a Source #

Analogue of replicate

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

convolve Source #

Arguments

:: (SNatI n, Num a) 
=> Tensor n a

Kernel

-> Tensor n a

Input

-> Tensor n a 

Convolution

See padWith for adjusting boundary conditions.

convolveWithStride Source #

Arguments

:: forall n a. Num a 
=> Vec n Int

Stride

-> Tensor n a

Kernel

-> Tensor n a

Input

-> Tensor n a 

Generalization of convolve when using a non-default stride

padWith :: SNatI n => a -> Int -> Tensor n a -> Tensor n a Source #

Add uniform padding

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

type family Lists n a where ... Source #

Equations

Lists Z a = a 
Lists (S n) a = [Lists n a] 

toLists :: Tensor n a -> Lists n a Source #

fromLists :: SNatI n => Lists n a -> Tensor n a Source #

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

shrinkWith Source #

Arguments

:: Maybe (Zero a)

Optional zero element (see shrinkElem)

-> (a -> [a])

Shrink individual elements

-> Tensor n a 
-> [Tensor n a] 

Shrink tensor

shrinkWith' Source #

Arguments

:: forall n a. [Axe n]

Shrink the size of the tensor (see allAxes)

-> Maybe (Zero a)

Optional zero element (see shrinkElem)

-> (a -> [a])

Shrink elements of the tensor

-> Tensor n a 
-> [Tensor n a] 

Generalization of shrinkWith

shrinkElem Source #

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 (offset, length) pair.

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

Instances

Instances details
Show (Axe n) Source # 
Instance details

Defined in Test.Tensor

Methods

showsPrec :: Int -> Axe n -> ShowS #

show :: Axe n -> String #

showList :: [Axe n] -> ShowS #

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

data Zero a where Source #

Zero element

Constructors

Zero :: Eq a => a -> Zero a 

zero :: (Num a, Eq a) => Zero a Source #

Default Zero

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