{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Short.TensorMathScan where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorMathScan.h THCudaShortTensor_cumsum"
c_cumsum :: Ptr C'THCState -> Ptr C'THCudaShortTensor -> Ptr C'THCudaShortTensor -> CInt -> IO ()
foreign import ccall "THCTensorMathScan.h THCudaShortTensor_cumprod"
c_cumprod :: Ptr C'THCState -> Ptr C'THCudaShortTensor -> Ptr C'THCudaShortTensor -> CInt -> IO ()
foreign import ccall "THCTensorMathScan.h &THCudaShortTensor_cumsum"
p_cumsum :: FunPtr (Ptr C'THCState -> Ptr C'THCudaShortTensor -> Ptr C'THCudaShortTensor -> CInt -> IO ())
foreign import ccall "THCTensorMathScan.h &THCudaShortTensor_cumprod"
p_cumprod :: FunPtr (Ptr C'THCState -> Ptr C'THCudaShortTensor -> Ptr C'THCudaShortTensor -> CInt -> IO ())