{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Char.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 THCudaCharTensor_sum"
  c_sum :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_prod"
  c_prod :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_sumall"
  c_sumall :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CLong
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_prodall"
  c_prodall :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CLong
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_min"
  c_min :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_max"
  c_max :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_minall"
  c_minall :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CChar
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_maxall"
  c_maxall :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CChar
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_medianall"
  c_medianall :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CChar
foreign import ccall "THCTensorMathReduce.h THCudaCharTensor_median"
  c_median :: Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ()
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_sum"
  p_sum :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_prod"
  p_prod :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_sumall"
  p_sumall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CLong)
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_prodall"
  p_prodall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CLong)
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_min"
  p_min :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_max"
  p_max :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ())
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_minall"
  p_minall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CChar)
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_maxall"
  p_maxall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CChar)
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_medianall"
  p_medianall :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> IO CChar)
foreign import ccall "THCTensorMathReduce.h &THCudaCharTensor_median"
  p_median :: FunPtr (Ptr C'THCState -> Ptr C'THCudaCharTensor -> Ptr C'THCudaLongTensor -> Ptr C'THCudaCharTensor -> CInt -> CInt -> IO ())