{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Double.TensorMathPointwise where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_sigmoid"
c_sigmoid :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_log"
c_log :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_lgamma"
c_lgamma :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_digamma"
c_digamma :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_polygamma"
c_polygamma :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CLLong -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_log1p"
c_log1p :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_exp"
c_exp :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_expm1"
c_expm1 :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cos"
c_cos :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_acos"
c_acos :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cosh"
c_cosh :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_sin"
c_sin :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_asin"
c_asin :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_sinh"
c_sinh :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_tan"
c_tan :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_atan"
c_atan :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_atan2"
c_atan2 :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_tanh"
c_tanh :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_erf"
c_erf :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_erfinv"
c_erfinv :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_pow"
c_pow :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_tpow"
c_tpow :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_sqrt"
c_sqrt :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_rsqrt"
c_rsqrt :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_ceil"
c_ceil :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_floor"
c_floor :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_round"
c_round :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_trunc"
c_trunc :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_frac"
c_frac :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_lerp"
c_lerp :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cinv"
c_cinv :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_neg"
c_neg :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_abs"
c_abs :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_sign"
c_sign :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_clamp"
c_clamp :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cross"
c_cross :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CInt -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cadd"
c_cadd :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_csub"
c_csub :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cmul"
c_cmul :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cpow"
c_cpow :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cdiv"
c_cdiv :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_clshift"
c_clshift :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_crshift"
c_crshift :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cmax"
c_cmax :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cmin"
c_cmin :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cfmod"
c_cfmod :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cremainder"
c_cremainder :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cmaxValue"
c_cmaxValue :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cminValue"
c_cminValue :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cbitand"
c_cbitand :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cbitor"
c_cbitor :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_cbitxor"
c_cbitxor :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_addcmul"
c_addcmul :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h THCudaDoubleTensor_addcdiv"
c_addcdiv :: Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ()
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_sigmoid"
p_sigmoid :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_log"
p_log :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_lgamma"
p_lgamma :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_digamma"
p_digamma :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_polygamma"
p_polygamma :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CLLong -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_log1p"
p_log1p :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_exp"
p_exp :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_expm1"
p_expm1 :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cos"
p_cos :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_acos"
p_acos :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cosh"
p_cosh :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_sin"
p_sin :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_asin"
p_asin :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_sinh"
p_sinh :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_tan"
p_tan :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_atan"
p_atan :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_atan2"
p_atan2 :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_tanh"
p_tanh :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_erf"
p_erf :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_erfinv"
p_erfinv :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_pow"
p_pow :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_tpow"
p_tpow :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_sqrt"
p_sqrt :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_rsqrt"
p_rsqrt :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_ceil"
p_ceil :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_floor"
p_floor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_round"
p_round :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_trunc"
p_trunc :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_frac"
p_frac :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_lerp"
p_lerp :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cinv"
p_cinv :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_neg"
p_neg :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_abs"
p_abs :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_sign"
p_sign :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_clamp"
p_clamp :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> CDouble -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cross"
p_cross :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CInt -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cadd"
p_cadd :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_csub"
p_csub :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cmul"
p_cmul :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cpow"
p_cpow :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cdiv"
p_cdiv :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_clshift"
p_clshift :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_crshift"
p_crshift :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cmax"
p_cmax :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cmin"
p_cmin :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cfmod"
p_cfmod :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cremainder"
p_cremainder :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cmaxValue"
p_cmaxValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cminValue"
p_cminValue :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cbitand"
p_cbitand :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cbitor"
p_cbitor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_cbitxor"
p_cbitxor :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_addcmul"
p_addcmul :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())
foreign import ccall "THCTensorMathPointwise.h &THCudaDoubleTensor_addcdiv"
p_addcdiv :: FunPtr (Ptr C'THCState -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> CDouble -> Ptr C'THCudaDoubleTensor -> Ptr C'THCudaDoubleTensor -> IO ())