{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Int.TensorMathCompareT where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_ltTensor"
  c_ltTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_gtTensor"
  c_gtTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_leTensor"
  c_leTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_geTensor"
  c_geTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_eqTensor"
  c_eqTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_neTensor"
  c_neTensor :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_ltTensorT"
  c_ltTensorT :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_gtTensorT"
  c_gtTensorT :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_leTensorT"
  c_leTensorT :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_geTensorT"
  c_geTensorT :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_eqTensorT"
  c_eqTensorT :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h THCudaIntTensor_neTensorT"
  c_neTensorT :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_ltTensor"
  p_ltTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_gtTensor"
  p_gtTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_leTensor"
  p_leTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_geTensor"
  p_geTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_eqTensor"
  p_eqTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_neTensor"
  p_neTensor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_ltTensorT"
  p_ltTensorT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_gtTensorT"
  p_gtTensorT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_leTensorT"
  p_leTensorT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_geTensorT"
  p_geTensorT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_eqTensorT"
  p_eqTensorT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorMathCompareT.h &THCudaIntTensor_neTensorT"
  p_neTensorT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())