hasktorch-ffi-thc-0.0.1.0: Bindings to Cutorch

Safe HaskellNone
LanguageHaskell2010

Torch.FFI.THC.Byte.Tensor

Synopsis

Documentation

c_storage :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCByteStorage) Source #

c_storage : state self -> THCStorage *

c_storageOffset :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CPtrdiff Source #

c_storageOffset : state self -> ptrdiff_t

c_nDimension :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CInt Source #

c_nDimension : state self -> int

c_size :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> IO CLLong Source #

c_size : state self dim -> int64_t

c_stride :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> IO CLLong Source #

c_stride : state self dim -> int64_t

c_newSizeOf :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THLongStorage) Source #

c_newSizeOf : state self -> THLongStorage *

c_newStrideOf :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THLongStorage) Source #

c_newStrideOf : state self -> THLongStorage *

c_data :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr CUChar) Source #

c_data : state self -> real *

c_setFlag :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CChar -> IO () Source #

c_setFlag : state self flag -> void

c_clearFlag :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CChar -> IO () Source #

c_clearFlag : state self flag -> void

c_new :: Ptr C'THCState -> IO (Ptr C'THCudaByteTensor) Source #

c_new : state -> THCTensor *

c_newWithTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithTensor : state tensor -> THCTensor *

c_newWithStorage :: Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithStorage : state storage_ storageOffset_ size_ stride_ -> THCTensor *

c_newWithStorage1d :: Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithStorage1d : state storage_ storageOffset_ size0_ stride0_ -> THCTensor *

c_newWithStorage2d :: Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithStorage2d : state storage_ storageOffset_ size0_ stride0_ size1_ stride1_ -> THCTensor *

c_newWithStorage3d :: Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithStorage3d : state storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ -> THCTensor *

c_newWithStorage4d :: Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithStorage4d : state storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ size3_ stride3_ -> THCTensor *

c_newWithSize :: Ptr C'THCState -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithSize : state size_ stride_ -> THCTensor *

c_newWithSize1d :: Ptr C'THCState -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithSize1d : state size0_ -> THCTensor *

c_newWithSize2d :: Ptr C'THCState -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithSize2d : state size0_ size1_ -> THCTensor *

c_newWithSize3d :: Ptr C'THCState -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithSize3d : state size0_ size1_ size2_ -> THCTensor *

c_newWithSize4d :: Ptr C'THCState -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newWithSize4d : state size0_ size1_ size2_ size3_ -> THCTensor *

c_newClone :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor) Source #

c_newClone : state self -> THCTensor *

c_newContiguous :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor) Source #

c_newContiguous : state tensor -> THCTensor *

c_newSelect :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newSelect : state tensor dimension_ sliceIndex_ -> THCTensor *

c_newNarrow :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newNarrow : state tensor dimension_ firstIndex_ size_ -> THCTensor *

c_newTranspose :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO (Ptr C'THCudaByteTensor) Source #

c_newTranspose : state tensor dimension1_ dimension2_ -> THCTensor *

c_newUnfold :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor) Source #

c_newUnfold : state tensor dimension_ size_ step_ -> THCTensor *

c_newView :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor) Source #

c_newView : state tensor size -> THCTensor *

c_newFoldBatchDim :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor) Source #

c_newFoldBatchDim : state input -> THCTensor *

c_newExpand :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor) Source #

c_newExpand : state tensor size -> THCTensor *

c_expand :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO () Source #

c_expand : state r tensor sizes -> void

c_expandNd :: Ptr C'THCState -> Ptr (Ptr C'THCudaByteTensor) -> Ptr (Ptr C'THCudaByteTensor) -> CInt -> IO () Source #

c_expandNd : state rets ops count -> void

c_resize :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO () Source #

c_resize : state tensor size stride -> void

c_resizeAs :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO () Source #

c_resizeAs : state tensor src -> void

c_resize1d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> IO () Source #

c_resize1d : state tensor size0_ -> void

c_resize2d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> IO () Source #

c_resize2d : state tensor size0_ size1_ -> void

c_resize3d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> IO () Source #

c_resize3d : state tensor size0_ size1_ size2_ -> void

c_resize4d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

c_resize4d : state tensor size0_ size1_ size2_ size3_ -> void

c_resize5d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

c_resize5d : state tensor size0_ size1_ size2_ size3_ size4_ -> void

c_resizeNd :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> Ptr CLLong -> Ptr CLLong -> IO () Source #

c_resizeNd : state tensor nDimension size stride -> void

c_set :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO () Source #

c_set : state self src -> void

c_setStorage :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO () Source #

c_setStorage : state self storage_ storageOffset_ size_ stride_ -> void

c_setStorageNd :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CInt -> Ptr CLLong -> Ptr CLLong -> IO () Source #

c_setStorageNd : state self storage storageOffset nDimension size stride -> void

c_setStorage1d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> IO () Source #

c_setStorage1d : state self storage_ storageOffset_ size0_ stride0_ -> void

c_setStorage2d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

c_setStorage2d : state self storage_ storageOffset_ size0_ stride0_ size1_ stride1_ -> void

c_setStorage3d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

c_setStorage3d : state self storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ -> void

c_setStorage4d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

c_setStorage4d : state self storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ size3_ stride3_ -> void

c_narrow :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO () Source #

c_narrow : state self src dimension_ firstIndex_ size_ -> void

c_select :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> IO () Source #

c_select : state self src dimension_ sliceIndex_ -> void

c_transpose :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO () Source #

c_transpose : state self src dimension1_ dimension2_ -> void

c_unfold :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO () Source #

c_unfold : state self src dimension_ size_ step_ -> void

c_squeeze :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO () Source #

c_squeeze : state self src -> void

c_squeeze1d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> IO () Source #

c_squeeze1d : state self src dimension_ -> void

c_unsqueeze1d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> IO () Source #

c_unsqueeze1d : state self src dimension_ -> void

c_isContiguous :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CInt Source #

c_isContiguous : state self -> int

c_isSameSizeAs :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO CInt Source #

c_isSameSizeAs : state self src -> int

c_isSetTo :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO CInt Source #

c_isSetTo : state self src -> int

c_isSize :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO CInt Source #

c_isSize : state self dims -> int

c_nElement :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CPtrdiff Source #

c_nElement : state self -> ptrdiff_t

c_retain :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO () Source #

c_retain : state self -> void

c_free :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO () Source #

c_free : state self -> void

c_freeCopyTo :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO () Source #

c_freeCopyTo : state self dst -> void

c_set1d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CUChar -> IO () Source #

c_set1d : state tensor x0 value -> void

c_set2d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CUChar -> IO () Source #

c_set2d : state tensor x0 x1 value -> void

c_set3d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CUChar -> IO () Source #

c_set3d : state tensor x0 x1 x2 value -> void

c_set4d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> CUChar -> IO () Source #

c_set4d : state tensor x0 x1 x2 x3 value -> void

c_get1d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> IO CUChar Source #

c_get1d : state tensor x0 -> real

c_get2d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> IO CUChar Source #

c_get2d : state tensor x0 x1 -> real

c_get3d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> IO CUChar Source #

c_get3d : state tensor x0 x1 x2 -> real

c_get4d :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> IO CUChar Source #

c_get4d : state tensor x0 x1 x2 x3 -> real

c_getDevice :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CInt Source #

c_getDevice : state self -> int

c_sizeDesc :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCDescBuff) Source #

c_sizeDesc : state tensor -> THCDescBuff

p_storage :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCByteStorage)) Source #

p_storage : Pointer to function : state self -> THCStorage *

p_storageOffset :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CPtrdiff) Source #

p_storageOffset : Pointer to function : state self -> ptrdiff_t

p_nDimension :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CInt) Source #

p_nDimension : Pointer to function : state self -> int

p_size :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> IO CLLong) Source #

p_size : Pointer to function : state self dim -> int64_t

p_stride :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> IO CLLong) Source #

p_stride : Pointer to function : state self dim -> int64_t

p_newSizeOf :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THLongStorage)) Source #

p_newSizeOf : Pointer to function : state self -> THLongStorage *

p_newStrideOf :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THLongStorage)) Source #

p_newStrideOf : Pointer to function : state self -> THLongStorage *

p_data :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr CUChar)) Source #

p_data : Pointer to function : state self -> real *

p_setFlag :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CChar -> IO ()) Source #

p_setFlag : Pointer to function : state self flag -> void

p_clearFlag :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CChar -> IO ()) Source #

p_clearFlag : Pointer to function : state self flag -> void

p_new :: FunPtr (Ptr C'THCState -> IO (Ptr C'THCudaByteTensor)) Source #

p_new : Pointer to function : state -> THCTensor *

p_newWithTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithTensor : Pointer to function : state tensor -> THCTensor *

p_newWithStorage :: FunPtr (Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithStorage : Pointer to function : state storage_ storageOffset_ size_ stride_ -> THCTensor *

p_newWithStorage1d :: FunPtr (Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithStorage1d : Pointer to function : state storage_ storageOffset_ size0_ stride0_ -> THCTensor *

p_newWithStorage2d :: FunPtr (Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithStorage2d : Pointer to function : state storage_ storageOffset_ size0_ stride0_ size1_ stride1_ -> THCTensor *

p_newWithStorage3d :: FunPtr (Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithStorage3d : Pointer to function : state storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ -> THCTensor *

p_newWithStorage4d :: FunPtr (Ptr C'THCState -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithStorage4d : Pointer to function : state storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ size3_ stride3_ -> THCTensor *

p_newWithSize :: FunPtr (Ptr C'THCState -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithSize : Pointer to function : state size_ stride_ -> THCTensor *

p_newWithSize1d :: FunPtr (Ptr C'THCState -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithSize1d : Pointer to function : state size0_ -> THCTensor *

p_newWithSize2d :: FunPtr (Ptr C'THCState -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithSize2d : Pointer to function : state size0_ size1_ -> THCTensor *

p_newWithSize3d :: FunPtr (Ptr C'THCState -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithSize3d : Pointer to function : state size0_ size1_ size2_ -> THCTensor *

p_newWithSize4d :: FunPtr (Ptr C'THCState -> CLLong -> CLLong -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newWithSize4d : Pointer to function : state size0_ size1_ size2_ size3_ -> THCTensor *

p_newClone :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor)) Source #

p_newClone : Pointer to function : state self -> THCTensor *

p_newContiguous :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor)) Source #

p_newContiguous : Pointer to function : state tensor -> THCTensor *

p_newSelect :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newSelect : Pointer to function : state tensor dimension_ sliceIndex_ -> THCTensor *

p_newNarrow :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newNarrow : Pointer to function : state tensor dimension_ firstIndex_ size_ -> THCTensor *

p_newTranspose :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO (Ptr C'THCudaByteTensor)) Source #

p_newTranspose : Pointer to function : state tensor dimension1_ dimension2_ -> THCTensor *

p_newUnfold :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO (Ptr C'THCudaByteTensor)) Source #

p_newUnfold : Pointer to function : state tensor dimension_ size_ step_ -> THCTensor *

p_newView :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor)) Source #

p_newView : Pointer to function : state tensor size -> THCTensor *

p_newFoldBatchDim :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCudaByteTensor)) Source #

p_newFoldBatchDim : Pointer to function : state input -> THCTensor *

p_newExpand :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO (Ptr C'THCudaByteTensor)) Source #

p_newExpand : Pointer to function : state tensor size -> THCTensor *

p_expand :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO ()) Source #

p_expand : Pointer to function : state r tensor sizes -> void

p_expandNd :: FunPtr (Ptr C'THCState -> Ptr (Ptr C'THCudaByteTensor) -> Ptr (Ptr C'THCudaByteTensor) -> CInt -> IO ()) Source #

p_expandNd : Pointer to function : state rets ops count -> void

p_resize :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO ()) Source #

p_resize : Pointer to function : state tensor size stride -> void

p_resizeAs :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO ()) Source #

p_resizeAs : Pointer to function : state tensor src -> void

p_resize1d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> IO ()) Source #

p_resize1d : Pointer to function : state tensor size0_ -> void

p_resize2d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> IO ()) Source #

p_resize2d : Pointer to function : state tensor size0_ size1_ -> void

p_resize3d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> IO ()) Source #

p_resize3d : Pointer to function : state tensor size0_ size1_ size2_ -> void

p_resize4d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> IO ()) Source #

p_resize4d : Pointer to function : state tensor size0_ size1_ size2_ size3_ -> void

p_resize5d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO ()) Source #

p_resize5d : Pointer to function : state tensor size0_ size1_ size2_ size3_ size4_ -> void

p_resizeNd :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CInt -> Ptr CLLong -> Ptr CLLong -> IO ()) Source #

p_resizeNd : Pointer to function : state tensor nDimension size stride -> void

p_set :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO ()) Source #

p_set : Pointer to function : state self src -> void

p_setStorage :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> Ptr C'THLongStorage -> Ptr C'THLongStorage -> IO ()) Source #

p_setStorage : Pointer to function : state self storage_ storageOffset_ size_ stride_ -> void

p_setStorageNd :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CInt -> Ptr CLLong -> Ptr CLLong -> IO ()) Source #

p_setStorageNd : Pointer to function : state self storage storageOffset nDimension size stride -> void

p_setStorage1d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> IO ()) Source #

p_setStorage1d : Pointer to function : state self storage_ storageOffset_ size0_ stride0_ -> void

p_setStorage2d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> IO ()) Source #

p_setStorage2d : Pointer to function : state self storage_ storageOffset_ size0_ stride0_ size1_ stride1_ -> void

p_setStorage3d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO ()) Source #

p_setStorage3d : Pointer to function : state self storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ -> void

p_setStorage4d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCByteStorage -> CPtrdiff -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> CLLong -> IO ()) Source #

p_setStorage4d : Pointer to function : state self storage_ storageOffset_ size0_ stride0_ size1_ stride1_ size2_ stride2_ size3_ stride3_ -> void

p_narrow :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO ()) Source #

p_narrow : Pointer to function : state self src dimension_ firstIndex_ size_ -> void

p_select :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> IO ()) Source #

p_select : Pointer to function : state self src dimension_ sliceIndex_ -> void

p_transpose :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ()) Source #

p_transpose : Pointer to function : state self src dimension1_ dimension2_ -> void

p_unfold :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CLLong -> CLLong -> IO ()) Source #

p_unfold : Pointer to function : state self src dimension_ size_ step_ -> void

p_squeeze :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO ()) Source #

p_squeeze : Pointer to function : state self src -> void

p_squeeze1d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> IO ()) Source #

p_squeeze1d : Pointer to function : state self src dimension_ -> void

p_unsqueeze1d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> IO ()) Source #

p_unsqueeze1d : Pointer to function : state self src dimension_ -> void

p_isContiguous :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CInt) Source #

p_isContiguous : Pointer to function : state self -> int

p_isSameSizeAs :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO CInt) Source #

p_isSameSizeAs : Pointer to function : state self src -> int

p_isSetTo :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO CInt) Source #

p_isSetTo : Pointer to function : state self src -> int

p_isSize :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THLongStorage -> IO CInt) Source #

p_isSize : Pointer to function : state self dims -> int

p_nElement :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CPtrdiff) Source #

p_nElement : Pointer to function : state self -> ptrdiff_t

p_retain :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO ()) Source #

p_retain : Pointer to function : state self -> void

p_free :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO ()) Source #

p_free : Pointer to function : state self -> void

p_freeCopyTo :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> IO ()) Source #

p_freeCopyTo : Pointer to function : state self dst -> void

p_set1d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CUChar -> IO ()) Source #

p_set1d : Pointer to function : state tensor x0 value -> void

p_set2d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CUChar -> IO ()) Source #

p_set2d : Pointer to function : state tensor x0 x1 value -> void

p_set3d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CUChar -> IO ()) Source #

p_set3d : Pointer to function : state tensor x0 x1 x2 value -> void

p_set4d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> CUChar -> IO ()) Source #

p_set4d : Pointer to function : state tensor x0 x1 x2 x3 value -> void

p_get1d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> IO CUChar) Source #

p_get1d : Pointer to function : state tensor x0 -> real

p_get2d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> IO CUChar) Source #

p_get2d : Pointer to function : state tensor x0 x1 -> real

p_get3d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> IO CUChar) Source #

p_get3d : Pointer to function : state tensor x0 x1 x2 -> real

p_get4d :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> CLLong -> CLLong -> CLLong -> CLLong -> IO CUChar) Source #

p_get4d : Pointer to function : state tensor x0 x1 x2 x3 -> real

p_getDevice :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CInt) Source #

p_getDevice : Pointer to function : state self -> int

p_sizeDesc :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO (Ptr C'THCDescBuff)) Source #

p_sizeDesc : Pointer to function : state tensor -> THCDescBuff