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

Contents

Description

 
Synopsis

Documentation

vector :: forall n. KnownDim n => KnownNat n => [HsReal] -> ExceptT String IO (Tensor '[n]) Source #

Purely make a 1d tensor from a list of unknown length.

unsafeVector :: (KnownDim n, KnownNat n) => [HsReal] -> IO (Tensor '[n]) Source #

newExpand :: Tensor d -> IndexStorage -> Tensor d' Source #

Static call to newExpand

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

Static call to _expand

_expandNd :: NonEmpty (Tensor d1) -> NonEmpty (Tensor d2) -> Int -> IO () Source #

Static call to _expandNd

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

Static call to resize_

resize1d_ :: Tensor d1 -> Word -> IO (Tensor d2) Source #

Static call to resize1d_

resize2d_ :: Tensor d1 -> Word -> Word -> IO (Tensor d2) Source #

Static call to resize2d_

resize3d_ :: Tensor d1 -> Word -> Word -> Word -> IO (Tensor d2) Source #

Static call to resize3d_

resize4d_ :: Tensor d1 -> Word -> Word -> Word -> Word -> IO (Tensor d2) Source #

Static call to resize4d_

resize5d_ :: Tensor d1 -> Word -> Word -> Word -> Word -> Word -> IO (Tensor d2) Source #

Static call to resize5d_

resizeAsT_ :: Tensor d1 -> Tensor d2 -> IO (Tensor d3) Source #

Static call to resizeAs_

resizeNd_ :: Tensor d1 -> Int32 -> [Size] -> [Stride] -> IO (Tensor d2) Source #

Static call to resizeNd_

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

Static call to retain

_clearFlag :: Tensor d -> Int8 -> IO () Source #

Static call to _clearFlag

tensordata :: Tensor d -> [HsReal] Source #

Static call to tensordata

get1d :: Tensor d -> Word -> Maybe HsReal Source #

Static call to get1d

get2d :: Tensor d -> Word -> Word -> Maybe HsReal Source #

Static call to get2d

get3d :: Tensor d -> Word -> Word -> Word -> Maybe HsReal Source #

Static call to get3d

get4d :: Tensor d -> Word -> Word -> Word -> Word -> Maybe HsReal Source #

Static call to get4d

isSetTo :: Tensor d1 -> Tensor d2 -> Bool Source #

Static call to isSetTo

isSize :: Tensor d -> LongStorage -> Bool Source #

Static call to isSize

nDimension :: Tensor d -> Word Source #

Static call to nDimension

nElement :: Tensor d -> Word64 Source #

Static call to nElement

_narrow :: Tensor d1 -> Tensor d2 -> Word -> Int64 -> Size -> IO () Source #

Static call to _narrow

empty :: Tensor d Source #

renamed from TH's new because this always returns an empty tensor FIXME: this __technically should be IO (Tensor '[]), but if you leave it as-is the types line-up nicely (and we currently don't use rank-0 tensors).

newClone :: Tensor d -> Tensor d Source #

Static call to newClone

newContiguous :: Tensor d1 -> Tensor d2 Source #

Static call to newContiguous

newNarrow :: Tensor d1 -> Word -> Int64 -> Size -> IO (Tensor d2) Source #

Static call to newNarrow

newSelect :: KnownDim i => '(ls, r :+ rs) ~ SplitAt i d => Tensor d -> (Dim i, Idx i) -> IO (Tensor (ls ++ rs)) Source #

Static call to newSelect

newTranspose :: Tensor d1 -> Word -> Word -> Tensor d2 Source #

Static call to newTranspose

newUnfold :: Tensor d1 -> Word -> Int64 -> Int64 -> Tensor d2 Source #

Static call to newUnfold

view :: forall d d'. (Dimensions d, Dimensions d') => Tensor d -> IO (Tensor d') Source #

Make a new view of a tensor.

newWithSize3d :: Word -> Word -> Word -> Tensor d Source #

Static call to newWithSize3d

newWithSize4d :: Word -> Word -> Word -> Word -> Tensor d Source #

Static call to newWithSize4d

newWithTensor :: Tensor d1 -> IO (Tensor d2) Source #

Static call to newWithTensor

_select :: Tensor d1 -> Tensor d2 -> Word -> Word -> IO () Source #

Static call to _select

_set :: Tensor d1 -> Tensor d2 -> IO () Source #

Static call to _set

set1d_ :: Tensor d -> Word -> HsReal -> IO () Source #

Static call to set1d_

set2d_ :: Tensor d -> Word -> Word -> HsReal -> IO () Source #

Static call to set2d_

set3d_ :: Tensor d -> Word -> Word -> Word -> HsReal -> IO () Source #

Static call to set3d_

set4d_ :: Tensor d -> Word -> Word -> Word -> Word -> HsReal -> IO () Source #

Static call to set4d_

setFlag_ :: Tensor d -> Int8 -> IO () Source #

Static call to setFlag_

setStorage2d_ :: Tensor d -> Storage -> StorageOffset -> (Size, Stride) -> (Size, Stride) -> IO () Source #

Static call to setStorage2d_

setStorage3d_ :: Tensor d -> Storage -> StorageOffset -> (Size, Stride) -> (Size, Stride) -> (Size, Stride) -> IO () Source #

Static call to setStorage3d_

setStorage4d_ :: Tensor d -> Storage -> StorageOffset -> (Size, Stride) -> (Size, Stride) -> (Size, Stride) -> (Size, Stride) -> IO () Source #

Static call to setStorage4d_

setStorageNd_ :: Tensor d -> Storage -> StorageOffset -> Word -> [Size] -> [Stride] -> IO () Source #

Static call to setStorageNd_

size :: Tensor d -> Word -> Word Source #

Static call to size

sizeDesc :: Tensor d -> IO DescBuff Source #

Static call to sizeDesc

_squeeze :: Tensor d1 -> Tensor d2 -> IO () Source #

Static call to _squeeze

squeeze1d :: Dimensions d => '(rs, 1 :+ ls) ~ SplitAt n d => Dim n -> Tensor d -> Tensor (rs ++ ls) Source #

Squeeze a dimension of size 1 out of the tensor

squeeze1d_ :: Dimensions d => '(rs, 1 :+ ls) ~ SplitAt n d => Dim n -> Tensor d -> IO (Tensor (rs ++ ls)) Source #

  • Not safe:* squeeze a dimension of size 1 out of the tensor.

storage :: Tensor d -> Storage Source #

Static call to storage

stride :: Tensor d -> Word -> IO Stride Source #

Static call to stride

_transpose :: Tensor d1 -> Tensor d2 -> Word -> Word -> IO () Source #

Static call to _transpose

_unfold :: Tensor d1 -> Tensor d2 -> Word -> Size -> Step -> IO () Source #

Static call to _unfold

unsqueeze1d :: Dimensions d => '(rs, ls) ~ SplitAt n d => Dim n -> Tensor d -> Tensor (rs ++ ('[1] ++ ls)) Source #

Unsqueeze a dimension of size 1 into the tensor (pure, dupable)

unsqueeze1d_ :: Dimensions d => '(rs, ls) ~ SplitAt n d => Dim n -> Tensor d -> IO (Tensor (rs ++ ('[1] ++ ls))) Source #

  • Not safe:* unsqueeze a dimension of size 1 into the tensor.

shape :: Tensor d -> [Word] Source #

Get runtime shape information from a tensor

getSomeDims :: Tensor d -> SomeDims Source #

alias to shape, casting the dimensions into a runtime SomeDims.

withInplace :: Dimensions d => Tensor d -> (Tensor d -> Tensor d -> IO ()) -> IO (Tensor d) Source #

Deprecated: this is a trivial function with a bad API

same as withEmpty (which should be called newFromSize) and withNew, but passes in an empty tensor to be mutated and returned with a static dimensionality that it is assumed to take on after the mutation.

Note: We can get away with this when Torch does resizing in C, but you need to examine the C implementation of the function you are trying to make pure. withEmpty' :: (Dimensions d) => (Tensor d -> IO ()) -> IO (Tensor d) withEmpty' op = let r = empty in op r >> pure r

This is actually inplace. Dimensions may change from original tensor given Torch resizing.

FIXME: remove this function

throwFIXME :: MonadThrow io => String -> String -> io x Source #

throw a FIXME string.

throwNE :: MonadThrow io => String -> io x Source #

throw an "unsafe head" string.

throwGT4 :: MonadThrow io => String -> io x Source #

throw an "unsupported dimension" string.

setStorageDim_ :: Tensor d -> Storage -> StorageOffset -> [(Size, Stride)] -> IO () Source #

Set the storage of a tensor. This is incredibly unsafe.

setDim_ :: Tensor d -> Dims (d' :: [Nat]) -> HsReal -> IO () Source #

Set the value of a tensor at a given index

FIXME: there should be a constraint to see that d' is in d

setDim'_ :: Tensor d -> SomeDims -> HsReal -> IO () Source #

runtime version of setDim_

getDim Source #

Arguments

:: All Dimensions '[d, i :+ d'] 
=> Tensor (d :: [Nat]) 
-> Dims (i :+ d' :: [Nat])

the index to get is a non-empty dims list

-> Maybe HsReal 

get the value of a tensor at the given index

FIXME: there should be a constraint to see that d' is in d

(!!) :: forall d ls r rs i. '(ls, r :+ rs) ~ SplitAt i d => KnownDim i => Dimensions d => Tensor d -> Dim i -> Tensor (ls ++ rs) Source #

Select a dimension of a tensor. If a vector is passed in, return a singleton tensor with the index value of the vector.

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

Create a new tensor. Elements have not yet been allocated and there will not be any gauruntees regarding what is inside.

_resizeDim :: forall d d'. Dimensions d' => Tensor d -> IO (Tensor d') Source #

Resize a tensor, returning the same tensor with a the changed dimensions.

NOTE: This is copied from the dynamic version to keep the constraints clean and is _unsafe_

resizeAs_ :: forall d d'. (All Dimensions '[d, d'], Product d ~ Product d') => Tensor d -> IO (Tensor d') Source #

Resize the input with the output shape. impure and mutates the tensor inplace.

FIXME: replace d with a linear type?

resizeAs :: forall d d'. (All Dimensions [d, d'], Product d ~ Product d') => Tensor d -> Tensor d' Source #

Pure version of resizeAs_ which clones the input tensor (pure, dupable?)

WARNING: This might be not be garbage collected as you expect since the input argument becomes a dangling phantom type.

flatten :: (Dimensions d, KnownDim (Product d)) => Tensor d -> Tensor '[Product d] Source #

flatten a tensor (pure, dupable)

fromList :: forall d. Dimensions d => KnownNat (Product d) => KnownDim (Product d) => [HsReal] -> IO (Maybe (Tensor d)) Source #

Initialize a tensor of arbitrary dimension from a list FIXME: There might be a faster way to do this with newWithSize

matrix :: forall n m. (All KnownDim '[n, m], All KnownNat '[n, m]) => KnownDim (n * m) => KnownNat (n * m) => [[HsReal]] -> ExceptT String IO (Tensor '[n, m]) Source #

Purely construct a matrix from a list of lists. This assumes that the list of lists is a dense matrix representation. Returns either the successful construction of the tensor, or a string explaining what went wrong.

unsafeMatrix :: forall n m. All KnownDim '[n, m, n * m] => All KnownNat '[n, m, n * m] => [[HsReal]] -> IO (Tensor '[n, m]) Source #

cuboid :: forall c h w. (All KnownDim '[c, h, w], All KnownNat '[c, h, w]) => [[[HsReal]]] -> ExceptT String IO (Tensor '[c, h, w]) Source #

Purely construct a cuboid from a list of list of lists. This assumes a dense representation. Returns either the successful construction of the tensor, or a string explaining what went wrong.

unsafeCuboid :: forall c h w. All KnownDim '[c, h, w] => All KnownNat '[c, h, w] => [[[HsReal]]] -> IO (Tensor '[c, h, w]) Source #

transpose2d :: All KnownDim '[r, c] => Tensor '[r, c] -> Tensor '[c, r] Source #

transpose a matrix (pure, dupable)

expand2d :: forall x y. All KnownDim '[x, y] => Tensor '[x] -> Tensor '[y, x] Source #

Expand a vector by copying into a matrix by set dimensions TODO - generalize this beyond the matrix case

getElem2d :: forall (n :: Nat) (m :: Nat). All KnownDim '[n, m] => Tensor '[n, m] -> Word -> Word -> Maybe HsReal Source #

Deprecated: use getDim instead

Get an element from a matrix with runtime index values.

FIXME: This is primarily for backwards compatability with lasso and should be removed.

setElem2d :: forall (n :: Nat) (m :: Nat) ns. All KnownDim '[n, m] => Tensor '[n, m] -> Word -> Word -> HsReal -> IO () Source #

Deprecated: use setDim_ instead

Set an element on a matrix with runtime index values.

FIXME: This is primarily for backwards compatability with lasso and should be removed.

Orphan instances

Show (Tensor d) Source # 
Instance details

Methods

showsPrec :: Int -> Tensor d -> ShowS #

show :: Tensor d -> String #

showList :: [Tensor d] -> ShowS #