{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Byte.TensorMathReduce where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_sum"
c_sum :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_prod"
c_prod :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_sumall"
c_sumall :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CLong
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_prodall"
c_prodall :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CLong
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_min"
c_min :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_max"
c_max :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_minall"
c_minall :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CUChar
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_maxall"
c_maxall :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CUChar
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_medianall"
c_medianall :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CUChar
foreign import ccall "THCTensorMathReduce.h THCudaByteTensor_median"
c_median :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_sum"
p_sum :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_prod"
p_prod :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_sumall"
p_sumall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CLong)
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_prodall"
p_prodall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CLong)
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_min"
p_min :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_max"
p_max :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_minall"
p_minall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CUChar)
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_maxall"
p_maxall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CUChar)
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_medianall"
p_medianall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> IO CUChar)
foreign import ccall "THCTensorMathReduce.h &THCudaByteTensor_median"
p_median :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaByteTensor -> CInt -> CInt -> IO ())