hasktorch-indef-0.0.1.0: Core Hasktorch abstractions wrapping FFI bindings

Copyright(c) Sam Stites 2017
LicenseBSD3
Maintainersam@stites.io
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Torch.Indef.Static.Tensor.Math

Description

 
Synopsis

Documentation

fill_ :: Tensor d -> HsReal -> IO () Source #

Static call to fill_

zero_ :: Tensor d -> IO () Source #

Static call to zero_

zeros_ :: Tensor d -> IndexStorage -> IO () Source #

mutate a tensor, inplace, resizing the tensor to the given IndexStorage size and replacing its value with zeros.

zerosLike_ Source #

Arguments

:: Tensor d

tensor to mutate inplace and replace contents with zeros

-> Tensor d'

tensor to extract shape information from.

-> IO () 

mutate a tensor, inplace, resizing the tensor to the same shape as the second tensor argument and replacing the first tensor's values with zeros.

ones_ :: Tensor d -> IndexStorage -> IO () Source #

mutate a tensor, inplace, resizing the tensor to the given IndexStorage size and replacing its value with ones.

onesLike_ Source #

Arguments

:: Tensor d

tensor to mutate inplace and replace contents with ones

-> Tensor d'

tensor to extract shape information from.

-> IO () 

mutate a tensor, inplace, resizing the tensor to the same shape as the second tensor argument and replacing the first tensor's values with ones.

numel :: Tensor d -> Integer Source #

Static call to numel

_reshape :: Tensor d1 -> Tensor d2 -> IndexStorage -> IO () Source #

Static call to _reshape

_catArray :: Tensor d -> NonEmpty Dynamic -> Word -> IO () Source #

Static call to _catArray

_nonzero :: LongTensor d1 -> Tensor d2 -> IO () Source #

Static call to _nonzero

_tril :: Tensor d1 -> Tensor d2 -> Integer -> IO () Source #

Static call to _tril

_triu :: Tensor d1 -> Tensor d2 -> Integer -> IO () Source #

Static call to _triu

eye_ :: Tensor d -> Integer -> Integer -> IO () Source #

Static call to eye_

ttrace :: Tensor d -> HsAccReal Source #

Returns the trace (sum of the diagonal elements) of a matrix x. This is equal to the sum of the eigenvalues of x.

Static call to ttrace

_arange :: Tensor d -> HsAccReal -> HsAccReal -> HsAccReal -> IO () Source #

Identical to a direct C call to the arange, or range with special consideration for floating precision types. Static call to _arange

range_ :: Tensor d -> HsAccReal -> HsAccReal -> HsAccReal -> IO () Source #

Static call to range_

constant :: forall d. Dimensions d => HsReal -> Tensor d Source #

Static call to constant

diag_ :: All Dimensions '[d, d'] => Tensor d -> Int -> IO (Tensor d') Source #

Static call to diag_

diag :: All Dimensions '[d, d'] => Tensor d -> Int -> Tensor d' Source #

Static call to diag

diag1d :: KnownDim n => Tensor '[n] -> Tensor '[n, n] Source #

Create a diagonal matrix from a 1D vector

cat_ :: All Dimensions '[d, d', d''] => Tensor d -> Tensor d' -> Word -> IO (Tensor d'') Source #

Warning: this function is impure and the dimensions can fall out of sync with the type, if used incorrectly

Static call to cat_. Unsafely returning the resulting tensor with new dimensions.

cat :: '(ls, r0 :+ rs) ~ SplitAt i d => '(ls, r1 :+ rs) ~ SplitAt i d' => Tensor d -> Tensor d' -> Dim (i :: Nat) -> Tensor (ls ++ ('[r0 + r1] ++ rs)) Source #

Static call to cat

cat1d :: (All KnownDim '[n1, n2, n], n ~ Sum [n1, n2]) => Tensor '[n1] -> Tensor '[n2] -> Tensor '[n] Source #

convenience function, specifying a type-safe cat operation.

cat2d0 :: (All KnownDim '[n, m, n0, n1], n ~ Sum [n0, n1]) => Tensor '[n0, m] -> Tensor '[n1, m] -> Tensor '[n, m] Source #

convenience function, specifying a type-safe cat operation.

stack1d0 :: KnownDim m => Tensor '[m] -> Tensor '[m] -> Tensor '[2, m] Source #

convenience function, stack two rank-1 tensors along the 0-dimension

cat2d1 :: (All KnownDim '[n, m, m0, m1], m ~ Sum [m0, m1]) => Tensor '[n, m0] -> Tensor '[n, m1] -> Tensor '[n, m] Source #

convenience function, specifying a type-safe cat operation.

stack1d1 :: KnownDim n => Tensor '[n] -> Tensor '[n] -> Tensor '[n, 2] Source #

convenience function, stack two rank-1 tensors along the 1-dimension

cat3d0 :: (All KnownDim '[x, y, x0, x1, z], x ~ Sum [x0, x1]) => Tensor '[x0, y, z] -> Tensor '[x1, y, z] -> Tensor '[x, y, z] Source #

convenience function, specifying a type-safe cat operation.

cat3d1 :: (All KnownDim '[x, y, y0, y1, z], y ~ Sum [y0, y1]) => Tensor '[x, y0, z] -> Tensor '[x, y1, z] -> Tensor '[x, y, z] Source #

convenience function, specifying a type-safe cat operation.

cat3d2 :: (All KnownDim '[x, y, z0, z1, z], z ~ Sum [z0, z1]) => Tensor '[x, y, z0] -> Tensor '[x, y, z1] -> Tensor '[x, y, z] Source #

convenience function, specifying a type-safe cat operation.

catArray :: Dimensions d => NonEmpty Dynamic -> Word -> Either String (Tensor d) Source #

Concatenate all tensors in a given list of dynamic tensors along the given dimension.

NOTE: In C, if the dimension is not specified or if it is -1, it is the maximum last dimension over all input tensors, except if all tensors are empty, then it is 1.

catArray' :: forall d ls rs r0 r1 i. Dimensions d => '(ls, r0 :+ rs) ~ SplitAt i d => d ~ (ls ++ ('[r0] ++ rs)) => (forall _i. NonEmpty (Tensor (ls ++ ('[_i] ++ rs)))) -> Dim i -> Either String (Tensor d) Source #

Concatenate all tensors in a given list of dynamic tensors along the given dimension. -- -- NOTE: In C, if the dimension is not specified or if it is -1, it is the maximum -- last dimension over all input tensors, except if all tensors are empty, then it is 1. catArray0 :: forall d ls rs r0 r1 i . Dimensions d => '([], r0:+rs) ~ Sing.SplitAt i d => (forall _i . [Tensor (_i+:rs)]) -> IO (Tensor (r0+:rs)) catArray0 ts dv = catArray (asDynamic $ ts) (dimVal dv)

Concatenate all tensors in a given list of dynamic tensors along the given dimension.

NOTE: In C, if the dimension is not specified or if it is -1, it is the maximum last dimension over all input tensors, except if all tensors are empty, then it is 1.

catArray0 :: (Dimensions d, Dimensions d2) => NonEmpty (Tensor d2) -> Either String (Tensor d) Source #

onesLike :: forall d. Dimensions d => Tensor d Source #

Static call to onesLike

zerosLike :: forall d. Dimensions d => Tensor d Source #

Static call to zerosLike