{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.TH.Int.TensorMath where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
foreign import ccall "THTensorMath.h THIntTensor_fill"
  c_fill_ :: Ptr C'THIntTensor -> CInt -> IO ()
c_fill :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> IO ()
c_fill = const c_fill_
foreign import ccall "THTensorMath.h THIntTensor_zero"
  c_zero_ :: Ptr C'THIntTensor -> IO ()
c_zero :: Ptr C'THState -> Ptr C'THIntTensor -> IO ()
c_zero = const c_zero_
foreign import ccall "THTensorMath.h THIntTensor_maskedFill"
  c_maskedFill_ :: Ptr C'THIntTensor -> Ptr C'THByteTensor -> CInt -> IO ()
c_maskedFill :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THByteTensor -> CInt -> IO ()
c_maskedFill = const c_maskedFill_
foreign import ccall "THTensorMath.h THIntTensor_maskedCopy"
  c_maskedCopy_ :: Ptr C'THIntTensor -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> IO ()
c_maskedCopy :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> IO ()
c_maskedCopy = const c_maskedCopy_
foreign import ccall "THTensorMath.h THIntTensor_maskedSelect"
  c_maskedSelect_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THByteTensor -> IO ()
c_maskedSelect :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THByteTensor -> IO ()
c_maskedSelect = const c_maskedSelect_
foreign import ccall "THTensorMath.h THIntTensor_nonzero"
  c_nonzero_ :: Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_nonzero :: Ptr C'THState -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_nonzero = const c_nonzero_
foreign import ccall "THTensorMath.h THIntTensor_indexSelect"
  c_indexSelect_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> IO ()
c_indexSelect :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> IO ()
c_indexSelect = const c_indexSelect_
foreign import ccall "THTensorMath.h THIntTensor_indexCopy"
  c_indexCopy_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_indexCopy :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_indexCopy = const c_indexCopy_
foreign import ccall "THTensorMath.h THIntTensor_indexAdd"
  c_indexAdd_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_indexAdd :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_indexAdd = const c_indexAdd_
foreign import ccall "THTensorMath.h THIntTensor_indexFill"
  c_indexFill_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> CInt -> IO ()
c_indexFill :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> CInt -> IO ()
c_indexFill = const c_indexFill_
foreign import ccall "THTensorMath.h THIntTensor_take"
  c_take_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> IO ()
c_take :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> IO ()
c_take = const c_take_
foreign import ccall "THTensorMath.h THIntTensor_put"
  c_put_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_put :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_put = const c_put_
foreign import ccall "THTensorMath.h THIntTensor_gather"
  c_gather_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> IO ()
c_gather :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> IO ()
c_gather = const c_gather_
foreign import ccall "THTensorMath.h THIntTensor_scatter"
  c_scatter_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_scatter :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_scatter = const c_scatter_
foreign import ccall "THTensorMath.h THIntTensor_scatterAdd"
  c_scatterAdd_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_scatterAdd :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ()
c_scatterAdd = const c_scatterAdd_
foreign import ccall "THTensorMath.h THIntTensor_scatterFill"
  c_scatterFill_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> CInt -> IO ()
c_scatterFill :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> CInt -> IO ()
c_scatterFill = const c_scatterFill_
foreign import ccall "THTensorMath.h THIntTensor_dot"
  c_dot_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO CLong
c_dot :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO CLong
c_dot = const c_dot_
foreign import ccall "THTensorMath.h THIntTensor_minall"
  c_minall_ :: Ptr C'THIntTensor -> IO CInt
c_minall :: Ptr C'THState -> Ptr C'THIntTensor -> IO CInt
c_minall = const c_minall_
foreign import ccall "THTensorMath.h THIntTensor_maxall"
  c_maxall_ :: Ptr C'THIntTensor -> IO CInt
c_maxall :: Ptr C'THState -> Ptr C'THIntTensor -> IO CInt
c_maxall = const c_maxall_
foreign import ccall "THTensorMath.h THIntTensor_medianall"
  c_medianall_ :: Ptr C'THIntTensor -> IO CInt
c_medianall :: Ptr C'THState -> Ptr C'THIntTensor -> IO CInt
c_medianall = const c_medianall_
foreign import ccall "THTensorMath.h THIntTensor_sumall"
  c_sumall_ :: Ptr C'THIntTensor -> IO CLong
c_sumall :: Ptr C'THState -> Ptr C'THIntTensor -> IO CLong
c_sumall = const c_sumall_
foreign import ccall "THTensorMath.h THIntTensor_prodall"
  c_prodall_ :: Ptr C'THIntTensor -> IO CLong
c_prodall :: Ptr C'THState -> Ptr C'THIntTensor -> IO CLong
c_prodall = const c_prodall_
foreign import ccall "THTensorMath.h THIntTensor_neg"
  c_neg_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_neg :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_neg = const c_neg_
foreign import ccall "THTensorMath.h THIntTensor_add"
  c_add_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_add :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_add = const c_add_
foreign import ccall "THTensorMath.h THIntTensor_sub"
  c_sub_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_sub :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_sub = const c_sub_
foreign import ccall "THTensorMath.h THIntTensor_add_scaled"
  c_add_scaled_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_add_scaled :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_add_scaled = const c_add_scaled_
foreign import ccall "THTensorMath.h THIntTensor_sub_scaled"
  c_sub_scaled_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_sub_scaled :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_sub_scaled = const c_sub_scaled_
foreign import ccall "THTensorMath.h THIntTensor_mul"
  c_mul_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_mul :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_mul = const c_mul_
foreign import ccall "THTensorMath.h THIntTensor_div"
  c_div_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_div :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_div = const c_div_
foreign import ccall "THTensorMath.h THIntTensor_lshift"
  c_lshift_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_lshift :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_lshift = const c_lshift_
foreign import ccall "THTensorMath.h THIntTensor_rshift"
  c_rshift_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_rshift :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_rshift = const c_rshift_
foreign import ccall "THTensorMath.h THIntTensor_fmod"
  c_fmod_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_fmod :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_fmod = const c_fmod_
foreign import ccall "THTensorMath.h THIntTensor_remainder"
  c_remainder_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_remainder :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_remainder = const c_remainder_
foreign import ccall "THTensorMath.h THIntTensor_clamp"
  c_clamp_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_clamp :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_clamp = const c_clamp_
foreign import ccall "THTensorMath.h THIntTensor_bitand"
  c_bitand_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_bitand :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_bitand = const c_bitand_
foreign import ccall "THTensorMath.h THIntTensor_bitor"
  c_bitor_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_bitor :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_bitor = const c_bitor_
foreign import ccall "THTensorMath.h THIntTensor_bitxor"
  c_bitxor_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_bitxor :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_bitxor = const c_bitxor_
foreign import ccall "THTensorMath.h THIntTensor_cadd"
  c_cadd_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> IO ()
c_cadd :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> IO ()
c_cadd = const c_cadd_
foreign import ccall "THTensorMath.h THIntTensor_csub"
  c_csub_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> IO ()
c_csub :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> IO ()
c_csub = const c_csub_
foreign import ccall "THTensorMath.h THIntTensor_cmul"
  c_cmul_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cmul :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cmul = const c_cmul_
foreign import ccall "THTensorMath.h THIntTensor_cpow"
  c_cpow_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cpow :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cpow = const c_cpow_
foreign import ccall "THTensorMath.h THIntTensor_cdiv"
  c_cdiv_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cdiv :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cdiv = const c_cdiv_
foreign import ccall "THTensorMath.h THIntTensor_clshift"
  c_clshift_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_clshift :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_clshift = const c_clshift_
foreign import ccall "THTensorMath.h THIntTensor_crshift"
  c_crshift_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_crshift :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_crshift = const c_crshift_
foreign import ccall "THTensorMath.h THIntTensor_cfmod"
  c_cfmod_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cfmod :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cfmod = const c_cfmod_
foreign import ccall "THTensorMath.h THIntTensor_cremainder"
  c_cremainder_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cremainder :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cremainder = const c_cremainder_
foreign import ccall "THTensorMath.h THIntTensor_cbitand"
  c_cbitand_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cbitand :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cbitand = const c_cbitand_
foreign import ccall "THTensorMath.h THIntTensor_cbitor"
  c_cbitor_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cbitor :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cbitor = const c_cbitor_
foreign import ccall "THTensorMath.h THIntTensor_cbitxor"
  c_cbitxor_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cbitxor :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cbitxor = const c_cbitxor_
foreign import ccall "THTensorMath.h THIntTensor_addcmul"
  c_addcmul_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addcmul :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addcmul = const c_addcmul_
foreign import ccall "THTensorMath.h THIntTensor_addcdiv"
  c_addcdiv_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addcdiv :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addcdiv = const c_addcdiv_
foreign import ccall "THTensorMath.h THIntTensor_addmv"
  c_addmv_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addmv :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addmv = const c_addmv_
foreign import ccall "THTensorMath.h THIntTensor_addmm"
  c_addmm_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addmm :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addmm = const c_addmm_
foreign import ccall "THTensorMath.h THIntTensor_addr"
  c_addr_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addr :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addr = const c_addr_
foreign import ccall "THTensorMath.h THIntTensor_addbmm"
  c_addbmm_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addbmm :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_addbmm = const c_addbmm_
foreign import ccall "THTensorMath.h THIntTensor_baddbmm"
  c_baddbmm_ :: Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_baddbmm :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_baddbmm = const c_baddbmm_
foreign import ccall "THTensorMath.h THIntTensor_match"
  c_match_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_match :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_match = const c_match_
foreign import ccall "THTensorMath.h THIntTensor_numel"
  c_numel_ :: Ptr C'THIntTensor -> IO CPtrdiff
c_numel :: Ptr C'THState -> Ptr C'THIntTensor -> IO CPtrdiff
c_numel = const c_numel_
foreign import ccall "THTensorMath.h THIntTensor_preserveReduceDimSemantics"
  c_preserveReduceDimSemantics_ :: Ptr C'THIntTensor -> CInt -> CInt -> CInt -> IO ()
c_preserveReduceDimSemantics :: Ptr C'THState -> Ptr C'THIntTensor -> CInt -> CInt -> CInt -> IO ()
c_preserveReduceDimSemantics = const c_preserveReduceDimSemantics_
foreign import ccall "THTensorMath.h THIntTensor_max"
  c_max_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_max :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_max = const c_max_
foreign import ccall "THTensorMath.h THIntTensor_min"
  c_min_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_min :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_min = const c_min_
foreign import ccall "THTensorMath.h THIntTensor_kthvalue"
  c_kthvalue_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CLLong -> CInt -> CInt -> IO ()
c_kthvalue :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CLLong -> CInt -> CInt -> IO ()
c_kthvalue = const c_kthvalue_
foreign import ccall "THTensorMath.h THIntTensor_mode"
  c_mode_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_mode :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_mode = const c_mode_
foreign import ccall "THTensorMath.h THIntTensor_median"
  c_median_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_median :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_median = const c_median_
foreign import ccall "THTensorMath.h THIntTensor_sum"
  c_sum_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_sum :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_sum = const c_sum_
foreign import ccall "THTensorMath.h THIntTensor_prod"
  c_prod_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_prod :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_prod = const c_prod_
foreign import ccall "THTensorMath.h THIntTensor_cumsum"
  c_cumsum_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cumsum :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cumsum = const c_cumsum_
foreign import ccall "THTensorMath.h THIntTensor_cumprod"
  c_cumprod_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cumprod :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cumprod = const c_cumprod_
foreign import ccall "THTensorMath.h THIntTensor_sign"
  c_sign_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_sign :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_sign = const c_sign_
foreign import ccall "THTensorMath.h THIntTensor_trace"
  c_trace_ :: Ptr C'THIntTensor -> IO CLong
c_trace :: Ptr C'THState -> Ptr C'THIntTensor -> IO CLong
c_trace = const c_trace_
foreign import ccall "THTensorMath.h THIntTensor_cross"
  c_cross_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cross :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cross = const c_cross_
foreign import ccall "THTensorMath.h THIntTensor_cmax"
  c_cmax_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cmax :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cmax = const c_cmax_
foreign import ccall "THTensorMath.h THIntTensor_cmin"
  c_cmin_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cmin :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_cmin = const c_cmin_
foreign import ccall "THTensorMath.h THIntTensor_cmaxValue"
  c_cmaxValue_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cmaxValue :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cmaxValue = const c_cmaxValue_
foreign import ccall "THTensorMath.h THIntTensor_cminValue"
  c_cminValue_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cminValue :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cminValue = const c_cminValue_
foreign import ccall "THTensorMath.h THIntTensor_zeros"
  c_zeros_ :: Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ()
c_zeros :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ()
c_zeros = const c_zeros_
foreign import ccall "THTensorMath.h THIntTensor_zerosLike"
  c_zerosLike_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_zerosLike :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_zerosLike = const c_zerosLike_
foreign import ccall "THTensorMath.h THIntTensor_ones"
  c_ones_ :: Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ()
c_ones :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ()
c_ones = const c_ones_
foreign import ccall "THTensorMath.h THIntTensor_onesLike"
  c_onesLike_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_onesLike :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_onesLike = const c_onesLike_
foreign import ccall "THTensorMath.h THIntTensor_diag"
  c_diag_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_diag :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_diag = const c_diag_
foreign import ccall "THTensorMath.h THIntTensor_eye"
  c_eye_ :: Ptr C'THIntTensor -> CLLong -> CLLong -> IO ()
c_eye :: Ptr C'THState -> Ptr C'THIntTensor -> CLLong -> CLLong -> IO ()
c_eye = const c_eye_
foreign import ccall "THTensorMath.h THIntTensor_arange"
  c_arange_ :: Ptr C'THIntTensor -> CLong -> CLong -> CLong -> IO ()
c_arange :: Ptr C'THState -> Ptr C'THIntTensor -> CLong -> CLong -> CLong -> IO ()
c_arange = const c_arange_
foreign import ccall "THTensorMath.h THIntTensor_range"
  c_range_ :: Ptr C'THIntTensor -> CLong -> CLong -> CLong -> IO ()
c_range :: Ptr C'THState -> Ptr C'THIntTensor -> CLong -> CLong -> CLong -> IO ()
c_range = const c_range_
foreign import ccall "THTensorMath.h THIntTensor_randperm"
  c_randperm_ :: Ptr C'THIntTensor -> Ptr C'THGenerator -> CLLong -> IO ()
c_randperm :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THGenerator -> CLLong -> IO ()
c_randperm = const c_randperm_
foreign import ccall "THTensorMath.h THIntTensor_reshape"
  c_reshape_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ()
c_reshape :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ()
c_reshape = const c_reshape_
foreign import ccall "THTensorMath.h THIntTensor_sort"
  c_sort_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_sort :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ()
c_sort = const c_sort_
foreign import ccall "THTensorMath.h THIntTensor_topk"
  c_topk_ :: Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CLLong -> CInt -> CInt -> CInt -> IO ()
c_topk :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CLLong -> CInt -> CInt -> CInt -> IO ()
c_topk = const c_topk_
foreign import ccall "THTensorMath.h THIntTensor_tril"
  c_tril_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CLLong -> IO ()
c_tril :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CLLong -> IO ()
c_tril = const c_tril_
foreign import ccall "THTensorMath.h THIntTensor_triu"
  c_triu_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CLLong -> IO ()
c_triu :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CLLong -> IO ()
c_triu = const c_triu_
foreign import ccall "THTensorMath.h THIntTensor_cat"
  c_cat_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cat :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_cat = const c_cat_
foreign import ccall "THTensorMath.h THIntTensor_catArray"
  c_catArray_ :: Ptr C'THIntTensor -> Ptr (Ptr C'THIntTensor) -> CInt -> CInt -> IO ()
c_catArray :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr (Ptr C'THIntTensor) -> CInt -> CInt -> IO ()
c_catArray = const c_catArray_
foreign import ccall "THTensorMath.h THIntTensor_equal"
  c_equal_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO CInt
c_equal :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO CInt
c_equal = const c_equal_
foreign import ccall "THTensorMath.h THIntTensor_ltValue"
  c_ltValue_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_ltValue :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_ltValue = const c_ltValue_
foreign import ccall "THTensorMath.h THIntTensor_leValue"
  c_leValue_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_leValue :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_leValue = const c_leValue_
foreign import ccall "THTensorMath.h THIntTensor_gtValue"
  c_gtValue_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_gtValue :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_gtValue = const c_gtValue_
foreign import ccall "THTensorMath.h THIntTensor_geValue"
  c_geValue_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_geValue :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_geValue = const c_geValue_
foreign import ccall "THTensorMath.h THIntTensor_neValue"
  c_neValue_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_neValue :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_neValue = const c_neValue_
foreign import ccall "THTensorMath.h THIntTensor_eqValue"
  c_eqValue_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_eqValue :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_eqValue = const c_eqValue_
foreign import ccall "THTensorMath.h THIntTensor_ltValueT"
  c_ltValueT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_ltValueT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_ltValueT = const c_ltValueT_
foreign import ccall "THTensorMath.h THIntTensor_leValueT"
  c_leValueT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_leValueT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_leValueT = const c_leValueT_
foreign import ccall "THTensorMath.h THIntTensor_gtValueT"
  c_gtValueT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_gtValueT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_gtValueT = const c_gtValueT_
foreign import ccall "THTensorMath.h THIntTensor_geValueT"
  c_geValueT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_geValueT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_geValueT = const c_geValueT_
foreign import ccall "THTensorMath.h THIntTensor_neValueT"
  c_neValueT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_neValueT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_neValueT = const c_neValueT_
foreign import ccall "THTensorMath.h THIntTensor_eqValueT"
  c_eqValueT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_eqValueT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ()
c_eqValueT = const c_eqValueT_
foreign import ccall "THTensorMath.h THIntTensor_ltTensor"
  c_ltTensor_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_ltTensor :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_ltTensor = const c_ltTensor_
foreign import ccall "THTensorMath.h THIntTensor_leTensor"
  c_leTensor_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_leTensor :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_leTensor = const c_leTensor_
foreign import ccall "THTensorMath.h THIntTensor_gtTensor"
  c_gtTensor_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_gtTensor :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_gtTensor = const c_gtTensor_
foreign import ccall "THTensorMath.h THIntTensor_geTensor"
  c_geTensor_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_geTensor :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_geTensor = const c_geTensor_
foreign import ccall "THTensorMath.h THIntTensor_neTensor"
  c_neTensor_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_neTensor :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_neTensor = const c_neTensor_
foreign import ccall "THTensorMath.h THIntTensor_eqTensor"
  c_eqTensor_ :: Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_eqTensor :: Ptr C'THState -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_eqTensor = const c_eqTensor_
foreign import ccall "THTensorMath.h THIntTensor_ltTensorT"
  c_ltTensorT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_ltTensorT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_ltTensorT = const c_ltTensorT_
foreign import ccall "THTensorMath.h THIntTensor_leTensorT"
  c_leTensorT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_leTensorT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_leTensorT = const c_leTensorT_
foreign import ccall "THTensorMath.h THIntTensor_gtTensorT"
  c_gtTensorT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_gtTensorT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_gtTensorT = const c_gtTensorT_
foreign import ccall "THTensorMath.h THIntTensor_geTensorT"
  c_geTensorT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_geTensorT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_geTensorT = const c_geTensorT_
foreign import ccall "THTensorMath.h THIntTensor_neTensorT"
  c_neTensorT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_neTensorT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_neTensorT = const c_neTensorT_
foreign import ccall "THTensorMath.h THIntTensor_eqTensorT"
  c_eqTensorT_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_eqTensorT :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_eqTensorT = const c_eqTensorT_
foreign import ccall "THTensorMath.h THIntTensor_abs"
  c_abs_ :: Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_abs :: Ptr C'THState -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ()
c_abs = const c_abs_
foreign import ccall "THTensorMath.h &THIntTensor_fill"
  p_fill :: FunPtr (Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_zero"
  p_zero :: FunPtr (Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_maskedFill"
  p_maskedFill :: FunPtr (Ptr C'THIntTensor -> Ptr C'THByteTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_maskedCopy"
  p_maskedCopy :: FunPtr (Ptr C'THIntTensor -> Ptr C'THByteTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_maskedSelect"
  p_maskedSelect :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THByteTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_nonzero"
  p_nonzero :: FunPtr (Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_indexSelect"
  p_indexSelect :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_indexCopy"
  p_indexCopy :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_indexAdd"
  p_indexAdd :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_indexFill"
  p_indexFill :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_take"
  p_take :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THLongTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_put"
  p_put :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_gather"
  p_gather :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_scatter"
  p_scatter :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_scatterAdd"
  p_scatterAdd :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_scatterFill"
  p_scatterFill :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THLongTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_dot"
  p_dot :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO CLong)
foreign import ccall "THTensorMath.h &THIntTensor_minall"
  p_minall :: FunPtr (Ptr C'THIntTensor -> IO CInt)
foreign import ccall "THTensorMath.h &THIntTensor_maxall"
  p_maxall :: FunPtr (Ptr C'THIntTensor -> IO CInt)
foreign import ccall "THTensorMath.h &THIntTensor_medianall"
  p_medianall :: FunPtr (Ptr C'THIntTensor -> IO CInt)
foreign import ccall "THTensorMath.h &THIntTensor_sumall"
  p_sumall :: FunPtr (Ptr C'THIntTensor -> IO CLong)
foreign import ccall "THTensorMath.h &THIntTensor_prodall"
  p_prodall :: FunPtr (Ptr C'THIntTensor -> IO CLong)
foreign import ccall "THTensorMath.h &THIntTensor_neg"
  p_neg :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_add"
  p_add :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_sub"
  p_sub :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_add_scaled"
  p_add_scaled :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_sub_scaled"
  p_sub_scaled :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_mul"
  p_mul :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_div"
  p_div :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_lshift"
  p_lshift :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_rshift"
  p_rshift :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_fmod"
  p_fmod :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_remainder"
  p_remainder :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_clamp"
  p_clamp :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_bitand"
  p_bitand :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_bitor"
  p_bitor :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_bitxor"
  p_bitxor :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cadd"
  p_cadd :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_csub"
  p_csub :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cmul"
  p_cmul :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cpow"
  p_cpow :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cdiv"
  p_cdiv :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_clshift"
  p_clshift :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_crshift"
  p_crshift :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cfmod"
  p_cfmod :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cremainder"
  p_cremainder :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cbitand"
  p_cbitand :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cbitor"
  p_cbitor :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cbitxor"
  p_cbitxor :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_addcmul"
  p_addcmul :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_addcdiv"
  p_addcdiv :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_addmv"
  p_addmv :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_addmm"
  p_addmm :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_addr"
  p_addr :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_addbmm"
  p_addbmm :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_baddbmm"
  p_baddbmm :: FunPtr (Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> CInt -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_match"
  p_match :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_numel"
  p_numel :: FunPtr (Ptr C'THIntTensor -> IO CPtrdiff)
foreign import ccall "THTensorMath.h &THIntTensor_preserveReduceDimSemantics"
  p_preserveReduceDimSemantics :: FunPtr (Ptr C'THIntTensor -> CInt -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_max"
  p_max :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_min"
  p_min :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_kthvalue"
  p_kthvalue :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CLLong -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_mode"
  p_mode :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_median"
  p_median :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_sum"
  p_sum :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_prod"
  p_prod :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cumsum"
  p_cumsum :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cumprod"
  p_cumprod :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_sign"
  p_sign :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_trace"
  p_trace :: FunPtr (Ptr C'THIntTensor -> IO CLong)
foreign import ccall "THTensorMath.h &THIntTensor_cross"
  p_cross :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cmax"
  p_cmax :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cmin"
  p_cmin :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cmaxValue"
  p_cmaxValue :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cminValue"
  p_cminValue :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_zeros"
  p_zeros :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_zerosLike"
  p_zerosLike :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_ones"
  p_ones :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_onesLike"
  p_onesLike :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_diag"
  p_diag :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_eye"
  p_eye :: FunPtr (Ptr C'THIntTensor -> CLLong -> CLLong -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_arange"
  p_arange :: FunPtr (Ptr C'THIntTensor -> CLong -> CLong -> CLong -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_range"
  p_range :: FunPtr (Ptr C'THIntTensor -> CLong -> CLong -> CLong -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_randperm"
  p_randperm :: FunPtr (Ptr C'THIntTensor -> Ptr C'THGenerator -> CLLong -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_reshape"
  p_reshape :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THLongStorage -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_sort"
  p_sort :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_topk"
  p_topk :: FunPtr (Ptr C'THIntTensor -> Ptr C'THLongTensor -> Ptr C'THIntTensor -> CLLong -> CInt -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_tril"
  p_tril :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CLLong -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_triu"
  p_triu :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CLLong -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_cat"
  p_cat :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_catArray"
  p_catArray :: FunPtr (Ptr C'THIntTensor -> Ptr (Ptr C'THIntTensor) -> CInt -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_equal"
  p_equal :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO CInt)
foreign import ccall "THTensorMath.h &THIntTensor_ltValue"
  p_ltValue :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_leValue"
  p_leValue :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_gtValue"
  p_gtValue :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_geValue"
  p_geValue :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_neValue"
  p_neValue :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_eqValue"
  p_eqValue :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_ltValueT"
  p_ltValueT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_leValueT"
  p_leValueT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_gtValueT"
  p_gtValueT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_geValueT"
  p_geValueT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_neValueT"
  p_neValueT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_eqValueT"
  p_eqValueT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> CInt -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_ltTensor"
  p_ltTensor :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_leTensor"
  p_leTensor :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_gtTensor"
  p_gtTensor :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_geTensor"
  p_geTensor :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_neTensor"
  p_neTensor :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_eqTensor"
  p_eqTensor :: FunPtr (Ptr C'THByteTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_ltTensorT"
  p_ltTensorT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_leTensorT"
  p_leTensorT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_gtTensorT"
  p_gtTensorT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_geTensorT"
  p_geTensorT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_neTensorT"
  p_neTensorT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_eqTensorT"
  p_eqTensorT :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())
foreign import ccall "THTensorMath.h &THIntTensor_abs"
  p_abs :: FunPtr (Ptr C'THIntTensor -> Ptr C'THIntTensor -> IO ())