{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Internal.Unmanaged.Native.Native8 where
import Foreign.C.String
import Foreign.C.Types
import Foreign
import Torch.Internal.Type
import qualified Language.C.Inline.Cpp as C
import qualified Language.C.Inline.Cpp.Unsafe as C
import qualified Language.C.Inline.Context as C
import qualified Language.C.Types as C
C.context $ C.cppCtx <> mempty { C.ctxTypesTable = typeTable }
C.include "<vector>"
C.include "<ATen/Tensor.h>"
C.include "<ATen/Functions.h>"
to_mkldnn_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
to_mkldnn_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
to_mkldnn_backward_tt Ptr Tensor
_grad Ptr Tensor
_input =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::to_mkldnn_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _input)));
}|]
quantize_per_tensor_dynamic_tsb
:: Ptr Tensor
-> ScalarType
-> CBool
-> IO (Ptr Tensor)
quantize_per_tensor_dynamic_tsb :: Ptr Tensor -> ScalarType -> CBool -> IO (Ptr Tensor)
quantize_per_tensor_dynamic_tsb Ptr Tensor
_self ScalarType
_dtype CBool
_reduce_range =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantize_per_tensor_dynamic(
*$(at::Tensor* _self)
, $(at::ScalarType _dtype)
, $(bool _reduce_range)));
}|]
quantize_per_tensor_tdls
:: Ptr Tensor
-> CDouble
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
quantize_per_tensor_tdls :: Ptr Tensor -> CDouble -> Int64 -> ScalarType -> IO (Ptr Tensor)
quantize_per_tensor_tdls Ptr Tensor
_self CDouble
_scale Int64
_zero_point ScalarType
_dtype =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantize_per_tensor(
*$(at::Tensor* _self)
, $(double _scale)
, $(int64_t _zero_point)
, $(at::ScalarType _dtype)));
}|]
quantize_per_tensor_ttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> ScalarType
-> IO (Ptr Tensor)
quantize_per_tensor_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
quantize_per_tensor_ttts Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point ScalarType
_dtype =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantize_per_tensor(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(at::ScalarType _dtype)));
}|]
quantize_per_tensor_ltts
:: Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> ScalarType
-> IO (Ptr TensorList)
quantize_per_tensor_ltts :: Ptr TensorList
-> Ptr Tensor -> Ptr Tensor -> ScalarType -> IO (Ptr TensorList)
quantize_per_tensor_ltts Ptr TensorList
_tensors Ptr Tensor
_scales Ptr Tensor
_zero_points ScalarType
_dtype =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::quantize_per_tensor(
*$(std::vector<at::Tensor>* _tensors)
, *$(at::Tensor* _scales)
, *$(at::Tensor* _zero_points)
, $(at::ScalarType _dtype)));
}|]
quantize_per_channel_tttls
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
quantize_per_channel_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
quantize_per_channel_tttls Ptr Tensor
_self Ptr Tensor
_scales Ptr Tensor
_zero_points Int64
_axis ScalarType
_dtype =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantize_per_channel(
*$(at::Tensor* _self)
, *$(at::Tensor* _scales)
, *$(at::Tensor* _zero_points)
, $(int64_t _axis)
, $(at::ScalarType _dtype)));
}|]
dequantize_t
:: Ptr Tensor
-> IO (Ptr Tensor)
dequantize_t :: Ptr Tensor -> IO (Ptr Tensor)
dequantize_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::dequantize(
*$(at::Tensor* _self)));
}|]
dequantize_l
:: Ptr TensorList
-> IO (Ptr TensorList)
dequantize_l :: Ptr TensorList -> IO (Ptr TensorList)
dequantize_l Ptr TensorList
_tensors =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::dequantize(
*$(std::vector<at::Tensor>* _tensors)));
}|]
q_scale_t
:: Ptr Tensor
-> IO (CDouble)
q_scale_t :: Ptr Tensor -> IO CDouble
q_scale_t Ptr Tensor
_self =
[C.throwBlock| double { return (at::q_scale(
*$(at::Tensor* _self)));
}|]
q_zero_point_t
:: Ptr Tensor
-> IO (Int64)
q_zero_point_t :: Ptr Tensor -> IO Int64
q_zero_point_t Ptr Tensor
_self =
[C.throwBlock| int64_t { return (at::q_zero_point(
*$(at::Tensor* _self)));
}|]
q_per_channel_scales_t
:: Ptr Tensor
-> IO (Ptr Tensor)
q_per_channel_scales_t :: Ptr Tensor -> IO (Ptr Tensor)
q_per_channel_scales_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::q_per_channel_scales(
*$(at::Tensor* _self)));
}|]
q_per_channel_zero_points_t
:: Ptr Tensor
-> IO (Ptr Tensor)
q_per_channel_zero_points_t :: Ptr Tensor -> IO (Ptr Tensor)
q_per_channel_zero_points_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::q_per_channel_zero_points(
*$(at::Tensor* _self)));
}|]
q_per_channel_axis_t
:: Ptr Tensor
-> IO (Int64)
q_per_channel_axis_t :: Ptr Tensor -> IO Int64
q_per_channel_axis_t Ptr Tensor
_self =
[C.throwBlock| int64_t { return (at::q_per_channel_axis(
*$(at::Tensor* _self)));
}|]
int_repr_t
:: Ptr Tensor
-> IO (Ptr Tensor)
int_repr_t :: Ptr Tensor -> IO (Ptr Tensor)
int_repr_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::int_repr(
*$(at::Tensor* _self)));
}|]
_make_per_tensor_quantized_tensor_tdl
:: Ptr Tensor
-> CDouble
-> Int64
-> IO (Ptr Tensor)
_make_per_tensor_quantized_tensor_tdl :: Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor)
_make_per_tensor_quantized_tensor_tdl Ptr Tensor
_self CDouble
_scale Int64
_zero_point =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_make_per_tensor_quantized_tensor(
*$(at::Tensor* _self)
, $(double _scale)
, $(int64_t _zero_point)));
}|]
_make_per_channel_quantized_tensor_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_make_per_channel_quantized_tensor_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
_make_per_channel_quantized_tensor_tttl Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_make_per_channel_quantized_tensor(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)));
}|]
fake_quantize_per_tensor_affine_tdlll
:: Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
fake_quantize_per_tensor_affine_tdlll :: Ptr Tensor -> CDouble -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
fake_quantize_per_tensor_affine_tdlll Ptr Tensor
_self CDouble
_scale Int64
_zero_point Int64
_quant_min Int64
_quant_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fake_quantize_per_tensor_affine(
*$(at::Tensor* _self)
, $(double _scale)
, $(int64_t _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fake_quantize_per_tensor_affine_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fake_quantize_per_tensor_affine_tttll :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fake_quantize_per_tensor_affine_tttll Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_quant_min Int64
_quant_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fake_quantize_per_tensor_affine(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fake_quantize_per_tensor_affine_cachemask_tdlll
:: Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
fake_quantize_per_tensor_affine_cachemask_tdlll :: Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
fake_quantize_per_tensor_affine_cachemask_tdlll Ptr Tensor
_self CDouble
_scale Int64
_zero_point Int64
_quant_min Int64
_quant_max =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::fake_quantize_per_tensor_affine_cachemask(
*$(at::Tensor* _self)
, $(double _scale)
, $(int64_t _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
_fake_quantize_per_tensor_affine_cachemask_tensor_qparams_ttttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_fake_quantize_per_tensor_affine_cachemask_tensor_qparams_ttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_fake_quantize_per_tensor_affine_cachemask_tensor_qparams_ttttll Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Ptr Tensor
_fake_quant_enabled Int64
_quant_min Int64
_quant_max =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_fake_quantize_per_tensor_affine_cachemask_tensor_qparams(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, *$(at::Tensor* _fake_quant_enabled)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fake_quantize_per_tensor_affine_cachemask_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
fake_quantize_per_tensor_affine_cachemask_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fake_quantize_per_tensor_affine_cachemask_backward_tt Ptr Tensor
_grad Ptr Tensor
_mask =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fake_quantize_per_tensor_affine_cachemask_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _mask)));
}|]
_fake_quantize_learnable_per_tensor_affine_tttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_tensor_affine_tttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_tensor_affine_tttlld Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_quant_min Int64
_quant_max CDouble
_grad_factor =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_fake_quantize_learnable_per_tensor_affine(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(double _grad_factor)));
}|]
_fake_quantize_learnable_per_tensor_affine_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_tensor_affine_tttll :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
_fake_quantize_learnable_per_tensor_affine_tttll Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_quant_min Int64
_quant_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_fake_quantize_learnable_per_tensor_affine(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
_fake_quantize_learnable_per_tensor_affine_backward_ttttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_fake_quantize_learnable_per_tensor_affine_backward_ttttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_fake_quantize_learnable_per_tensor_affine_backward_ttttlld Ptr Tensor
_grad Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_quant_min Int64
_quant_max CDouble
_grad_factor =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_fake_quantize_learnable_per_tensor_affine_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(double _grad_factor)));
}|]
_fake_quantize_learnable_per_tensor_affine_backward_ttttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_fake_quantize_learnable_per_tensor_affine_backward_ttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_fake_quantize_learnable_per_tensor_affine_backward_ttttll Ptr Tensor
_grad Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_quant_min Int64
_quant_max =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_fake_quantize_learnable_per_tensor_affine_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fake_quantize_per_channel_affine_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
fake_quantize_per_channel_affine_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
fake_quantize_per_channel_affine_tttlll Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis Int64
_quant_min Int64
_quant_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fake_quantize_per_channel_affine(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fake_quantize_per_channel_affine_cachemask_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
fake_quantize_per_channel_affine_cachemask_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
fake_quantize_per_channel_affine_cachemask_tttlll Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis Int64
_quant_min Int64
_quant_max =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::fake_quantize_per_channel_affine_cachemask(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fake_quantize_per_channel_affine_cachemask_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
fake_quantize_per_channel_affine_cachemask_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fake_quantize_per_channel_affine_cachemask_backward_tt Ptr Tensor
_grad Ptr Tensor
_mask =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fake_quantize_per_channel_affine_cachemask_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _mask)));
}|]
_fake_quantize_learnable_per_channel_affine_tttllld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_channel_affine_tttllld :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_channel_affine_tttllld Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis Int64
_quant_min Int64
_quant_max CDouble
_grad_factor =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_fake_quantize_learnable_per_channel_affine(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(double _grad_factor)));
}|]
_fake_quantize_learnable_per_channel_affine_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_channel_affine_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
_fake_quantize_learnable_per_channel_affine_tttlll Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis Int64
_quant_min Int64
_quant_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_fake_quantize_learnable_per_channel_affine(
*$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
_fake_quantize_learnable_per_channel_affine_backward_ttttllld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_fake_quantize_learnable_per_channel_affine_backward_ttttllld :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_fake_quantize_learnable_per_channel_affine_backward_ttttllld Ptr Tensor
_grad Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis Int64
_quant_min Int64
_quant_max CDouble
_grad_factor =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_fake_quantize_learnable_per_channel_affine_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(double _grad_factor)));
}|]
_fake_quantize_learnable_per_channel_affine_backward_ttttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_fake_quantize_learnable_per_channel_affine_backward_ttttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_fake_quantize_learnable_per_channel_affine_backward_ttttlll Ptr Tensor
_grad Ptr Tensor
_self Ptr Tensor
_scale Ptr Tensor
_zero_point Int64
_axis Int64
_quant_min Int64
_quant_max =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_fake_quantize_learnable_per_channel_affine_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _self)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(int64_t _axis)
, $(int64_t _quant_min)
, $(int64_t _quant_max)));
}|]
fused_moving_avg_obs_fake_quant_tttttttdlllbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllbb Ptr Tensor
_self Ptr Tensor
_observer_on Ptr Tensor
_fake_quant_on Ptr Tensor
_running_min Ptr Tensor
_running_max Ptr Tensor
_scale Ptr Tensor
_zero_point CDouble
_averaging_const Int64
_quant_min Int64
_quant_max Int64
_ch_axis CBool
_per_row_fake_quant CBool
_symmetric_quant =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fused_moving_avg_obs_fake_quant(
*$(at::Tensor* _self)
, *$(at::Tensor* _observer_on)
, *$(at::Tensor* _fake_quant_on)
, *$(at::Tensor* _running_min)
, *$(at::Tensor* _running_max)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(double _averaging_const)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(int64_t _ch_axis)
, $(bool _per_row_fake_quant)
, $(bool _symmetric_quant)));
}|]
fused_moving_avg_obs_fake_quant_tttttttdlllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (Ptr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (Ptr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllb Ptr Tensor
_self Ptr Tensor
_observer_on Ptr Tensor
_fake_quant_on Ptr Tensor
_running_min Ptr Tensor
_running_max Ptr Tensor
_scale Ptr Tensor
_zero_point CDouble
_averaging_const Int64
_quant_min Int64
_quant_max Int64
_ch_axis CBool
_per_row_fake_quant =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fused_moving_avg_obs_fake_quant(
*$(at::Tensor* _self)
, *$(at::Tensor* _observer_on)
, *$(at::Tensor* _fake_quant_on)
, *$(at::Tensor* _running_min)
, *$(at::Tensor* _running_max)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(double _averaging_const)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(int64_t _ch_axis)
, $(bool _per_row_fake_quant)));
}|]
fused_moving_avg_obs_fake_quant_tttttttdlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlll Ptr Tensor
_self Ptr Tensor
_observer_on Ptr Tensor
_fake_quant_on Ptr Tensor
_running_min Ptr Tensor
_running_max Ptr Tensor
_scale Ptr Tensor
_zero_point CDouble
_averaging_const Int64
_quant_min Int64
_quant_max Int64
_ch_axis =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fused_moving_avg_obs_fake_quant(
*$(at::Tensor* _self)
, *$(at::Tensor* _observer_on)
, *$(at::Tensor* _fake_quant_on)
, *$(at::Tensor* _running_min)
, *$(at::Tensor* _running_max)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(double _averaging_const)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(int64_t _ch_axis)));
}|]
_fused_moving_avg_obs_fq_helper_tttttttdlllbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_fused_moving_avg_obs_fq_helper_tttttttdlllbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_fused_moving_avg_obs_fq_helper_tttttttdlllbb Ptr Tensor
_self Ptr Tensor
_observer_on Ptr Tensor
_fake_quant_on Ptr Tensor
_running_min Ptr Tensor
_running_max Ptr Tensor
_scale Ptr Tensor
_zero_point CDouble
_averaging_const Int64
_quant_min Int64
_quant_max Int64
_ch_axis CBool
_per_row_fake_quant CBool
_symmetric_quant =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_fused_moving_avg_obs_fq_helper(
*$(at::Tensor* _self)
, *$(at::Tensor* _observer_on)
, *$(at::Tensor* _fake_quant_on)
, *$(at::Tensor* _running_min)
, *$(at::Tensor* _running_max)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(double _averaging_const)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(int64_t _ch_axis)
, $(bool _per_row_fake_quant)
, $(bool _symmetric_quant)));
}|]
_fused_moving_avg_obs_fq_helper_tttttttdlllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_fused_moving_avg_obs_fq_helper_tttttttdlllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_fused_moving_avg_obs_fq_helper_tttttttdlllb Ptr Tensor
_self Ptr Tensor
_observer_on Ptr Tensor
_fake_quant_on Ptr Tensor
_running_min Ptr Tensor
_running_max Ptr Tensor
_scale Ptr Tensor
_zero_point CDouble
_averaging_const Int64
_quant_min Int64
_quant_max Int64
_ch_axis CBool
_per_row_fake_quant =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_fused_moving_avg_obs_fq_helper(
*$(at::Tensor* _self)
, *$(at::Tensor* _observer_on)
, *$(at::Tensor* _fake_quant_on)
, *$(at::Tensor* _running_min)
, *$(at::Tensor* _running_max)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(double _averaging_const)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(int64_t _ch_axis)
, $(bool _per_row_fake_quant)));
}|]
_fused_moving_avg_obs_fq_helper_tttttttdlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_fused_moving_avg_obs_fq_helper_tttttttdlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_fused_moving_avg_obs_fq_helper_tttttttdlll Ptr Tensor
_self Ptr Tensor
_observer_on Ptr Tensor
_fake_quant_on Ptr Tensor
_running_min Ptr Tensor
_running_max Ptr Tensor
_scale Ptr Tensor
_zero_point CDouble
_averaging_const Int64
_quant_min Int64
_quant_max Int64
_ch_axis =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_fused_moving_avg_obs_fq_helper(
*$(at::Tensor* _self)
, *$(at::Tensor* _observer_on)
, *$(at::Tensor* _fake_quant_on)
, *$(at::Tensor* _running_min)
, *$(at::Tensor* _running_max)
, *$(at::Tensor* _scale)
, *$(at::Tensor* _zero_point)
, $(double _averaging_const)
, $(int64_t _quant_min)
, $(int64_t _quant_max)
, $(int64_t _ch_axis)));
}|]
_choose_qparams_per_tensor_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(CDouble,Int64)))
_choose_qparams_per_tensor_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(CDouble, Int64)))
_choose_qparams_per_tensor_tb Ptr Tensor
_self CBool
_reduce_range =
[C.throwBlock| std::tuple<double,int64_t>* { return new std::tuple<double,int64_t>(at::_choose_qparams_per_tensor(
*$(at::Tensor* _self)
, $(bool _reduce_range)));
}|]
_choose_qparams_per_tensor_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(CDouble,Int64)))
_choose_qparams_per_tensor_t :: Ptr Tensor -> IO (Ptr (StdTuple '(CDouble, Int64)))
_choose_qparams_per_tensor_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<double,int64_t>* { return new std::tuple<double,int64_t>(at::_choose_qparams_per_tensor(
*$(at::Tensor* _self)));
}|]
_saturate_weight_to_fp16_t
:: Ptr Tensor
-> IO (Ptr Tensor)
_saturate_weight_to_fp16_t :: Ptr Tensor -> IO (Ptr Tensor)
_saturate_weight_to_fp16_t Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_saturate_weight_to_fp16(
*$(at::Tensor* _weight)));
}|]
choose_qparams_optimized_tlldl
:: Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
choose_qparams_optimized_tlldl :: Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
choose_qparams_optimized_tlldl Ptr Tensor
_input Int64
_numel Int64
_n_bins CDouble
_ratio Int64
_bit_width =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::choose_qparams_optimized(
*$(at::Tensor* _input)
, $(int64_t _numel)
, $(int64_t _n_bins)
, $(double _ratio)
, $(int64_t _bit_width)));
}|]
_to_copy_tobM
:: Ptr Tensor
-> Ptr TensorOptions
-> CBool
-> MemoryFormat
-> IO (Ptr Tensor)
_to_copy_tobM :: Ptr Tensor
-> Ptr TensorOptions -> CBool -> ScalarType -> IO (Ptr Tensor)
_to_copy_tobM Ptr Tensor
_self Ptr TensorOptions
_options CBool
_non_blocking ScalarType
_memory_format =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_to_copy(
*$(at::Tensor* _self)
, *$(at::TensorOptions* _options)
, $(bool _non_blocking)
, $(at::MemoryFormat _memory_format)));
}|]
_to_copy_tob
:: Ptr Tensor
-> Ptr TensorOptions
-> CBool
-> IO (Ptr Tensor)
_to_copy_tob :: Ptr Tensor -> Ptr TensorOptions -> CBool -> IO (Ptr Tensor)
_to_copy_tob Ptr Tensor
_self Ptr TensorOptions
_options CBool
_non_blocking =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_to_copy(
*$(at::Tensor* _self)
, *$(at::TensorOptions* _options)
, $(bool _non_blocking)));
}|]
_to_copy_to
:: Ptr Tensor
-> Ptr TensorOptions
-> IO (Ptr Tensor)
_to_copy_to :: Ptr Tensor -> Ptr TensorOptions -> IO (Ptr Tensor)
_to_copy_to Ptr Tensor
_self Ptr TensorOptions
_options =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_to_copy(
*$(at::Tensor* _self)
, *$(at::TensorOptions* _options)));
}|]
_to_copy_t
:: Ptr Tensor
-> IO (Ptr Tensor)
_to_copy_t :: Ptr Tensor -> IO (Ptr Tensor)
_to_copy_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_to_copy(
*$(at::Tensor* _self)));
}|]
meshgrid_l
:: Ptr TensorList
-> IO (Ptr TensorList)
meshgrid_l :: Ptr TensorList -> IO (Ptr TensorList)
meshgrid_l Ptr TensorList
_tensors =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::meshgrid(
*$(std::vector<at::Tensor>* _tensors)));
}|]
meshgrid_ls
:: Ptr TensorList
-> Ptr StdString
-> IO (Ptr TensorList)
meshgrid_ls :: Ptr TensorList -> Ptr StdString -> IO (Ptr TensorList)
meshgrid_ls Ptr TensorList
_tensors Ptr StdString
_indexing =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::meshgrid(
*$(std::vector<at::Tensor>* _tensors)
, *$(std::string* _indexing)));
}|]
cartesian_prod_l
:: Ptr TensorList
-> IO (Ptr Tensor)
cartesian_prod_l :: Ptr TensorList -> IO (Ptr Tensor)
cartesian_prod_l Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cartesian_prod(
*$(std::vector<at::Tensor>* _tensors)));
}|]
combinations_tlb
:: Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr Tensor)
combinations_tlb :: Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor)
combinations_tlb Ptr Tensor
_self Int64
_r CBool
_with_replacement =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::combinations(
*$(at::Tensor* _self)
, $(int64_t _r)
, $(bool _with_replacement)));
}|]
combinations_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
combinations_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
combinations_tl Ptr Tensor
_self Int64
_r =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::combinations(
*$(at::Tensor* _self)
, $(int64_t _r)));
}|]
combinations_t
:: Ptr Tensor
-> IO (Ptr Tensor)
combinations_t :: Ptr Tensor -> IO (Ptr Tensor)
combinations_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::combinations(
*$(at::Tensor* _self)));
}|]
result_type_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (ScalarType)
result_type_tt :: Ptr Tensor -> Ptr Tensor -> IO ScalarType
result_type_tt Ptr Tensor
_tensor Ptr Tensor
_other =
[C.throwBlock| at::ScalarType { return (at::result_type(
*$(at::Tensor* _tensor)
, *$(at::Tensor* _other)));
}|]
result_type_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (ScalarType)
result_type_ts :: Ptr Tensor -> Ptr Scalar -> IO ScalarType
result_type_ts Ptr Tensor
_tensor Ptr Scalar
_other =
[C.throwBlock| at::ScalarType { return (at::result_type(
*$(at::Tensor* _tensor)
, *$(at::Scalar* _other)));
}|]
result_type_st
:: Ptr Scalar
-> Ptr Tensor
-> IO (ScalarType)
result_type_st :: Ptr Scalar -> Ptr Tensor -> IO ScalarType
result_type_st Ptr Scalar
_scalar Ptr Tensor
_tensor =
[C.throwBlock| at::ScalarType { return (at::result_type(
*$(at::Scalar* _scalar)
, *$(at::Tensor* _tensor)));
}|]
result_type_ss
:: Ptr Scalar
-> Ptr Scalar
-> IO (ScalarType)
result_type_ss :: Ptr Scalar -> Ptr Scalar -> IO ScalarType
result_type_ss Ptr Scalar
_scalar1 Ptr Scalar
_scalar2 =
[C.throwBlock| at::ScalarType { return (at::result_type(
*$(at::Scalar* _scalar1)
, *$(at::Scalar* _scalar2)));
}|]
can_cast_ss
:: ScalarType
-> ScalarType
-> IO (CBool)
can_cast_ss :: ScalarType -> ScalarType -> IO CBool
can_cast_ss ScalarType
_from ScalarType
_to =
[C.throwBlock| bool { return (at::can_cast(
$(at::ScalarType _from)
, $(at::ScalarType _to)));
}|]
promote_types_ss
:: ScalarType
-> ScalarType
-> IO (ScalarType)
promote_types_ss :: ScalarType -> ScalarType -> IO ScalarType
promote_types_ss ScalarType
_type1 ScalarType
_type2 =
[C.throwBlock| at::ScalarType { return (at::promote_types(
$(at::ScalarType _type1)
, $(at::ScalarType _type2)));
}|]
_local_scalar_dense_t
:: Ptr Tensor
-> IO (Ptr Scalar)
_local_scalar_dense_t :: Ptr Tensor -> IO (Ptr Scalar)
_local_scalar_dense_t Ptr Tensor
_self =
[C.throwBlock| at::Scalar* { return new at::Scalar(at::_local_scalar_dense(
*$(at::Tensor* _self)));
}|]
_thnn_fused_lstm_cell_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_thnn_fused_lstm_cell_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_thnn_fused_lstm_cell_ttttt Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_cx Ptr Tensor
_input_bias Ptr Tensor
_hidden_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_thnn_fused_lstm_cell(
*$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _cx)
, *$(at::Tensor* _input_bias)
, *$(at::Tensor* _hidden_bias)));
}|]
_thnn_fused_lstm_cell_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_thnn_fused_lstm_cell_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_thnn_fused_lstm_cell_tttt Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_cx Ptr Tensor
_input_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_thnn_fused_lstm_cell(
*$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _cx)
, *$(at::Tensor* _input_bias)));
}|]
_thnn_fused_lstm_cell_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_thnn_fused_lstm_cell_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_thnn_fused_lstm_cell_ttt Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_cx =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_thnn_fused_lstm_cell(
*$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _cx)));
}|]
_thnn_fused_lstm_cell_backward_tttttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)))
_thnn_fused_lstm_cell_backward_tttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
_thnn_fused_lstm_cell_backward_tttttb Ptr Tensor
_grad_hy Ptr Tensor
_grad_cy Ptr Tensor
_cx Ptr Tensor
_cy Ptr Tensor
_workspace CBool
_has_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_thnn_fused_lstm_cell_backward(
*$(at::Tensor* _grad_hy)
, *$(at::Tensor* _grad_cy)
, *$(at::Tensor* _cx)
, *$(at::Tensor* _cy)
, *$(at::Tensor* _workspace)
, $(bool _has_bias)));
}|]
_thnn_differentiable_lstm_cell_backward_tttttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)))
_thnn_differentiable_lstm_cell_backward_tttttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
_thnn_differentiable_lstm_cell_backward_tttttttt Ptr Tensor
_grad_hy Ptr Tensor
_grad_cy Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_input_bias Ptr Tensor
_hidden_bias Ptr Tensor
_cx Ptr Tensor
_cy =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_thnn_differentiable_lstm_cell_backward(
*$(at::Tensor* _grad_hy)
, *$(at::Tensor* _grad_cy)
, *$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _input_bias)
, *$(at::Tensor* _hidden_bias)
, *$(at::Tensor* _cx)
, *$(at::Tensor* _cy)));
}|]
_thnn_fused_gru_cell_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_thnn_fused_gru_cell_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_thnn_fused_gru_cell_ttttt Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_hx Ptr Tensor
_input_bias Ptr Tensor
_hidden_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_thnn_fused_gru_cell(
*$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _input_bias)
, *$(at::Tensor* _hidden_bias)));
}|]
_thnn_fused_gru_cell_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_thnn_fused_gru_cell_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_thnn_fused_gru_cell_tttt Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_hx Ptr Tensor
_input_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_thnn_fused_gru_cell(
*$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _input_bias)));
}|]
_thnn_fused_gru_cell_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_thnn_fused_gru_cell_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_thnn_fused_gru_cell_ttt Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_hx =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_thnn_fused_gru_cell(
*$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _hx)));
}|]
_thnn_fused_gru_cell_backward_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)))
_thnn_fused_gru_cell_backward_ttb :: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
_thnn_fused_gru_cell_backward_ttb Ptr Tensor
_grad_hy Ptr Tensor
_workspace CBool
_has_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_thnn_fused_gru_cell_backward(
*$(at::Tensor* _grad_hy)
, *$(at::Tensor* _workspace)
, $(bool _has_bias)));
}|]
_thnn_differentiable_gru_cell_backward_tttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)))
_thnn_differentiable_gru_cell_backward_tttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
_thnn_differentiable_gru_cell_backward_tttttt Ptr Tensor
_grad_hy Ptr Tensor
_input_gates Ptr Tensor
_hidden_gates Ptr Tensor
_hx Ptr Tensor
_input_bias Ptr Tensor
_hidden_bias =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_thnn_differentiable_gru_cell_backward(
*$(at::Tensor* _grad_hy)
, *$(at::Tensor* _input_gates)
, *$(at::Tensor* _hidden_gates)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _input_bias)
, *$(at::Tensor* _hidden_bias)));
}|]
lstm_tllbldbbb
:: Ptr Tensor
-> Ptr TensorList
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lstm_tllbldbbb :: Ptr Tensor
-> Ptr TensorList
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lstm_tllbldbbb Ptr Tensor
_input Ptr TensorList
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional CBool
_batch_first =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lstm(
*$(at::Tensor* _input)
, *$(std::vector<at::Tensor>* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)
, $(bool _batch_first)));
}|]
lstm_ttllbldbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lstm_ttllbldbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lstm_ttllbldbb Ptr Tensor
_data Ptr Tensor
_batch_sizes Ptr TensorList
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lstm(
*$(at::Tensor* _data)
, *$(at::Tensor* _batch_sizes)
, *$(std::vector<at::Tensor>* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)));
}|]
gru_ttlbldbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
gru_ttlbldbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
gru_ttlbldbbb Ptr Tensor
_input Ptr Tensor
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional CBool
_batch_first =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::gru(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)
, $(bool _batch_first)));
}|]
gru_tttlbldbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
gru_tttlbldbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
gru_tttlbldbb Ptr Tensor
_data Ptr Tensor
_batch_sizes Ptr Tensor
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::gru(
*$(at::Tensor* _data)
, *$(at::Tensor* _batch_sizes)
, *$(at::Tensor* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)));
}|]
rnn_tanh_ttlbldbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
rnn_tanh_ttlbldbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
rnn_tanh_ttlbldbbb Ptr Tensor
_input Ptr Tensor
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional CBool
_batch_first =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::rnn_tanh(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)
, $(bool _batch_first)));
}|]
rnn_tanh_tttlbldbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
rnn_tanh_tttlbldbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
rnn_tanh_tttlbldbb Ptr Tensor
_data Ptr Tensor
_batch_sizes Ptr Tensor
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::rnn_tanh(
*$(at::Tensor* _data)
, *$(at::Tensor* _batch_sizes)
, *$(at::Tensor* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)));
}|]
rnn_relu_ttlbldbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
rnn_relu_ttlbldbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
rnn_relu_ttlbldbbb Ptr Tensor
_input Ptr Tensor
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional CBool
_batch_first =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::rnn_relu(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)
, $(bool _batch_first)));
}|]
rnn_relu_tttlbldbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
rnn_relu_tttlbldbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
rnn_relu_tttlbldbb Ptr Tensor
_data Ptr Tensor
_batch_sizes Ptr Tensor
_hx Ptr TensorList
_params CBool
_has_biases Int64
_num_layers CDouble
_dropout CBool
_train CBool
_bidirectional =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::rnn_relu(
*$(at::Tensor* _data)
, *$(at::Tensor* _batch_sizes)
, *$(at::Tensor* _hx)
, *$(std::vector<at::Tensor>* _params)
, $(bool _has_biases)
, $(int64_t _num_layers)
, $(double _dropout)
, $(bool _train)
, $(bool _bidirectional)));
}|]
lstm_cell_tltttt
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
lstm_cell_tltttt :: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
lstm_cell_tltttt Ptr Tensor
_input Ptr TensorList
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::lstm_cell(
*$(at::Tensor* _input)
, *$(std::vector<at::Tensor>* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)));
}|]
lstm_cell_tlttt
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
lstm_cell_tlttt :: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
lstm_cell_tlttt Ptr Tensor
_input Ptr TensorList
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::lstm_cell(
*$(at::Tensor* _input)
, *$(std::vector<at::Tensor>* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)));
}|]
lstm_cell_tltt
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
lstm_cell_tltt :: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
lstm_cell_tltt Ptr Tensor
_input Ptr TensorList
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::lstm_cell(
*$(at::Tensor* _input)
, *$(std::vector<at::Tensor>* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)));
}|]
gru_cell_tttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gru_cell_tttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gru_cell_tttttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gru_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)));
}|]
gru_cell_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gru_cell_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gru_cell_ttttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gru_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)));
}|]
gru_cell_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gru_cell_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
gru_cell_tttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gru_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)));
}|]
rnn_tanh_cell_tttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_tanh_cell_tttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_tanh_cell_tttttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::rnn_tanh_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)));
}|]
rnn_tanh_cell_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_tanh_cell_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_tanh_cell_ttttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::rnn_tanh_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)));
}|]
rnn_tanh_cell_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_tanh_cell_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
rnn_tanh_cell_tttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::rnn_tanh_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)));
}|]
rnn_relu_cell_tttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_relu_cell_tttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_relu_cell_tttttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::rnn_relu_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)));
}|]
rnn_relu_cell_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_relu_cell_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_relu_cell_ttttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::rnn_relu_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)));
}|]
rnn_relu_cell_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
rnn_relu_cell_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
rnn_relu_cell_tttt Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::rnn_relu_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)));
}|]
quantized_lstm_cell_tlttttttttssss
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
quantized_lstm_cell_tlttttttttssss :: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
quantized_lstm_cell_tlttttttttssss Ptr Tensor
_input Ptr TensorList
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh Ptr Tensor
_packed_ih Ptr Tensor
_packed_hh Ptr Tensor
_col_offsets_ih Ptr Tensor
_col_offsets_hh Ptr Scalar
_scale_ih Ptr Scalar
_scale_hh Ptr Scalar
_zero_point_ih Ptr Scalar
_zero_point_hh =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::quantized_lstm_cell(
*$(at::Tensor* _input)
, *$(std::vector<at::Tensor>* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)
, *$(at::Tensor* _packed_ih)
, *$(at::Tensor* _packed_hh)
, *$(at::Tensor* _col_offsets_ih)
, *$(at::Tensor* _col_offsets_hh)
, *$(at::Scalar* _scale_ih)
, *$(at::Scalar* _scale_hh)
, *$(at::Scalar* _zero_point_ih)
, *$(at::Scalar* _zero_point_hh)));
}|]
quantized_gru_cell_ttttttttttssss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
quantized_gru_cell_ttttttttttssss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
quantized_gru_cell_ttttttttttssss Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh Ptr Tensor
_packed_ih Ptr Tensor
_packed_hh Ptr Tensor
_col_offsets_ih Ptr Tensor
_col_offsets_hh Ptr Scalar
_scale_ih Ptr Scalar
_scale_hh Ptr Scalar
_zero_point_ih Ptr Scalar
_zero_point_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_gru_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)
, *$(at::Tensor* _packed_ih)
, *$(at::Tensor* _packed_hh)
, *$(at::Tensor* _col_offsets_ih)
, *$(at::Tensor* _col_offsets_hh)
, *$(at::Scalar* _scale_ih)
, *$(at::Scalar* _scale_hh)
, *$(at::Scalar* _zero_point_ih)
, *$(at::Scalar* _zero_point_hh)));
}|]
quantized_rnn_relu_cell_ttttttttttssss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
quantized_rnn_relu_cell_ttttttttttssss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
quantized_rnn_relu_cell_ttttttttttssss Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh Ptr Tensor
_packed_ih Ptr Tensor
_packed_hh Ptr Tensor
_col_offsets_ih Ptr Tensor
_col_offsets_hh Ptr Scalar
_scale_ih Ptr Scalar
_scale_hh Ptr Scalar
_zero_point_ih Ptr Scalar
_zero_point_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_rnn_relu_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)
, *$(at::Tensor* _packed_ih)
, *$(at::Tensor* _packed_hh)
, *$(at::Tensor* _col_offsets_ih)
, *$(at::Tensor* _col_offsets_hh)
, *$(at::Scalar* _scale_ih)
, *$(at::Scalar* _scale_hh)
, *$(at::Scalar* _zero_point_ih)
, *$(at::Scalar* _zero_point_hh)));
}|]
quantized_rnn_tanh_cell_ttttttttttssss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
quantized_rnn_tanh_cell_ttttttttttssss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
quantized_rnn_tanh_cell_ttttttttttssss Ptr Tensor
_input Ptr Tensor
_hx Ptr Tensor
_w_ih Ptr Tensor
_w_hh Ptr Tensor
_b_ih Ptr Tensor
_b_hh Ptr Tensor
_packed_ih Ptr Tensor
_packed_hh Ptr Tensor
_col_offsets_ih Ptr Tensor
_col_offsets_hh Ptr Scalar
_scale_ih Ptr Scalar
_scale_hh Ptr Scalar
_zero_point_ih Ptr Scalar
_zero_point_hh =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_rnn_tanh_cell(
*$(at::Tensor* _input)
, *$(at::Tensor* _hx)
, *$(at::Tensor* _w_ih)
, *$(at::Tensor* _w_hh)
, *$(at::Tensor* _b_ih)
, *$(at::Tensor* _b_hh)
, *$(at::Tensor* _packed_ih)
, *$(at::Tensor* _packed_hh)
, *$(at::Tensor* _col_offsets_ih)
, *$(at::Tensor* _col_offsets_hh)
, *$(at::Scalar* _scale_ih)
, *$(at::Scalar* _scale_hh)
, *$(at::Scalar* _zero_point_ih)
, *$(at::Scalar* _zero_point_hh)));
}|]
_pack_padded_sequence_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_pack_padded_sequence_ttb :: Ptr Tensor
-> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
_pack_padded_sequence_ttb Ptr Tensor
_input Ptr Tensor
_lengths CBool
_batch_first =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_pack_padded_sequence(
*$(at::Tensor* _input)
, *$(at::Tensor* _lengths)
, $(bool _batch_first)));
}|]
_pack_padded_sequence_backward_tltb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_pack_padded_sequence_backward_tltb :: Ptr Tensor
-> Ptr IntArray -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
_pack_padded_sequence_backward_tltb Ptr Tensor
_grad Ptr IntArray
_input_size Ptr Tensor
_batch_sizes CBool
_batch_first =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_pack_padded_sequence_backward(
*$(at::Tensor* _grad)
, *$(std::vector<int64_t>* _input_size)
, *$(at::Tensor* _batch_sizes)
, $(bool _batch_first)));
}|]
_pad_packed_sequence_ttbsl
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> Ptr Scalar
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_pad_packed_sequence_ttbsl :: Ptr Tensor
-> Ptr Tensor
-> CBool
-> Ptr Scalar
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_pad_packed_sequence_ttbsl Ptr Tensor
_data Ptr Tensor
_batch_sizes CBool
_batch_first Ptr Scalar
_padding_value Int64
_total_length =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_pad_packed_sequence(
*$(at::Tensor* _data)
, *$(at::Tensor* _batch_sizes)
, $(bool _batch_first)
, *$(at::Scalar* _padding_value)
, $(int64_t _total_length)));
}|]
masked_fill_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
masked_fill_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
masked_fill_tts Ptr Tensor
_self Ptr Tensor
_mask Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::masked_fill(
*$(at::Tensor* _self)
, *$(at::Tensor* _mask)
, *$(at::Scalar* _value)));
}|]
masked_fill_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
masked_fill_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
masked_fill_ttt Ptr Tensor
_self Ptr Tensor
_mask Ptr Tensor
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::masked_fill(
*$(at::Tensor* _self)
, *$(at::Tensor* _mask)
, *$(at::Tensor* _value)));
}|]
masked_scatter_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
masked_scatter_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
masked_scatter_ttt Ptr Tensor
_self Ptr Tensor
_mask Ptr Tensor
_source =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::masked_scatter(
*$(at::Tensor* _self)
, *$(at::Tensor* _mask)
, *$(at::Tensor* _source)));
}|]
_masked_softmax_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_masked_softmax_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_masked_softmax_tt Ptr Tensor
_self Ptr Tensor
_mask =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_masked_softmax(
*$(at::Tensor* _self)
, *$(at::Tensor* _mask)));
}|]
put_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
put_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
put_tttb Ptr Tensor
_self Ptr Tensor
_index Ptr Tensor
_source CBool
_accumulate =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::put(
*$(at::Tensor* _self)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)
, $(bool _accumulate)));
}|]
put_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
put_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
put_ttt Ptr Tensor
_self Ptr Tensor
_index Ptr Tensor
_source =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::put(
*$(at::Tensor* _self)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)));
}|]
index_add_out_ttltts
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_add_out_ttltts :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_add_out_ttltts Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_source Ptr Scalar
_alpha =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_add_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)
, *$(at::Scalar* _alpha)));
}|]
index_add_out_ttltt
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
index_add_out_ttltt :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
index_add_out_ttltt Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_source =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_add_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)));
}|]
index_add_tltts
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_add_tltts :: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_add_tltts Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_source Ptr Scalar
_alpha =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_add(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)
, *$(at::Scalar* _alpha)));
}|]
index_add_tltt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
index_add_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
index_add_tltt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_source =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_add(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)));
}|]
index_add_tntts
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_add_tntts :: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_add_tntts Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Tensor
_source Ptr Scalar
_alpha =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_add(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)
, *$(at::Scalar* _alpha)));
}|]
index_add_tntt
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
index_add_tntt :: Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
index_add_tntt Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Tensor
_source =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_add(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _source)));
}|]
index_fill_tlts
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_fill_tlts :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
index_fill_tlts Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_fill(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)));
}|]
index_fill_tltt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
index_fill_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
index_fill_tltt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_fill(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _value)));
}|]
index_fill_tnts
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
index_fill_tnts :: Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
index_fill_tnts Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_fill(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)));
}|]
index_fill_tntt
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
index_fill_tntt :: Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
index_fill_tntt Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Tensor
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_fill(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _value)));
}|]
scatter_tltt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
scatter_tltt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_src =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)));
}|]
scatter_out_ttltt
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_out_ttltt :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_out_ttltt Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_src =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)));
}|]
scatter_tlts
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
scatter_tlts :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
scatter_tlts Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)));
}|]
scatter_out_ttlts
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
scatter_out_ttlts :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
scatter_out_ttlts Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)));
}|]
scatter_tltts
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_tltts :: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_tltts Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_src Ptr StdString
_reduce =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)
, *$(std::string* _reduce)));
}|]
scatter_out_ttltts
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_out_ttltts :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_out_ttltts Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_src Ptr StdString
_reduce =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)
, *$(std::string* _reduce)));
}|]
scatter_tltss
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_tltss :: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_tltss Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Scalar
_value Ptr StdString
_reduce =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)
, *$(std::string* _reduce)));
}|]
scatter_out_ttltss
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_out_ttltss :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_out_ttltss Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Scalar
_value Ptr StdString
_reduce =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)
, *$(std::string* _reduce)));
}|]
scatter_tntt
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_tntt :: Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
scatter_tntt Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Tensor
_src =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)));
}|]
scatter_tnts
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
scatter_tnts :: Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
scatter_tnts Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Scalar* _value)));
}|]
scatter_add_tltt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_add_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
scatter_add_tltt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_src =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_add(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)));
}|]
scatter_add_out_ttltt
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_add_out_ttltt :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_add_out_ttltt Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_src =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_add_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)));
}|]
scatter_add_tntt
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
scatter_add_tntt :: Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
scatter_add_tntt Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index Ptr Tensor
_src =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_add(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _src)));
}|]
scatter_reduce_tltsl
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr StdString
-> Int64
-> IO (Ptr Tensor)
scatter_reduce_tltsl :: Ptr Tensor
-> Int64 -> Ptr Tensor -> Ptr StdString -> Int64 -> IO (Ptr Tensor)
scatter_reduce_tltsl Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr StdString
_reduce Int64
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_reduce(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(std::string* _reduce)
, $(int64_t _output_size)));
}|]
scatter_reduce_tlts
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
scatter_reduce_tlts :: Ptr Tensor
-> Int64 -> Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor)
scatter_reduce_tlts Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr StdString
_reduce =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::scatter_reduce(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(std::string* _reduce)));
}|]
bitwise_and_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_and_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_and_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_and_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_and_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_and_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_and_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_and_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_and_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_and_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_and_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_and(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_and_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_and_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_and_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_and(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
__and___ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
__and___ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
__and___ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__and__(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
__and___tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
__and___tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
__and___tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__and__(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_or_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_or_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_or_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_or_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_or_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_or_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_or_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_or_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_or_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_or_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_or_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_or(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_or_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_or_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_or_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_or(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
__or___ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
__or___ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
__or___ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__or__(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
__or___tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
__or___tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
__or___tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__or__(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_xor_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_xor_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_xor_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_xor_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_xor_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_xor_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_xor_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_xor_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_xor_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_xor_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_xor_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_xor(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_xor_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_xor_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_xor_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_xor(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
__xor___ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
__xor___ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
__xor___ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__xor__(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
__xor___tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
__xor___tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
__xor___tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__xor__(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
__lshift___ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
__lshift___ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
__lshift___ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__lshift__(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
__lshift___tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
__lshift___tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
__lshift___tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__lshift__(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_left_shift_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_left_shift_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_left_shift_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_left_shift(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_left_shift_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_left_shift_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_left_shift_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_left_shift_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_left_shift_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_left_shift_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_left_shift_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_left_shift(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_left_shift_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_left_shift_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_left_shift_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_left_shift_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_left_shift_st
:: Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_left_shift_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_left_shift_st Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_left_shift(
*$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
__rshift___ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
__rshift___ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
__rshift___ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__rshift__(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
__rshift___tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
__rshift___tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
__rshift___tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::__rshift__(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_right_shift_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_right_shift_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_right_shift_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_right_shift(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_right_shift_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_right_shift_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_right_shift_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_right_shift_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
bitwise_right_shift_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_right_shift_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_right_shift_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_right_shift(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_right_shift_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
bitwise_right_shift_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
bitwise_right_shift_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_right_shift_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
bitwise_right_shift_st
:: Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_right_shift_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_right_shift_st Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_right_shift(
*$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
addbmm_out_ttttss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_out_ttttss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_out_ttttss Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_batch1 Ptr Tensor
_batch2 Ptr Scalar
_beta Ptr Scalar
_alpha =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addbmm_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _batch1)
, *$(at::Tensor* _batch2)
, *$(at::Scalar* _beta)
, *$(at::Scalar* _alpha)));
}|]
addbmm_out_tttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_out_tttts :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_out_tttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_batch1 Ptr Tensor
_batch2 Ptr Scalar
_beta =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addbmm_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _batch1)
, *$(at::Tensor* _batch2)
, *$(at::Scalar* _beta)));
}|]
addbmm_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
addbmm_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
addbmm_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_batch1 Ptr Tensor
_batch2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addbmm_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _batch1)
, *$(at::Tensor* _batch2)));
}|]
addbmm_tttss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_tttss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_tttss Ptr Tensor
_self Ptr Tensor
_batch1 Ptr Tensor
_batch2 Ptr Scalar
_beta Ptr Scalar
_alpha =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addbmm(
*$(at::Tensor* _self)
, *$(at::Tensor* _batch1)
, *$(at::Tensor* _batch2)
, *$(at::Scalar* _beta)
, *$(at::Scalar* _alpha)));
}|]
addbmm_ttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addbmm_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
addbmm_ttts Ptr Tensor
_self Ptr Tensor
_batch1 Ptr Tensor
_batch2 Ptr Scalar
_beta =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addbmm(
*$(at::Tensor* _self)
, *$(at::Tensor* _batch1)
, *$(at::Tensor* _batch2)
, *$(at::Scalar* _beta)));
}|]
addbmm_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
addbmm_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
addbmm_ttt Ptr Tensor
_self Ptr Tensor
_batch1 Ptr Tensor
_batch2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addbmm(
*$(at::Tensor* _self)
, *$(at::Tensor* _batch1)
, *$(at::Tensor* _batch2)));
}|]
diag_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
diag_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diag_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _diagonal)));
}|]
diag_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
diag_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
diag_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
diag_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
diag_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diag_tl Ptr Tensor
_self Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::diag(
*$(at::Tensor* _self)
, $(int64_t _diagonal)));
}|]
diag_t
:: Ptr Tensor
-> IO (Ptr Tensor)
diag_t :: Ptr Tensor -> IO (Ptr Tensor)
diag_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::diag(
*$(at::Tensor* _self)));
}|]
diag_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
diag_backward_tll :: Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr Tensor)
diag_backward_tll Ptr Tensor
_grad Ptr IntArray
_input_sizes Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_backward(
*$(at::Tensor* _grad)
, *$(std::vector<int64_t>* _input_sizes)
, $(int64_t _diagonal)));
}|]
cross_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
cross_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cross_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)
, $(int64_t _dim)));
}|]
cross_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cross_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cross_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
cross_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
cross_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cross_ttl Ptr Tensor
_self Ptr Tensor
_other Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)
, $(int64_t _dim)));
}|]
cross_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cross_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cross_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
triu_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
triu_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
triu_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _diagonal)));
}|]
triu_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
triu_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
triu_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
triu_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
triu_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
triu_tl Ptr Tensor
_self Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu(
*$(at::Tensor* _self)
, $(int64_t _diagonal)));
}|]
triu_t
:: Ptr Tensor
-> IO (Ptr Tensor)
triu_t :: Ptr Tensor -> IO (Ptr Tensor)
triu_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu(
*$(at::Tensor* _self)));
}|]
tril_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
tril_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
tril_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _diagonal)));
}|]
tril_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
tril_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
tril_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
tril_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
tril_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
tril_tl Ptr Tensor
_self Int64
_diagonal =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril(
*$(at::Tensor* _self)
, $(int64_t _diagonal)));
}|]
tril_t
:: Ptr Tensor
-> IO (Ptr Tensor)
tril_t :: Ptr Tensor -> IO (Ptr Tensor)
tril_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril(
*$(at::Tensor* _self)));
}|]
tril_indices_lllo
:: Int64
-> Int64
-> Int64
-> Ptr TensorOptions
-> IO (Ptr Tensor)
tril_indices_lllo :: Int64 -> Int64 -> Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
tril_indices_lllo Int64
_row Int64
_col Int64
_offset Ptr TensorOptions
_options =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril_indices(
$(int64_t _row)
, $(int64_t _col)
, $(int64_t _offset)
, *$(at::TensorOptions* _options)));
}|]
tril_indices_lll
:: Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
tril_indices_lll :: Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
tril_indices_lll Int64
_row Int64
_col Int64
_offset =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril_indices(
$(int64_t _row)
, $(int64_t _col)
, $(int64_t _offset)));
}|]
tril_indices_ll
:: Int64
-> Int64
-> IO (Ptr Tensor)
tril_indices_ll :: Int64 -> Int64 -> IO (Ptr Tensor)
tril_indices_ll Int64
_row Int64
_col =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tril_indices(
$(int64_t _row)
, $(int64_t _col)));
}|]
triu_indices_lllo
:: Int64
-> Int64
-> Int64
-> Ptr TensorOptions
-> IO (Ptr Tensor)
triu_indices_lllo :: Int64 -> Int64 -> Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
triu_indices_lllo Int64
_row Int64
_col Int64
_offset Ptr TensorOptions
_options =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices(
$(int64_t _row)
, $(int64_t _col)
, $(int64_t _offset)
, *$(at::TensorOptions* _options)));
}|]
triu_indices_lll
:: Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
triu_indices_lll :: Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
triu_indices_lll Int64
_row Int64
_col Int64
_offset =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices(
$(int64_t _row)
, $(int64_t _col)
, $(int64_t _offset)));
}|]
triu_indices_ll
:: Int64
-> Int64
-> IO (Ptr Tensor)
triu_indices_ll :: Int64 -> Int64 -> IO (Ptr Tensor)
triu_indices_ll Int64
_row Int64
_col =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices(
$(int64_t _row)
, $(int64_t _col)));
}|]
trace_t
:: Ptr Tensor
-> IO (Ptr Tensor)
trace_t :: Ptr Tensor -> IO (Ptr Tensor)
trace_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::trace(
*$(at::Tensor* _self)));
}|]
trace_backward_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
trace_backward_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
trace_backward_tl Ptr Tensor
_grad Ptr IntArray
_sizes =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::trace_backward(
*$(at::Tensor* _grad)
, *$(std::vector<int64_t>* _sizes)));
}|]
ne_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
ne_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
ne_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ne_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
ne_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
ne_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
ne_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ne(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
ne_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ne_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ne_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ne_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
ne_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ne_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ne_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ne(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
not_equal_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
not_equal_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
not_equal_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
not_equal_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
not_equal_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
not_equal_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
not_equal_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
not_equal_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
not_equal_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
not_equal_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
not_equal_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
not_equal_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
eq_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
eq_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
eq_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::eq_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
eq_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
eq_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
eq_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::eq(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
eq_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
eq_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
eq_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::eq_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
eq_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
eq_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
eq_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::eq(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
ge_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
ge_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
ge_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ge_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
ge_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
ge_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
ge_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ge(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
ge_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ge_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ge_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ge_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
ge_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ge_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ge_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ge(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
greater_equal_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
greater_equal_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
greater_equal_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
greater_equal_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
greater_equal_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
greater_equal_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
greater_equal_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
greater_equal_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
greater_equal_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
greater_equal_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
greater_equal_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
greater_equal_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
le_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
le_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
le_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::le_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
le_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
le_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
le_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::le(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
le_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
le_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
le_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::le_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
le_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
le_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
le_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::le(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]