| Copyright | (c) Sam Stites 2017 |
|---|---|
| License | BSD3 |
| Maintainer | sam@stites.io |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Torch.Indef.Static.Tensor.Math.Blas
Description
Synopsis
- addmv :: All KnownDim '[r, c] => HsReal -> Tensor '[r] -> HsReal -> Tensor '[r, c] -> Tensor '[c] -> Tensor '[r]
- addmv_ :: All KnownDim '[r, c] => HsReal -> Tensor '[r] -> HsReal -> Tensor '[r, c] -> Tensor '[c] -> IO ()
- mv :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[c] -> Tensor '[r]
- (!*) :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[c] -> Tensor '[r]
- addmm :: All KnownDim '[a, b, c] => HsReal -> Tensor '[a, c] -> HsReal -> Tensor '[a, b] -> Tensor '[b, c] -> Tensor '[a, c]
- addmm_ :: All KnownDim '[a, b, c] => HsReal -> Tensor '[a, c] -> HsReal -> Tensor '[a, b] -> Tensor '[b, c] -> IO ()
- mmult :: All KnownDim '[a, b, c] => Tensor '[a, b] -> Tensor '[b, c] -> Tensor '[a, c]
- (!*!) :: All KnownDim '[a, b, c] => Tensor '[a, b] -> Tensor '[b, c] -> Tensor '[a, c]
- addr :: All KnownDim '[r, c] => HsReal -> Tensor '[r, c] -> HsReal -> Tensor '[r] -> Tensor '[c] -> Tensor '[r, c]
- addr_ :: All KnownDim '[r, c] => HsReal -> Tensor '[r, c] -> HsReal -> Tensor '[r] -> Tensor '[c] -> IO ()
- outer :: forall t r c. All KnownDim '[r, c] => Tensor '[r] -> Tensor '[c] -> Tensor '[r, c]
- addbmm :: All KnownDim '[n, p, b, m] => HsReal -> Tensor '[n, p] -> HsReal -> Tensor '[b, n, m] -> Tensor '[b, m, p] -> Tensor '[n, p]
- addbmm_ :: All KnownDim '[n, p, b, m] => HsReal -> Tensor '[n, p] -> HsReal -> Tensor '[b, n, m] -> Tensor '[b, m, p] -> IO ()
- baddbmm :: All KnownDim '[n, p, b, m] => HsReal -> Tensor '[b, n, p] -> HsReal -> Tensor '[b, n, m] -> Tensor '[b, m, p] -> Tensor '[b, n, p]
- baddbmm_ :: All KnownDim '[n, p, b, m] => HsReal -> Tensor '[b, n, p] -> HsReal -> Tensor '[b, n, m] -> Tensor '[b, m, p] -> IO ()
- dot :: All Dimensions '[d, d'] => Tensor d -> Tensor d' -> HsAccReal
- (<.>) :: All Dimensions '[d, d'] => Tensor d -> Tensor d' -> HsAccReal
Documentation
Arguments
| :: All KnownDim '[r, c] | |
| => HsReal | v1 |
| -> Tensor '[r] | vec1 |
| -> HsReal | v2 |
| -> Tensor '[r, c] | mat |
| -> Tensor '[c] | vec2 |
| -> Tensor '[r] | res |
Performs a matrix-vector multiplication between mat (2D Tensor) and vec2
(1D Tensor) and add it to vec1.
Values v1 and v2 are scalars that multiply vec1 and vec2 respectively.
They are optional in C and we may be able to add this to the API in the future.
In other words,
res = (v1 * vec1) + (v2 * (mat * vec2))
Sizes must respect the matrix-multiplication operation: if mat is a n × m
matrix, vec2 must be vector of size m and vec1 must be a vector of size
n.
Arguments
| :: All KnownDim '[r, c] | |
| => HsReal | v1 |
| -> Tensor '[r] | vec1 |
| -> HsReal | v2 |
| -> Tensor '[r, c] | mat |
| -> Tensor '[c] | vec2 |
| -> IO () |
Inline version of addmv, mutating vec1 inplace.
mv :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[c] -> Tensor '[r] Source #
added simplified use of addmv: src1 #> src2
(!*) :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[c] -> Tensor '[r] Source #
inline version of mv
Arguments
| :: All KnownDim '[a, b, c] | |
| => HsReal | v1 |
| -> Tensor '[a, c] | M |
| -> HsReal | v2 |
| -> Tensor '[a, b] | mat1 |
| -> Tensor '[b, c] | mat2 |
| -> Tensor '[a, c] | res |
Performs a matrix-matrix multiplication between mat1 (2D Tensor) and mat2 (2D Tensor).
Values v1 and v2 are scalars that multiply M and mat1 * mat2 respectively.
They are optional in C and we may be able to add this to the API in the future.
In other words,
res = (v1 * M) + (v2 * mat1 * mat2)
If mat1 is a n × m matrix, mat2 a m × p matrix, M must be a n × p matrix.
Arguments
| :: All KnownDim '[a, b, c] | |
| => HsReal | v1 |
| -> Tensor '[a, c] | M |
| -> HsReal | v2 |
| -> Tensor '[a, b] | mat1 |
| -> Tensor '[b, c] | mat2 |
| -> IO () |
Inline version of addmm, mutating M inplace.
mmult :: All KnownDim '[a, b, c] => Tensor '[a, b] -> Tensor '[b, c] -> Tensor '[a, c] Source #
simplified wrapper of addmm
FIXME: see if we can pass a null pointer in as the constant value (which might eliminate a noop linear pass).
(!*!) :: All KnownDim '[a, b, c] => Tensor '[a, b] -> Tensor '[b, c] -> Tensor '[a, c] Source #
infix mmult
Arguments
| :: All KnownDim '[r, c] | |
| => HsReal | v1 |
| -> Tensor '[r, c] | mat_ij |
| -> HsReal | v2 |
| -> Tensor '[r] | vec1_i |
| -> Tensor '[c] | vec2_j |
| -> Tensor '[r, c] | res_ij |
Performs the outer-product between vec1 (1D Tensor) and vec2
(1D Tensor).
Values v1 and v2 are scalars that multiply mat_ij and vec1_i [out] vec2_j respectively.
They are optional in C and we may be able to add this to the API in the future.
Thus:
res_ij = (v1 * mat_ij) + (v2 * vec1_i * vec2_j)
If vec1_ is a vector of size i and vec2_j is a vector of size j, then
mat_ij must be a matrix of size i × j.
Arguments
| :: All KnownDim '[r, c] | |
| => HsReal | v1 |
| -> Tensor '[r, c] | mat_ij -- mutated inplace |
| -> HsReal | v2 |
| -> Tensor '[r] | vec1_i |
| -> Tensor '[c] | vec2_j |
| -> IO () |
Inline version of addr, mutating mat_ij in-place.
outer :: forall t r c. All KnownDim '[r, c] => Tensor '[r] -> Tensor '[c] -> Tensor '[r, c] Source #
addr with the parameters for an outer product filled in.
Arguments
| :: All KnownDim '[n, p, b, m] | |
| => HsReal | v1 |
| -> Tensor '[n, p] | M |
| -> HsReal | v2 |
| -> Tensor '[b, n, m] | batch1_i |
| -> Tensor '[b, m, p] | batch2_i |
| -> Tensor '[n, p] | res |
Batch matrix-matrix product of matrices stored in batch1 and batch2,
with a reduced add step (all matrix multiplications get accumulated in
a single place).
batch1 and batch2 must be 3D Tensors each containing the same number
of matrices. If batch1 is a b × n × m Tensor, batch2 a b × m × p
Tensor, res will be a n × p Tensor.
In other words,
res = (v1 * M) + (v2 * sum(batch1_i * batch2_i, i = 1, b))
Arguments
| :: All KnownDim '[n, p, b, m] | |
| => HsReal | v1 |
| -> Tensor '[n, p] | M -- mutated inplace |
| -> HsReal | v2 |
| -> Tensor '[b, n, m] | batch1_i |
| -> Tensor '[b, m, p] | batch2_i |
| -> IO () |
Inline version of addbmm, mutating M in-place.
Arguments
| :: All KnownDim '[n, p, b, m] | |
| => HsReal | v1 |
| -> Tensor '[b, n, p] | M_i |
| -> HsReal | v2 |
| -> Tensor '[b, n, m] | batch1_i |
| -> Tensor '[b, m, p] | batch2_i |
| -> Tensor '[b, n, p] | res_i |
Batch matrix matrix product of matrices stored in batch1 and batch2, with batch add.
batch1 and batch2 must be 3D Tensors each containing the same number of
matrices. If batch1 is a b × n × m Tensor, batch2 a b × m × p Tensor,
res will be a b × n × p Tensor.
In other words,
res_i = (v1 * M_i) + (v2 * batch1_i * batch2_i)
Arguments
| :: All KnownDim '[n, p, b, m] | |
| => HsReal | v1 |
| -> Tensor '[b, n, p] | M_i -- mutated inplace |
| -> HsReal | v2 |
| -> Tensor '[b, n, m] | batch1_i |
| -> Tensor '[b, m, p] | batch2_i |
| -> IO () |
Inline version of baddbmm, mutating M_i in-place.