{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Double.TensorMath where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_fill"
c_fill :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_zero"
c_zero :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_zeros"
c_zeros :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THLongStorage -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_zerosLike"
c_zerosLike :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_ones"
c_ones :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THLongStorage -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_onesLike"
c_onesLike :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_reshape"
c_reshape :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THLongStorage -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_numel"
c_numel :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> IO CPtrdiff
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_cat"
c_cat :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CInt -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_catArray"
c_catArray :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr (Ptr C'THCudaDoubleTensor) -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_nonzero"
c_nonzero :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_tril"
c_tril :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CLLong -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_triu"
c_triu :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CLLong -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_diag"
c_diag :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CLLong -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_eye"
c_eye :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CLLong -> CLLong -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_trace"
c_trace :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> IO CDouble
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_linspace"
c_linspace :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CLLong -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_logspace"
c_logspace :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CLLong -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_range"
c_range :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "THCTensorMath.h THCudaDoubleTensor_arange"
c_arange :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_fill"
p_fill :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_zero"
p_zero :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_zeros"
p_zeros :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THLongStorage -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_zerosLike"
p_zerosLike :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_ones"
p_ones :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THLongStorage -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_onesLike"
p_onesLike :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_reshape"
p_reshape :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THLongStorage -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_numel"
p_numel :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> IO CPtrdiff)
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_cat"
p_cat :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CInt -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_catArray"
p_catArray :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr (Ptr C'THCudaDoubleTensor) -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_nonzero"
p_nonzero :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_tril"
p_tril :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CLLong -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_triu"
p_triu :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CLLong -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_diag"
p_diag :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CLLong -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_eye"
p_eye :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CLLong -> CLLong -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_trace"
p_trace :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> IO CDouble)
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_linspace"
p_linspace :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CLLong -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_logspace"
p_logspace :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CLLong -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_range"
p_range :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CDouble -> IO ())
foreign import ccall "THCTensorMath.h &THCudaDoubleTensor_arange"
p_arange :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> CDouble -> IO ())