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.Dynamic.Tensor.Math

Description

Torch provides MATLAB-like functions for manipulating Tensor objects. Functions fall into several types of categories:

  • Constructors like zeros, ones;
  • Extractors like diag and triu;
  • Element-wise mathematical operations like abs and pow;
  • BLAS operations;
  • Column or row-wise operations like sum and max;
  • Matrix-wide operations like trace and norm;
  • Convolution and cross-correlation operations like conv2;
  • Basic linear algebra operations like eig;
  • Logical operations on Tensors.

Unfortunately the above this comes from the Lua docs. Hasktorch doesn't mimic this exactly and (FIXME) we will have to restructure this module header to reflect these changes.

Synopsis

Documentation

fill_ :: Dynamic -> HsReal -> IO () Source #

fill a dynamic tensor, inplace, with the given value.

zero_ :: Dynamic -> IO () Source #

mutate a tensor, inplace, filling it with zero values.

zeros_ :: Dynamic -> IndexStorage -> IO () Source #

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

zerosLike_ Source #

Arguments

:: Dynamic

tensor to mutate inplace and replace contents with zeros

-> Dynamic

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_ :: Dynamic -> IndexStorage -> IO () Source #

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

onesLike_ Source #

Arguments

:: Dynamic

tensor to mutate inplace and replace contents with ones

-> Dynamic

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 :: Dynamic -> Integer Source #

returns the count of the number of elements in the matrix.

_reshape :: Dynamic -> Dynamic -> IndexStorage -> IO () Source #

  _reshape y x (Ix.newStorage [m, n, k, l, o])

Mutates the y dynamic tensor to be reshaped as a m × n × k × l × o tensor whose elements are taken rowwise from x, which must have m * n * k * l * o elements. The elements are copied into the new Tensor.

_catArray Source #

Arguments

:: Dynamic

result to mutate

-> NonEmpty Dynamic

tensors to concatenate

-> Word

dimension to concatenate along.

-> IO () 

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.

C-Style: In the classic Torch C-style, the first argument is treated as the return type and is mutated in-place.

_tril :: Dynamic -> Dynamic -> Integer -> IO () Source #

"Get the lower triangle of a tensor."

Mutates the first tensor to have the triangular part of the second tensor under the Kth diagonal. where k=0 is the main diagonal, k>0 is above the main diagonal, and k<0 is below the main diagonal. All other elements are set to 0.

C-Style: In the classic Torch C-style, the first argument is treated as the return type and is mutated in-place.

_triu :: Dynamic -> Dynamic -> Integer -> IO () Source #

"Get the upper triangle of a tensor."

Mutates the first tensor to have the triangular part of the second tensor above the Kth diagonal. where k=0 is the main diagonal, k>0 is above the main diagonal, and k<0 is below the main diagonal. All other elements are set to 0.

C-Style: In the classic Torch C-style, the first argument is treated as the return type and is mutated in-place.

_cat Source #

Arguments

:: Dynamic 
-> Dynamic 
-> Dynamic 
-> Word

dimension to concatenate along

-> IO () 

Concatinate two dynamic tensors along the specified dimension, treating the first argument as the return tensor, to be mutated in-place.

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.

C-Style: In the classic Torch C-style, the first argument is treated as the return type and is mutated in-place.

cat :: Dynamic -> Dynamic -> Word -> Either String Dynamic Source #

pure version of _cat

_nonzero :: IndexDynamic -> Dynamic -> IO () Source #

Finds and returns a LongTensor corresponding to the subscript indices of all non-zero elements in tensor.

C-Style: In the classic Torch C-style, the first argument is treated as the return type and is mutated in-place.

ttrace :: Dynamic -> 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.

eye_ Source #

Arguments

:: Dynamic

tensor to mutate inplace

-> Integer

n dimension in an n × m matrix

-> Integer

m dimension in an n × m matrix

-> IO () 

mutates a tensor to be an n × m identity matrix with ones on the diagonal and zeros elsewhere.

_arange :: Dynamic -> HsAccReal -> HsAccReal -> HsAccReal -> IO () Source #

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

arange :: HsAccReal -> HsAccReal -> HsAccReal -> Dynamic Source #

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

range_ Source #

Arguments

:: Dynamic

tensor to mutate

-> HsAccReal

min value

-> HsAccReal

max value

-> HsAccReal

step size

-> IO () 

mutate a Tensor inplace, filling it with values from min to max with step. Will make the tensor take a shape of size floor((y - x) / step) + 1.

range :: Dims (d :: [Nat]) -> HsAccReal -> HsAccReal -> HsAccReal -> Dynamic Source #

pure version of range_

constant :: Dims (d :: [Nat]) -> HsReal -> Dynamic Source #

create a Dynamic tensor with a given dimension and value

We can get away unsafePerformIO this as constant is pure and thread-safe

_diag :: Dynamic -> Dynamic -> Int -> IO () Source #

direct call to the C-FFI of diag, mutating the first tensor argument with the data from the remaining aruments.

diag_ :: Dynamic -> Int -> IO () Source #

mutates the tensor inplace and replaces it with the given k-th diagonal, where k=0 is the main diagonal, k>0 is above the main diagonal, and k<0 is below the main diagonal.

diag :: Dynamic -> Int -> Dynamic Source #

returns the k-th diagonal of the input tensor, where k=0 is the main diagonal, k>0 is above the main diagonal, and k<0 is below the main diagonal.

diag1d :: Dynamic -> Dynamic Source #

returns a diagonal matrix with diagonal elements constructed from the input tensor

_tenLike :: (Dynamic -> Dynamic -> IO ()) -> Dims (d :: [Nat]) -> IO Dynamic Source #

Warning: this should not be exported outside of hasktorch

helper function for onesLike and zerosLike

onesLike :: Dims (d :: [Nat]) -> Dynamic Source #

pure version of onesLike_

zerosLike :: Dims (d :: [Nat]) -> Dynamic Source #

pure version of zerosLike_