{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Long.TensorMathCompare where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_ltValue"
  c_ltValue :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_gtValue"
  c_gtValue :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_leValue"
  c_leValue :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_geValue"
  c_geValue :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_eqValue"
  c_eqValue :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_neValue"
  c_neValue :: Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_ltValueT"
  c_ltValueT :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_gtValueT"
  c_gtValueT :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_leValueT"
  c_leValueT :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_geValueT"
  c_geValueT :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_eqValueT"
  c_eqValueT :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h THCudaLongTensor_neValueT"
  c_neValueT :: Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ()
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_ltValue"
  p_ltValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_gtValue"
  p_gtValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_leValue"
  p_leValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_geValue"
  p_geValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_eqValue"
  p_eqValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_neValue"
  p_neValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaByteTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_ltValueT"
  p_ltValueT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_gtValueT"
  p_gtValueT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_leValueT"
  p_leValueT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_geValueT"
  p_geValueT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_eqValueT"
  p_eqValueT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())
foreign import ccall "THCTensorMathCompare.h &THCudaLongTensor_neValueT"
  p_neValueT :: FunPtr (Ptr C'THCState -> Ptr C'THCudaLongTensor -> Ptr C'THCudaLongTensor -> CLong -> IO ())