{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Int.TensorCopy where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copy"
c_copy :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyIgnoringOverlaps"
c_copyIgnoringOverlaps :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyByte"
c_copyByte :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THByteTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyChar"
c_copyChar :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCharTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyShort"
c_copyShort :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THShortTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyInt"
c_copyInt :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyLong"
c_copyLong :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THLongTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyFloat"
c_copyFloat :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THFloatTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyDouble"
c_copyDouble :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THDoubleTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyHalf"
c_copyHalf :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THHalfTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCudaByte"
c_copyCudaByte :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaByteTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCudaChar"
c_copyCudaChar :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaCharTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCudaShort"
c_copyCudaShort :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaShortTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCudaInt"
c_copyCudaInt :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCudaLong"
c_copyCudaLong :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaLongTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCudaDouble"
c_copyCudaDouble :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCuda"
c_copyCuda :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THIntTensor_copyCuda"
c_thCopyCuda :: Ptr C'THCState -> Ptr C'THIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyCPU"
c_copyCPU :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THCudaIntTensor_copyAsyncCPU"
c_copyAsyncCPU :: Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h THIntTensor_copyAsyncCuda"
c_thCopyAsyncCuda :: Ptr C'THCState -> Ptr C'THIntTensor -> Ptr C'THCudaIntTensor -> IO ()
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copy"
p_copy :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyIgnoringOverlaps"
p_copyIgnoringOverlaps :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyByte"
p_copyByte :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THByteTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyChar"
p_copyChar :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCharTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyShort"
p_copyShort :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THShortTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyInt"
p_copyInt :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyLong"
p_copyLong :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THLongTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyFloat"
p_copyFloat :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THFloatTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyDouble"
p_copyDouble :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THDoubleTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyHalf"
p_copyHalf :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THHalfTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCudaByte"
p_copyCudaByte :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaByteTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCudaChar"
p_copyCudaChar :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaCharTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCudaShort"
p_copyCudaShort :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaShortTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCudaInt"
p_copyCudaInt :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCudaLong"
p_copyCudaLong :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaLongTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCudaDouble"
p_copyCudaDouble :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCuda"
p_copyCuda :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THIntTensor_copyCuda"
p_thCopyCuda :: FunPtr (Ptr C'THCState -> Ptr C'THIntTensor -> Ptr C'THCudaIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyCPU"
p_copyCPU :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THCudaIntTensor_copyAsyncCPU"
p_copyAsyncCPU :: FunPtr (Ptr C'THCState -> Ptr C'THCudaIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THCTensorCopy.h &THIntTensor_copyAsyncCuda"
p_thCopyAsyncCuda :: FunPtr (Ptr C'THCState -> Ptr C'THIntTensor -> Ptr C'THCudaIntTensor -> IO ())