-- generated by using spec/Declarations.yaml {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} module Torch.Functional.Internal where import System.IO.Unsafe import Foreign.ForeignPtr import qualified Torch.Internal.Managed.Native as ATen import qualified Torch.Internal.Managed.Type.Tensor as ATen import qualified Torch.Internal.Managed.Type.Scalar as ATen import qualified Torch.Internal.Managed.Type.Tuple as ATen import qualified Torch.Internal.Const as ATen import qualified Torch.Internal.Type as ATen import qualified Torch.Internal.Managed.Cast import Torch.Internal.Cast import Torch.Tensor import Torch.Scalar import Torch.Dimname import Torch.DType import Torch.Cast align_tensors :: [Tensor] -- ^ tensors -> [Tensor] align_tensors _tensors = unsafePerformIO $ (cast1 ATen.align_tensors_l) _tensors native_dropout :: Tensor -- ^ input -> Double -- ^ p -> Bool -- ^ train -> (Tensor,Tensor) native_dropout _input _p _train = unsafePerformIO $ (cast3 ATen.native_dropout_tdb) _input _p _train dropout :: Tensor -- ^ input -> Double -- ^ p -> Bool -- ^ train -> Tensor dropout _input _p _train = unsafePerformIO $ (cast3 ATen.dropout_tdb) _input _p _train feature_dropout :: Tensor -- ^ input -> Double -- ^ p -> Bool -- ^ train -> Tensor feature_dropout _input _p _train = unsafePerformIO $ (cast3 ATen.feature_dropout_tdb) _input _p _train alpha_dropout :: Tensor -- ^ input -> Double -- ^ p -> Bool -- ^ train -> Tensor alpha_dropout _input _p _train = unsafePerformIO $ (cast3 ATen.alpha_dropout_tdb) _input _p _train feature_alpha_dropout :: Tensor -- ^ input -> Double -- ^ p -> Bool -- ^ train -> Tensor feature_alpha_dropout _input _p _train = unsafePerformIO $ (cast3 ATen.feature_alpha_dropout_tdb) _input _p _train abs :: Tensor -- ^ self -> Tensor abs _self = unsafePerformIO $ (cast1 ATen.abs_t) _self absolute :: Tensor -- ^ self -> Tensor absolute _self = unsafePerformIO $ (cast1 ATen.absolute_t) _self angle :: Tensor -- ^ self -> Tensor angle _self = unsafePerformIO $ (cast1 ATen.angle_t) _self view_as_real :: Tensor -- ^ self -> Tensor view_as_real _self = unsafePerformIO $ (cast1 ATen.view_as_real_t) _self view_as_complex :: Tensor -- ^ self -> Tensor view_as_complex _self = unsafePerformIO $ (cast1 ATen.view_as_complex_t) _self sgn :: Tensor -- ^ self -> Tensor sgn _self = unsafePerformIO $ (cast1 ATen.sgn_t) _self real :: Tensor -- ^ self -> Tensor real _self = unsafePerformIO $ (cast1 ATen.real_t) _self imag :: Tensor -- ^ self -> Tensor imag _self = unsafePerformIO $ (cast1 ATen.imag_t) _self conj :: Tensor -- ^ self -> Tensor conj _self = unsafePerformIO $ (cast1 ATen.conj_t) _self conj_physical :: Tensor -- ^ self -> Tensor conj_physical _self = unsafePerformIO $ (cast1 ATen.conj_physical_t) _self resolve_conj :: Tensor -- ^ self -> Tensor resolve_conj _self = unsafePerformIO $ (cast1 ATen.resolve_conj_t) _self resolve_neg :: Tensor -- ^ self -> Tensor resolve_neg _self = unsafePerformIO $ (cast1 ATen.resolve_neg_t) _self acos :: Tensor -- ^ self -> Tensor acos _self = unsafePerformIO $ (cast1 ATen.acos_t) _self arccos :: Tensor -- ^ self -> Tensor arccos _self = unsafePerformIO $ (cast1 ATen.arccos_t) _self avg_pool1d :: Tensor -- ^ self -> Int -- ^ kernel_size -> Int -- ^ stride -> Int -- ^ padding -> Bool -- ^ ceil_mode -> Bool -- ^ count_include_pad -> Tensor avg_pool1d _self _kernel_size _stride _padding _ceil_mode _count_include_pad = unsafePerformIO $ (cast6 ATen.avg_pool1d_tlllbb) _self _kernel_size _stride _padding _ceil_mode _count_include_pad adaptive_avg_pool1d :: Tensor -- ^ self -> Int -- ^ output_size -> Tensor adaptive_avg_pool1d _self _output_size = unsafePerformIO $ (cast2 ATen.adaptive_avg_pool1d_tl) _self _output_size adaptive_max_pool1d :: Tensor -- ^ self -> Int -- ^ output_size -> (Tensor,Tensor) adaptive_max_pool1d _self _output_size = unsafePerformIO $ (cast2 ATen.adaptive_max_pool1d_tl) _self _output_size add :: Tensor -- ^ self -> Tensor -- ^ other -> Float -- ^ alpha -> Tensor add _self _other _alpha = unsafePerformIO $ (cast3 ATen.add_tts) _self _other _alpha addScalar :: Tensor -- ^ self -> Float -- ^ other -> Float -- ^ alpha -> Tensor addScalar _self _other _alpha = unsafePerformIO $ (cast3 ATen.add_tss) _self _other _alpha addmv :: Tensor -- ^ self -> Tensor -- ^ mat -> Tensor -- ^ vec -> Float -- ^ beta -> Float -- ^ alpha -> Tensor addmv _self _mat _vec _beta _alpha = unsafePerformIO $ (cast5 ATen.addmv_tttss) _self _mat _vec _beta _alpha addr :: Tensor -- ^ self -> Tensor -- ^ vec1 -> Tensor -- ^ vec2 -> Float -- ^ beta -> Float -- ^ alpha -> Tensor addr _self _vec1 _vec2 _beta _alpha = unsafePerformIO $ (cast5 ATen.addr_tttss) _self _vec1 _vec2 _beta _alpha affine_grid_generator :: Tensor -- ^ theta -> [Int] -- ^ size -> Bool -- ^ align_corners -> Tensor affine_grid_generator _theta _size _align_corners = unsafePerformIO $ (cast3 ATen.affine_grid_generator_tlb) _theta _size _align_corners allDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor allDim _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.all_tlb) _self _dim _keepdim allWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> Tensor allWithDimname _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.all_tnb) _self _dim _keepdim allclose :: Tensor -- ^ self -> Tensor -- ^ other -> Double -- ^ rtol -> Double -- ^ atol -> Bool -- ^ equal_nan -> Bool allclose _self _other _rtol _atol _equal_nan = unsafePerformIO $ (cast5 ATen.allclose_ttddb) _self _other _rtol _atol _equal_nan anyDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor anyDim _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.any_tlb) _self _dim _keepdim anyWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> Tensor anyWithDimname _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.any_tnb) _self _dim _keepdim argmax :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor argmax _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.argmax_tlb) _self _dim _keepdim argmin :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor argmin _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.argmin_tlb) _self _dim _keepdim acosh :: Tensor -- ^ self -> Tensor acosh _self = unsafePerformIO $ (cast1 ATen.acosh_t) _self arccosh :: Tensor -- ^ self -> Tensor arccosh _self = unsafePerformIO $ (cast1 ATen.arccosh_t) _self asinh :: Tensor -- ^ self -> Tensor asinh _self = unsafePerformIO $ (cast1 ATen.asinh_t) _self arcsinh :: Tensor -- ^ self -> Tensor arcsinh _self = unsafePerformIO $ (cast1 ATen.arcsinh_t) _self atanh :: Tensor -- ^ self -> Tensor atanh _self = unsafePerformIO $ (cast1 ATen.atanh_t) _self arctanh :: Tensor -- ^ self -> Tensor arctanh _self = unsafePerformIO $ (cast1 ATen.arctanh_t) _self as_strided :: Tensor -- ^ self -> [Int] -- ^ size -> [Int] -- ^ stride -> Int -- ^ storage_offset -> Tensor as_strided _self _size _stride _storage_offset = unsafePerformIO $ (cast4 ATen.as_strided_tlll) _self _size _stride _storage_offset asin :: Tensor -- ^ self -> Tensor asin _self = unsafePerformIO $ (cast1 ATen.asin_t) _self arcsin :: Tensor -- ^ self -> Tensor arcsin _self = unsafePerformIO $ (cast1 ATen.arcsin_t) _self atan :: Tensor -- ^ self -> Tensor atan _self = unsafePerformIO $ (cast1 ATen.atan_t) _self arctan :: Tensor -- ^ self -> Tensor arctan _self = unsafePerformIO $ (cast1 ATen.arctan_t) _self atleast_1d_t :: Tensor -- ^ self -> Tensor atleast_1d_t _self = unsafePerformIO $ (cast1 ATen.atleast_1d_t) _self atleast_1d_l :: [Tensor] -- ^ tensors -> [Tensor] atleast_1d_l _tensors = unsafePerformIO $ (cast1 ATen.atleast_1d_l) _tensors atleast_2d_t :: Tensor -- ^ self -> Tensor atleast_2d_t _self = unsafePerformIO $ (cast1 ATen.atleast_2d_t) _self atleast_2d_l :: [Tensor] -- ^ tensors -> [Tensor] atleast_2d_l _tensors = unsafePerformIO $ (cast1 ATen.atleast_2d_l) _tensors atleast_3d_t :: Tensor -- ^ self -> Tensor atleast_3d_t _self = unsafePerformIO $ (cast1 ATen.atleast_3d_t) _self atleast_3d_l :: [Tensor] -- ^ tensors -> [Tensor] atleast_3d_l _tensors = unsafePerformIO $ (cast1 ATen.atleast_3d_l) _tensors baddbmm :: Tensor -- ^ self -> Tensor -- ^ batch1 -> Tensor -- ^ batch2 -> Float -- ^ beta -> Float -- ^ alpha -> Tensor baddbmm _self _batch1 _batch2 _beta _alpha = unsafePerformIO $ (cast5 ATen.baddbmm_tttss) _self _batch1 _batch2 _beta _alpha batch_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Bool -- ^ training -> Double -- ^ momentum -> Double -- ^ eps -> Bool -- ^ cudnn_enabled -> Tensor batch_norm _input _weight _bias _running_mean _running_var _training _momentum _eps _cudnn_enabled = unsafePerformIO $ (cast9 ATen.batch_norm_tttttbddb) _input _weight _bias _running_mean _running_var _training _momentum _eps _cudnn_enabled quantized_batch_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ mean -> Tensor -- ^ var -> Double -- ^ eps -> Double -- ^ output_scale -> Int -- ^ output_zero_point -> Tensor quantized_batch_norm _input _weight _bias _mean _var _eps _output_scale _output_zero_point = unsafePerformIO $ (cast8 ATen.quantized_batch_norm_tttttddl) _input _weight _bias _mean _var _eps _output_scale _output_zero_point bilinear :: Tensor -- ^ input1 -> Tensor -- ^ input2 -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor bilinear _input1 _input2 _weight _bias = unsafePerformIO $ (cast4 ATen.bilinear_tttt) _input1 _input2 _weight _bias binary_cross_entropy :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Tensor binary_cross_entropy _self _target _weight _reduction = unsafePerformIO $ (cast4 ATen.binary_cross_entropy_tttl) _self _target _weight _reduction binary_cross_entropy_with_logits :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Tensor -- ^ pos_weight -> Int -- ^ reduction -> Tensor binary_cross_entropy_with_logits _self _target _weight _pos_weight _reduction = unsafePerformIO $ (cast5 ATen.binary_cross_entropy_with_logits_ttttl) _self _target _weight _pos_weight _reduction bincount :: Tensor -- ^ self -> Tensor -- ^ weights -> Int -- ^ minlength -> Tensor bincount _self _weights _minlength = unsafePerformIO $ (cast3 ATen.bincount_ttl) _self _weights _minlength bitwise_not :: Tensor -- ^ self -> Tensor bitwise_not _self = unsafePerformIO $ (cast1 ATen.bitwise_not_t) _self copysign_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor copysign_tt _self _other = unsafePerformIO $ (cast2 ATen.copysign_tt) _self _other copysign_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor copysign_ts _self _other = unsafePerformIO $ (cast2 ATen.copysign_ts) _self _other logical_not :: Tensor -- ^ self -> Tensor logical_not _self = unsafePerformIO $ (cast1 ATen.logical_not_t) _self logical_xor :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor logical_xor _self _other = unsafePerformIO $ (cast2 ATen.logical_xor_tt) _self _other logical_and :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor logical_and _self _other = unsafePerformIO $ (cast2 ATen.logical_and_tt) _self _other logical_or :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor logical_or _self _other = unsafePerformIO $ (cast2 ATen.logical_or_tt) _self _other bmm :: Tensor -- ^ self -> Tensor -- ^ mat2 -> Tensor bmm _self _mat2 = unsafePerformIO $ (cast2 ATen.bmm_tt) _self _mat2 broadcast_tensors :: [Tensor] -- ^ tensors -> [Tensor] broadcast_tensors _tensors = unsafePerformIO $ (cast1 ATen.broadcast_tensors_l) _tensors broadcast_to :: Tensor -- ^ self -> [Int] -- ^ size -> Tensor broadcast_to _self _size = unsafePerformIO $ (cast2 ATen.broadcast_to_tl) _self _size cat :: [Tensor] -- ^ tensors -> Int -- ^ dim -> Tensor cat _tensors _dim = unsafePerformIO $ (cast2 ATen.cat_ll) _tensors _dim catWithDimname :: [Tensor] -- ^ tensors -> Dimname -- ^ dim -> Tensor catWithDimname _tensors _dim = unsafePerformIO $ (cast2 ATen.cat_ln) _tensors _dim concat_ll :: [Tensor] -- ^ tensors -> Int -- ^ dim -> Tensor concat_ll _tensors _dim = unsafePerformIO $ (cast2 ATen.concat_ll) _tensors _dim concat_ln :: [Tensor] -- ^ tensors -> Dimname -- ^ dim -> Tensor concat_ln _tensors _dim = unsafePerformIO $ (cast2 ATen.concat_ln) _tensors _dim concatenate_ll :: [Tensor] -- ^ tensors -> Int -- ^ dim -> Tensor concatenate_ll _tensors _dim = unsafePerformIO $ (cast2 ATen.concatenate_ll) _tensors _dim concatenate_ln :: [Tensor] -- ^ tensors -> Dimname -- ^ dim -> Tensor concatenate_ln _tensors _dim = unsafePerformIO $ (cast2 ATen.concatenate_ln) _tensors _dim block_diag :: [Tensor] -- ^ tensors -> Tensor block_diag _tensors = unsafePerformIO $ (cast1 ATen.block_diag_l) _tensors ceil :: Tensor -- ^ self -> Tensor ceil _self = unsafePerformIO $ (cast1 ATen.ceil_t) _self chain_matmul :: [Tensor] -- ^ matrices -> Tensor chain_matmul _matrices = unsafePerformIO $ (cast1 ATen.chain_matmul_l) _matrices unsafe_chunk :: Tensor -- ^ self -> Int -- ^ chunks -> Int -- ^ dim -> [Tensor] unsafe_chunk _self _chunks _dim = unsafePerformIO $ (cast3 ATen.unsafe_chunk_tll) _self _chunks _dim chunk :: Tensor -- ^ self -> Int -- ^ chunks -> Int -- ^ dim -> [Tensor] chunk _self _chunks _dim = unsafePerformIO $ (cast3 ATen.chunk_tll) _self _chunks _dim tensor_split_tll :: Tensor -- ^ self -> Int -- ^ sections -> Int -- ^ dim -> [Tensor] tensor_split_tll _self _sections _dim = unsafePerformIO $ (cast3 ATen.tensor_split_tll) _self _sections _dim -- tensor_split_tll -- :: Tensor -- ^ self -- -> [Int] -- ^ indices -- -> Int -- ^ dim -- -> [Tensor] -- tensor_split_tll _self _indices _dim = unsafePerformIO $ (cast3 ATen.tensor_split_tll) _self _indices _dim tensor_split_ttl :: Tensor -- ^ self -> Tensor -- ^ tensor_indices_or_sections -> Int -- ^ dim -> [Tensor] tensor_split_ttl _self _tensor_indices_or_sections _dim = unsafePerformIO $ (cast3 ATen.tensor_split_ttl) _self _tensor_indices_or_sections _dim clamp_tss :: Tensor -- ^ self -> Float -- ^ min -> Float -- ^ max -> Tensor clamp_tss _self _min _max = unsafePerformIO $ (cast3 ATen.clamp_tss) _self _min _max clamp_ttt :: Tensor -- ^ self -> Tensor -- ^ min -> Tensor -- ^ max -> Tensor clamp_ttt _self _min _max = unsafePerformIO $ (cast3 ATen.clamp_ttt) _self _min _max clamp_max_ts :: Tensor -- ^ self -> Float -- ^ max -> Tensor clamp_max_ts _self _max = unsafePerformIO $ (cast2 ATen.clamp_max_ts) _self _max clamp_max_tt :: Tensor -- ^ self -> Tensor -- ^ max -> Tensor clamp_max_tt _self _max = unsafePerformIO $ (cast2 ATen.clamp_max_tt) _self _max clamp_min_ts :: Tensor -- ^ self -> Float -- ^ min -> Tensor clamp_min_ts _self _min = unsafePerformIO $ (cast2 ATen.clamp_min_ts) _self _min clamp_min_tt :: Tensor -- ^ self -> Tensor -- ^ min -> Tensor clamp_min_tt _self _min = unsafePerformIO $ (cast2 ATen.clamp_min_tt) _self _min clip_tss :: Tensor -- ^ self -> Float -- ^ min -> Float -- ^ max -> Tensor clip_tss _self _min _max = unsafePerformIO $ (cast3 ATen.clip_tss) _self _min _max clip_ttt :: Tensor -- ^ self -> Tensor -- ^ min -> Tensor -- ^ max -> Tensor clip_ttt _self _min _max = unsafePerformIO $ (cast3 ATen.clip_ttt) _self _min _max cudnn_is_acceptable :: Tensor -- ^ self -> Bool cudnn_is_acceptable _self = unsafePerformIO $ (cast1 ATen.cudnn_is_acceptable_t) _self complex :: Tensor -- ^ real -> Tensor -- ^ imag -> Tensor complex _real _imag = unsafePerformIO $ (cast2 ATen.complex_tt) _real _imag polar :: Tensor -- ^ abs -> Tensor -- ^ angle -> Tensor polar _abs _angle = unsafePerformIO $ (cast2 ATen.polar_tt) _abs _angle constant_pad_nd :: Tensor -- ^ self -> [Int] -- ^ pad -> Float -- ^ value -> Tensor constant_pad_nd _self _pad _value = unsafePerformIO $ (cast3 ATen.constant_pad_nd_tls) _self _pad _value convolution :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Bool -- ^ transposed -> [Int] -- ^ output_padding -> Int -- ^ groups -> Tensor convolution _input _weight _bias _stride _padding _dilation _transposed _output_padding _groups = unsafePerformIO $ (cast9 ATen.convolution_tttlllbll) _input _weight _bias _stride _padding _dilation _transposed _output_padding _groups convolution_overrideable :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Bool -- ^ transposed -> [Int] -- ^ output_padding -> Int -- ^ groups -> Tensor convolution_overrideable _input _weight _bias _stride _padding _dilation _transposed _output_padding _groups = unsafePerformIO $ (cast9 ATen.convolution_overrideable_tttlllbll) _input _weight _bias _stride _padding _dilation _transposed _output_padding _groups convolution_backward_overrideable :: Tensor -- ^ grad_output -> Tensor -- ^ input -> Tensor -- ^ weight -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Bool -- ^ transposed -> [Int] -- ^ output_padding -> Int -- ^ groups -> (Bool,Bool,Bool) -- ^ output_mask -> (Tensor,Tensor,Tensor) convolution_backward_overrideable _grad_output _input _weight _stride _padding _dilation _transposed _output_padding _groups _output_mask = unsafePerformIO $ (cast10 ATen.convolution_backward_overrideable_tttlllblla) _grad_output _input _weight _stride _padding _dilation _transposed _output_padding _groups _output_mask conv1d_tttllll :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Int -- ^ stride -> Int -- ^ padding -> Int -- ^ dilation -> Int -- ^ groups -> Tensor conv1d_tttllll _input _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.conv1d_tttllll) _input _weight _bias _stride _padding _dilation _groups conv2d :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ dilation -> Int -- ^ groups -> Tensor conv2d _input _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.conv2d_tttllll) _input _weight _bias _stride _padding _dilation _groups conv3d_tttllll :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Int -- ^ groups -> Tensor conv3d_tttllll _input _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.conv3d_tttllll) _input _weight _bias _stride _padding _dilation _groups conv1d_tttlsll :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Int -- ^ stride -> String -- ^ padding -> Int -- ^ dilation -> Int -- ^ groups -> Tensor conv1d_tttlsll _input _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.conv1d_tttlsll) _input _weight _bias _stride _padding _dilation _groups conv2d_tttlsll :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> (Int,Int) -- ^ stride -> String -- ^ padding -> (Int,Int) -- ^ dilation -> Int -- ^ groups -> Tensor conv2d_tttlsll _input _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.conv2d_tttlsll) _input _weight _bias _stride _padding _dilation _groups conv3d_tttlsll :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> String -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Int -- ^ groups -> Tensor conv3d_tttlsll _input _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.conv3d_tttlsll) _input _weight _bias _stride _padding _dilation _groups conv_tbc :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> Int -- ^ pad -> Tensor conv_tbc _self _weight _bias _pad = unsafePerformIO $ (cast4 ATen.conv_tbc_tttl) _self _weight _bias _pad conv_transpose1d :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Int -- ^ stride -> Int -- ^ padding -> Int -- ^ output_padding -> Int -- ^ groups -> Int -- ^ dilation -> Tensor conv_transpose1d _input _weight _bias _stride _padding _output_padding _groups _dilation = unsafePerformIO $ (cast8 ATen.conv_transpose1d_tttlllll) _input _weight _bias _stride _padding _output_padding _groups _dilation conv_transpose2d :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ output_padding -> Int -- ^ groups -> (Int,Int) -- ^ dilation -> Tensor conv_transpose2d _input _weight _bias _stride _padding _output_padding _groups _dilation = unsafePerformIO $ (cast8 ATen.conv_transpose2d_tttlllll) _input _weight _bias _stride _padding _output_padding _groups _dilation conv_transpose3d :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ output_padding -> Int -- ^ groups -> (Int,Int,Int) -- ^ dilation -> Tensor conv_transpose3d _input _weight _bias _stride _padding _output_padding _groups _dilation = unsafePerformIO $ (cast8 ATen.conv_transpose3d_tttlllll) _input _weight _bias _stride _padding _output_padding _groups _dilation copy :: Tensor -- ^ self -> Tensor -- ^ src -> Bool -- ^ non_blocking -> Tensor copy _self _src _non_blocking = unsafePerformIO $ (cast3 ATen.copy_ttb) _self _src _non_blocking cos :: Tensor -- ^ self -> Tensor cos _self = unsafePerformIO $ (cast1 ATen.cos_t) _self cosh :: Tensor -- ^ self -> Tensor cosh _self = unsafePerformIO $ (cast1 ATen.cosh_t) _self cosine_embedding_loss :: Tensor -- ^ input1 -> Tensor -- ^ input2 -> Tensor -- ^ target -> Double -- ^ margin -> Int -- ^ reduction -> Tensor cosine_embedding_loss _input1 _input2 _target _margin _reduction = unsafePerformIO $ (cast5 ATen.cosine_embedding_loss_tttdl) _input1 _input2 _target _margin _reduction -- count_nonzero_tl -- :: Tensor -- ^ self -- -> [Int] -- ^ dim -- -> Tensor -- count_nonzero_tl _self _dim = unsafePerformIO $ (cast2 ATen.count_nonzero_tl) _self _dim count_nonzero_tl :: Tensor -- ^ self -> Int -- ^ dim -> Tensor count_nonzero_tl _self _dim = unsafePerformIO $ (cast2 ATen.count_nonzero_tl) _self _dim cov :: Tensor -- ^ self -> Int -- ^ correction -> Tensor -- ^ fweights -> Tensor -- ^ aweights -> Tensor cov _self _correction _fweights _aweights = unsafePerformIO $ (cast4 ATen.cov_tltt) _self _correction _fweights _aweights corrcoef :: Tensor -- ^ self -> Tensor corrcoef _self = unsafePerformIO $ (cast1 ATen.corrcoef_t) _self cudnn_affine_grid_generator :: Tensor -- ^ theta -> Int -- ^ N -> Int -- ^ C -> Int -- ^ H -> Int -- ^ W -> Tensor cudnn_affine_grid_generator _theta _N _C _H _W = unsafePerformIO $ (cast5 ATen.cudnn_affine_grid_generator_tllll) _theta _N _C _H _W cudnn_batch_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Bool -- ^ training -> Double -- ^ exponential_average_factor -> Double -- ^ epsilon -> (Tensor,Tensor,Tensor,Tensor) cudnn_batch_norm _input _weight _bias _running_mean _running_var _training _exponential_average_factor _epsilon = unsafePerformIO $ (cast8 ATen.cudnn_batch_norm_tttttbdd) _input _weight _bias _running_mean _running_var _training _exponential_average_factor _epsilon cudnn_convolution :: Tensor -- ^ self -> Tensor -- ^ weight -> [Int] -- ^ padding -> [Int] -- ^ stride -> [Int] -- ^ dilation -> Int -- ^ groups -> Bool -- ^ benchmark -> Bool -- ^ deterministic -> Bool -- ^ allow_tf32 -> Tensor cudnn_convolution _self _weight _padding _stride _dilation _groups _benchmark _deterministic _allow_tf32 = unsafePerformIO $ (cast9 ATen.cudnn_convolution_ttllllbbb) _self _weight _padding _stride _dilation _groups _benchmark _deterministic _allow_tf32 cudnn_convolution_transpose :: Tensor -- ^ self -> Tensor -- ^ weight -> [Int] -- ^ padding -> [Int] -- ^ output_padding -> [Int] -- ^ stride -> [Int] -- ^ dilation -> Int -- ^ groups -> Bool -- ^ benchmark -> Bool -- ^ deterministic -> Bool -- ^ allow_tf32 -> Tensor cudnn_convolution_transpose _self _weight _padding _output_padding _stride _dilation _groups _benchmark _deterministic _allow_tf32 = unsafePerformIO $ (cast10 ATen.cudnn_convolution_transpose_ttlllllbbb) _self _weight _padding _output_padding _stride _dilation _groups _benchmark _deterministic _allow_tf32 cudnn_convolution_relu :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Int -- ^ groups -> Tensor cudnn_convolution_relu _self _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.cudnn_convolution_relu_tttllll) _self _weight _bias _stride _padding _dilation _groups cudnn_convolution_add_relu :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ z -> Float -- ^ alpha -> Tensor -- ^ bias -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Int -- ^ groups -> Tensor cudnn_convolution_add_relu _self _weight _z _alpha _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast9 ATen.cudnn_convolution_add_relu_tttstllll) _self _weight _z _alpha _bias _stride _padding _dilation _groups cudnn_grid_sampler :: Tensor -- ^ self -> Tensor -- ^ grid -> Tensor cudnn_grid_sampler _self _grid = unsafePerformIO $ (cast2 ATen.cudnn_grid_sampler_tt) _self _grid cummax_tl :: Tensor -- ^ self -> Int -- ^ dim -> (Tensor,Tensor) cummax_tl _self _dim = unsafePerformIO $ (cast2 ATen.cummax_tl) _self _dim cummax_tn :: Tensor -- ^ self -> Dimname -- ^ dim -> (Tensor,Tensor) cummax_tn _self _dim = unsafePerformIO $ (cast2 ATen.cummax_tn) _self _dim cummin_tl :: Tensor -- ^ self -> Int -- ^ dim -> (Tensor,Tensor) cummin_tl _self _dim = unsafePerformIO $ (cast2 ATen.cummin_tl) _self _dim cummin_tn :: Tensor -- ^ self -> Dimname -- ^ dim -> (Tensor,Tensor) cummin_tn _self _dim = unsafePerformIO $ (cast2 ATen.cummin_tn) _self _dim cumprod :: Tensor -- ^ self -> Int -- ^ dim -> DType -- ^ dtype -> Tensor cumprod _self _dim _dtype = unsafePerformIO $ (cast3 ATen.cumprod_tls) _self _dim _dtype cumprodWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> DType -- ^ dtype -> Tensor cumprodWithDimname _self _dim _dtype = unsafePerformIO $ (cast3 ATen.cumprod_tns) _self _dim _dtype cumsum :: Tensor -- ^ self -> Int -- ^ dim -> DType -- ^ dtype -> Tensor cumsum _self _dim _dtype = unsafePerformIO $ (cast3 ATen.cumsum_tls) _self _dim _dtype cumsumWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> DType -- ^ dtype -> Tensor cumsumWithDimname _self _dim _dtype = unsafePerformIO $ (cast3 ATen.cumsum_tns) _self _dim _dtype cumulative_trapezoid_ttl :: Tensor -- ^ y -> Tensor -- ^ x -> Int -- ^ dim -> Tensor cumulative_trapezoid_ttl _y _x _dim = unsafePerformIO $ (cast3 ATen.cumulative_trapezoid_ttl) _y _x _dim cumulative_trapezoid_tsl :: Tensor -- ^ y -> Float -- ^ dx -> Int -- ^ dim -> Tensor cumulative_trapezoid_tsl _y _dx _dim = unsafePerformIO $ (cast3 ATen.cumulative_trapezoid_tsl) _y _dx _dim ctcLoss' :: Tensor -- ^ log_probs -> Tensor -- ^ targets -> [Int] -- ^ input_lengths -> [Int] -- ^ target_lengths -> Int -- ^ blank -> Int -- ^ reduction -> Bool -- ^ zero_infinity -> Tensor ctcLoss' _log_probs _targets _input_lengths _target_lengths _blank _reduction _zero_infinity = unsafePerformIO $ (cast7 ATen.ctc_loss_ttllllb) _log_probs _targets _input_lengths _target_lengths _blank _reduction _zero_infinity ctcLoss :: Tensor -- ^ log_probs -> Tensor -- ^ targets -> Tensor -- ^ input_lengths -> Tensor -- ^ target_lengths -> Int -- ^ blank -> Int -- ^ reduction -> Bool -- ^ zero_infinity -> Tensor ctcLoss _log_probs _targets _input_lengths _target_lengths _blank _reduction _zero_infinity = unsafePerformIO $ (cast7 ATen.ctc_loss_ttttllb) _log_probs _targets _input_lengths _target_lengths _blank _reduction _zero_infinity diag_embed :: Tensor -- ^ self -> Int -- ^ offset -> Int -- ^ dim1 -> Int -- ^ dim2 -> Tensor diag_embed _self _offset _dim1 _dim2 = unsafePerformIO $ (cast4 ATen.diag_embed_tlll) _self _offset _dim1 _dim2 diagflat :: Tensor -- ^ self -> Int -- ^ offset -> Tensor diagflat _self _offset = unsafePerformIO $ (cast2 ATen.diagflat_tl) _self _offset diagonal_tlll :: Tensor -- ^ self -> Int -- ^ offset -> Int -- ^ dim1 -> Int -- ^ dim2 -> Tensor diagonal_tlll _self _offset _dim1 _dim2 = unsafePerformIO $ (cast4 ATen.diagonal_tlll) _self _offset _dim1 _dim2 linalg_diagonal :: Tensor -- ^ A -> Int -- ^ offset -> Int -- ^ dim1 -> Int -- ^ dim2 -> Tensor linalg_diagonal _A _offset _dim1 _dim2 = unsafePerformIO $ (cast4 ATen.linalg_diagonal_tlll) _A _offset _dim1 _dim2 diagonal_tnnnl :: Tensor -- ^ self -> Dimname -- ^ outdim -> Dimname -- ^ dim1 -> Dimname -- ^ dim2 -> Int -- ^ offset -> Tensor diagonal_tnnnl _self _outdim _dim1 _dim2 _offset = unsafePerformIO $ (cast5 ATen.diagonal_tnnnl) _self _outdim _dim1 _dim2 _offset diff :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> Tensor -- ^ prepend -> Tensor -- ^ append -> Tensor diff _self _n _dim _prepend _append = unsafePerformIO $ (cast5 ATen.diff_tlltt) _self _n _dim _prepend _append gradient_tsll :: Tensor -- ^ self -> Float -- ^ spacing -> Int -- ^ dim -> Int -- ^ edge_order -> [Tensor] gradient_tsll _self _spacing _dim _edge_order = unsafePerformIO $ (cast4 ATen.gradient_tsll) _self _spacing _dim _edge_order -- gradient_tsll -- :: Tensor -- ^ self -- -> Float -- ^ spacing -- -> [Int] -- ^ dim -- -> Int -- ^ edge_order -- -> [Tensor] -- gradient_tsll _self _spacing _dim _edge_order = unsafePerformIO $ (cast4 ATen.gradient_tsll) _self _spacing _dim _edge_order gradient_tll :: Tensor -- ^ self -> [Int] -- ^ dim -> Int -- ^ edge_order -> [Tensor] gradient_tll _self _dim _edge_order = unsafePerformIO $ (cast3 ATen.gradient_tll) _self _dim _edge_order -- gradient_tAll -- :: Tensor -- ^ self -- -> [Scalar] -- ^ spacing -- -> Int -- ^ dim -- -> Int -- ^ edge_order -- -> [Tensor] -- gradient_tAll _self _spacing _dim _edge_order = unsafePerformIO $ (cast4 ATen.gradient_tAll) _self _spacing _dim _edge_order -- gradient_tAll -- :: Tensor -- ^ self -- -> [Scalar] -- ^ spacing -- -> [Int] -- ^ dim -- -> Int -- ^ edge_order -- -> [Tensor] -- gradient_tAll _self _spacing _dim _edge_order = unsafePerformIO $ (cast4 ATen.gradient_tAll) _self _spacing _dim _edge_order -- gradient_tlll -- :: Tensor -- ^ self -- -> [Tensor] -- ^ spacing -- -> Int -- ^ dim -- -> Int -- ^ edge_order -- -> [Tensor] -- gradient_tlll _self _spacing _dim _edge_order = unsafePerformIO $ (cast4 ATen.gradient_tlll) _self _spacing _dim _edge_order -- gradient_tlll -- :: Tensor -- ^ self -- -> [Tensor] -- ^ spacing -- -> [Int] -- ^ dim -- -> Int -- ^ edge_order -- -> [Tensor] -- gradient_tlll _self _spacing _dim _edge_order = unsafePerformIO $ (cast4 ATen.gradient_tlll) _self _spacing _dim _edge_order div :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor div _self _other = unsafePerformIO $ (cast2 ATen.div_tt) _self _other div_tts :: Tensor -- ^ self -> Tensor -- ^ other -> String -- ^ rounding_mode -> Tensor div_tts _self _other _rounding_mode = unsafePerformIO $ (cast3 ATen.div_tts) _self _other _rounding_mode divScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor divScalar _self _other = unsafePerformIO $ (cast2 ATen.div_ts) _self _other div_tss :: Tensor -- ^ self -> Float -- ^ other -> String -- ^ rounding_mode -> Tensor div_tss _self _other _rounding_mode = unsafePerformIO $ (cast3 ATen.div_tss) _self _other _rounding_mode divide_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor divide_tt _self _other = unsafePerformIO $ (cast2 ATen.divide_tt) _self _other divide_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor divide_ts _self _other = unsafePerformIO $ (cast2 ATen.divide_ts) _self _other divide_tts :: Tensor -- ^ self -> Tensor -- ^ other -> String -- ^ rounding_mode -> Tensor divide_tts _self _other _rounding_mode = unsafePerformIO $ (cast3 ATen.divide_tts) _self _other _rounding_mode divide_tss :: Tensor -- ^ self -> Float -- ^ other -> String -- ^ rounding_mode -> Tensor divide_tss _self _other _rounding_mode = unsafePerformIO $ (cast3 ATen.divide_tss) _self _other _rounding_mode true_divide_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor true_divide_tt _self _other = unsafePerformIO $ (cast2 ATen.true_divide_tt) _self _other true_divide_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor true_divide_ts _self _other = unsafePerformIO $ (cast2 ATen.true_divide_ts) _self _other dot :: Tensor -- ^ self -> Tensor -- ^ tensor -> Tensor dot _self _tensor = unsafePerformIO $ (cast2 ATen.dot_tt) _self _tensor vdot :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor vdot _self _other = unsafePerformIO $ (cast2 ATen.vdot_tt) _self _other einsum :: String -- ^ equation -> [Tensor] -- ^ tensors -> [Int] -- ^ path -> Tensor einsum _equation _tensors _path = unsafePerformIO $ (cast3 ATen.einsum_sll) _equation _tensors _path embedding :: Tensor -- ^ weight -> Tensor -- ^ indices -> Int -- ^ padding_idx -> Bool -- ^ scale_grad_by_freq -> Bool -- ^ sparse -> Tensor embedding _weight _indices _padding_idx _scale_grad_by_freq _sparse = unsafePerformIO $ (cast5 ATen.embedding_ttlbb) _weight _indices _padding_idx _scale_grad_by_freq _sparse row_stack :: [Tensor] -- ^ tensors -> Tensor row_stack _tensors = unsafePerformIO $ (cast1 ATen.row_stack_l) _tensors embedding_bag_tttblbtb :: Tensor -- ^ weight -> Tensor -- ^ indices -> Tensor -- ^ offsets -> Bool -- ^ scale_grad_by_freq -> Int -- ^ mode -> Bool -- ^ sparse -> Tensor -- ^ per_sample_weights -> Bool -- ^ include_last_offset -> (Tensor,Tensor,Tensor,Tensor) embedding_bag_tttblbtb _weight _indices _offsets _scale_grad_by_freq _mode _sparse _per_sample_weights _include_last_offset = unsafePerformIO $ (cast8 ATen.embedding_bag_tttblbtb) _weight _indices _offsets _scale_grad_by_freq _mode _sparse _per_sample_weights _include_last_offset embedding_bag_tttblbtbl :: Tensor -- ^ weight -> Tensor -- ^ indices -> Tensor -- ^ offsets -> Bool -- ^ scale_grad_by_freq -> Int -- ^ mode -> Bool -- ^ sparse -> Tensor -- ^ per_sample_weights -> Bool -- ^ include_last_offset -> Int -- ^ padding_idx -> (Tensor,Tensor,Tensor,Tensor) embedding_bag_tttblbtbl _weight _indices _offsets _scale_grad_by_freq _mode _sparse _per_sample_weights _include_last_offset _padding_idx = unsafePerformIO $ (cast9 ATen.embedding_bag_tttblbtbl) _weight _indices _offsets _scale_grad_by_freq _mode _sparse _per_sample_weights _include_last_offset _padding_idx erf :: Tensor -- ^ self -> Tensor erf _self = unsafePerformIO $ (cast1 ATen.erf_t) _self erfc :: Tensor -- ^ self -> Tensor erfc _self = unsafePerformIO $ (cast1 ATen.erfc_t) _self exp :: Tensor -- ^ self -> Tensor exp _self = unsafePerformIO $ (cast1 ATen.exp_t) _self exp2 :: Tensor -- ^ self -> Tensor exp2 _self = unsafePerformIO $ (cast1 ATen.exp2_t) _self expm1 :: Tensor -- ^ self -> Tensor expm1 _self = unsafePerformIO $ (cast1 ATen.expm1_t) _self flatten :: Tensor -- ^ self -> Int -- ^ start_dim -> Int -- ^ end_dim -> Tensor flatten _self _start_dim _end_dim = unsafePerformIO $ (cast3 ATen.flatten_tll) _self _start_dim _end_dim flattenTo :: Tensor -- ^ self -> Int -- ^ start_dim -> Int -- ^ end_dim -> Dimname -- ^ out_dim -> Tensor flattenTo _self _start_dim _end_dim _out_dim = unsafePerformIO $ (cast4 ATen.flatten_tlln) _self _start_dim _end_dim _out_dim flattenToWithDimname :: Tensor -- ^ self -> Dimname -- ^ start_dim -> Dimname -- ^ end_dim -> Dimname -- ^ out_dim -> Tensor flattenToWithDimname _self _start_dim _end_dim _out_dim = unsafePerformIO $ (cast4 ATen.flatten_tnnn) _self _start_dim _end_dim _out_dim flattenToWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dims -> Dimname -- ^ out_dim -> Tensor flattenToWithDimnames _self _dims _out_dim = unsafePerformIO $ (cast3 ATen.flatten_tNn) _self _dims _out_dim unflatten_tll :: Tensor -- ^ self -> Int -- ^ dim -> [Int] -- ^ sizes -> Tensor unflatten_tll _self _dim _sizes = unsafePerformIO $ (cast3 ATen.unflatten_tll) _self _dim _sizes unflatten_tnlN :: Tensor -- ^ self -> Dimname -- ^ dim -> [Int] -- ^ sizes -> [Dimname] -- ^ names -> Tensor unflatten_tnlN _self _dim _sizes _names = unsafePerformIO $ (cast4 ATen.unflatten_tnlN) _self _dim _sizes _names fill_ts :: Tensor -- ^ self -> Float -- ^ value -> Tensor fill_ts _self _value = unsafePerformIO $ (cast2 ATen.fill_ts) _self _value fill_tt :: Tensor -- ^ self -> Tensor -- ^ value -> Tensor fill_tt _self _value = unsafePerformIO $ (cast2 ATen.fill_tt) _self _value floor :: Tensor -- ^ self -> Tensor floor _self = unsafePerformIO $ (cast1 ATen.floor_t) _self floor_divide_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor floor_divide_tt _self _other = unsafePerformIO $ (cast2 ATen.floor_divide_tt) _self _other floor_divide_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor floor_divide_ts _self _other = unsafePerformIO $ (cast2 ATen.floor_divide_ts) _self _other frac :: Tensor -- ^ self -> Tensor frac _self = unsafePerformIO $ (cast1 ATen.frac_t) _self gcd :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor gcd _self _other = unsafePerformIO $ (cast2 ATen.gcd_tt) _self _other lcm :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor lcm _self _other = unsafePerformIO $ (cast2 ATen.lcm_tt) _self _other grid_sampler :: Tensor -- ^ input -> Tensor -- ^ grid -> Int -- ^ interpolation_mode -> Int -- ^ padding_mode -> Bool -- ^ align_corners -> Tensor grid_sampler _input _grid _interpolation_mode _padding_mode _align_corners = unsafePerformIO $ (cast5 ATen.grid_sampler_ttllb) _input _grid _interpolation_mode _padding_mode _align_corners grid_sampler_2d :: Tensor -- ^ input -> Tensor -- ^ grid -> Int -- ^ interpolation_mode -> Int -- ^ padding_mode -> Bool -- ^ align_corners -> Tensor grid_sampler_2d _input _grid _interpolation_mode _padding_mode _align_corners = unsafePerformIO $ (cast5 ATen.grid_sampler_2d_ttllb) _input _grid _interpolation_mode _padding_mode _align_corners grid_sampler_3d :: Tensor -- ^ input -> Tensor -- ^ grid -> Int -- ^ interpolation_mode -> Int -- ^ padding_mode -> Bool -- ^ align_corners -> Tensor grid_sampler_3d _input _grid _interpolation_mode _padding_mode _align_corners = unsafePerformIO $ (cast5 ATen.grid_sampler_3d_ttllb) _input _grid _interpolation_mode _padding_mode _align_corners hinge_embedding_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Double -- ^ margin -> Int -- ^ reduction -> Tensor hinge_embedding_loss _self _target _margin _reduction = unsafePerformIO $ (cast4 ATen.hinge_embedding_loss_ttdl) _self _target _margin _reduction group_norm :: Tensor -- ^ input -> Int -- ^ num_groups -> Tensor -- ^ weight -> Tensor -- ^ bias -> Double -- ^ eps -> Bool -- ^ cudnn_enabled -> Tensor group_norm _input _num_groups _weight _bias _eps _cudnn_enabled = unsafePerformIO $ (cast6 ATen.group_norm_tlttdb) _input _num_groups _weight _bias _eps _cudnn_enabled native_group_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Int -- ^ N -> Int -- ^ C -> Int -- ^ HxW -> Int -- ^ group -> Double -- ^ eps -> (Tensor,Tensor,Tensor) native_group_norm _input _weight _bias _N _C _HxW _group _eps = unsafePerformIO $ (cast8 ATen.native_group_norm_tttlllld) _input _weight _bias _N _C _HxW _group _eps index :: Tensor -- ^ self -> [Tensor] -- ^ indices -> Tensor index _self _indices = unsafePerformIO $ (cast2 ATen.index_tl) _self _indices indexCopy :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ source -> Tensor indexCopy _self _dim _index _source = unsafePerformIO $ (cast4 ATen.index_copy_tltt) _self _dim _index _source indexCopyWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ source -> Tensor indexCopyWithDimname _self _dim _index _source = unsafePerformIO $ (cast4 ATen.index_copy_tntt) _self _dim _index _source index_put :: Tensor -- ^ self -> [Tensor] -- ^ indices -> Tensor -- ^ values -> Bool -- ^ accumulate -> Tensor index_put _self _indices _values _accumulate = unsafePerformIO $ (cast4 ATen.index_put_tltb) _self _indices _values _accumulate instance_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Bool -- ^ use_input_stats -> Double -- ^ momentum -> Double -- ^ eps -> Bool -- ^ cudnn_enabled -> Tensor instance_norm _input _weight _bias _running_mean _running_var _use_input_stats _momentum _eps _cudnn_enabled = unsafePerformIO $ (cast9 ATen.instance_norm_tttttbddb) _input _weight _bias _running_mean _running_var _use_input_stats _momentum _eps _cudnn_enabled isclose :: Tensor -- ^ self -> Tensor -- ^ other -> Double -- ^ rtol -> Double -- ^ atol -> Bool -- ^ equal_nan -> Tensor isclose _self _other _rtol _atol _equal_nan = unsafePerformIO $ (cast5 ATen.isclose_ttddb) _self _other _rtol _atol _equal_nan isin_ttbb :: Tensor -- ^ elements -> Tensor -- ^ test_elements -> Bool -- ^ assume_unique -> Bool -- ^ invert -> Tensor isin_ttbb _elements _test_elements _assume_unique _invert = unsafePerformIO $ (cast4 ATen.isin_ttbb) _elements _test_elements _assume_unique _invert isin_tsbb :: Tensor -- ^ elements -> Float -- ^ test_element -> Bool -- ^ assume_unique -> Bool -- ^ invert -> Tensor isin_tsbb _elements _test_element _assume_unique _invert = unsafePerformIO $ (cast4 ATen.isin_tsbb) _elements _test_element _assume_unique _invert isin_stbb :: Float -- ^ element -> Tensor -- ^ test_elements -> Bool -- ^ assume_unique -> Bool -- ^ invert -> Tensor isin_stbb _element _test_elements _assume_unique _invert = unsafePerformIO $ (cast4 ATen.isin_stbb) _element _test_elements _assume_unique _invert isnan :: Tensor -- ^ self -> Tensor isnan _self = unsafePerformIO $ (cast1 ATen.isnan_t) _self is_distributed :: Tensor -- ^ self -> Bool is_distributed _self = unsafePerformIO $ (cast1 ATen.is_distributed_t) _self is_floating_point :: Tensor -- ^ self -> Bool is_floating_point _self = unsafePerformIO $ (cast1 ATen.is_floating_point_t) _self is_complex :: Tensor -- ^ self -> Bool is_complex _self = unsafePerformIO $ (cast1 ATen.is_complex_t) _self is_conj :: Tensor -- ^ self -> Bool is_conj _self = unsafePerformIO $ (cast1 ATen.is_conj_t) _self is_neg :: Tensor -- ^ self -> Bool is_neg _self = unsafePerformIO $ (cast1 ATen.is_neg_t) _self isreal :: Tensor -- ^ self -> Tensor isreal _self = unsafePerformIO $ (cast1 ATen.isreal_t) _self is_nonzero :: Tensor -- ^ self -> Bool is_nonzero _self = unsafePerformIO $ (cast1 ATen.is_nonzero_t) _self is_same_size :: Tensor -- ^ self -> Tensor -- ^ other -> Bool is_same_size _self _other = unsafePerformIO $ (cast2 ATen.is_same_size_tt) _self _other is_signed :: Tensor -- ^ self -> Bool is_signed _self = unsafePerformIO $ (cast1 ATen.is_signed_t) _self is_inference :: Tensor -- ^ self -> Bool is_inference _self = unsafePerformIO $ (cast1 ATen.is_inference_t) _self kl_div :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Bool -- ^ log_target -> Tensor kl_div _self _target _reduction _log_target = unsafePerformIO $ (cast4 ATen.kl_div_ttlb) _self _target _reduction _log_target kron :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor kron _self _other = unsafePerformIO $ (cast2 ATen.kron_tt) _self _other kthvalue :: Tensor -- ^ self -> Int -- ^ k -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) kthvalue _self _k _dim _keepdim = unsafePerformIO $ (cast4 ATen.kthvalue_tllb) _self _k _dim _keepdim kthvalueWithDimname :: Tensor -- ^ self -> Int -- ^ k -> Dimname -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) kthvalueWithDimname _self _k _dim _keepdim = unsafePerformIO $ (cast4 ATen.kthvalue_tlnb) _self _k _dim _keepdim layer_norm :: Tensor -- ^ input -> [Int] -- ^ normalized_shape -> Tensor -- ^ weight -> Tensor -- ^ bias -> Double -- ^ eps -> Bool -- ^ cudnn_enable -> Tensor layer_norm _input _normalized_shape _weight _bias _eps _cudnn_enable = unsafePerformIO $ (cast6 ATen.layer_norm_tlttdb) _input _normalized_shape _weight _bias _eps _cudnn_enable native_layer_norm :: Tensor -- ^ input -> [Int] -- ^ normalized_shape -> Tensor -- ^ weight -> Tensor -- ^ bias -> Double -- ^ eps -> (Tensor,Tensor,Tensor) native_layer_norm _input _normalized_shape _weight _bias _eps = unsafePerformIO $ (cast5 ATen.native_layer_norm_tlttd) _input _normalized_shape _weight _bias _eps nan_to_num :: Tensor -- ^ self -> Double -- ^ nan -> Double -- ^ posinf -> Double -- ^ neginf -> Tensor nan_to_num _self _nan _posinf _neginf = unsafePerformIO $ (cast4 ATen.nan_to_num_tddd) _self _nan _posinf _neginf linear :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor linear _input _weight _bias = unsafePerformIO $ (cast3 ATen.linear_ttt) _input _weight _bias mkldnn_linear :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor mkldnn_linear _self _weight _bias = unsafePerformIO $ (cast3 ATen.mkldnn_linear_ttt) _self _weight _bias mkldnn_linear_backward_input :: [Int] -- ^ input_size -> Tensor -- ^ grad_output -> Tensor -- ^ weight -> Tensor mkldnn_linear_backward_input _input_size _grad_output _weight = unsafePerformIO $ (cast3 ATen.mkldnn_linear_backward_input_ltt) _input_size _grad_output _weight mkldnn_linear_backward_weights :: Tensor -- ^ grad_output -> Tensor -- ^ input -> Tensor -- ^ weight -> Bool -- ^ bias_defined -> (Tensor,Tensor) mkldnn_linear_backward_weights _grad_output _input _weight _bias_defined = unsafePerformIO $ (cast4 ATen.mkldnn_linear_backward_weights_tttb) _grad_output _input _weight _bias_defined fbgemm_linear_int8_weight_fp32_activation :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ packed -> Tensor -- ^ col_offsets -> Float -- ^ weight_scale -> Float -- ^ weight_zero_point -> Tensor -- ^ bias -> Tensor fbgemm_linear_int8_weight_fp32_activation _input _weight _packed _col_offsets _weight_scale _weight_zero_point _bias = unsafePerformIO $ (cast7 ATen.fbgemm_linear_int8_weight_fp32_activation_ttttsst) _input _weight _packed _col_offsets _weight_scale _weight_zero_point _bias fbgemm_linear_int8_weight :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ packed -> Tensor -- ^ col_offsets -> Float -- ^ weight_scale -> Float -- ^ weight_zero_point -> Tensor -- ^ bias -> Tensor fbgemm_linear_int8_weight _input _weight _packed _col_offsets _weight_scale _weight_zero_point _bias = unsafePerformIO $ (cast7 ATen.fbgemm_linear_int8_weight_ttttsst) _input _weight _packed _col_offsets _weight_scale _weight_zero_point _bias fbgemm_linear_quantize_weight :: Tensor -- ^ input -> (Tensor,Tensor,Double,Int) fbgemm_linear_quantize_weight _input = unsafePerformIO $ (cast1 ATen.fbgemm_linear_quantize_weight_t) _input fbgemm_pack_gemm_matrix_fp16 :: Tensor -- ^ input -> Tensor fbgemm_pack_gemm_matrix_fp16 _input = unsafePerformIO $ (cast1 ATen.fbgemm_pack_gemm_matrix_fp16_t) _input fbgemm_linear_fp16_weight_fp32_activation :: Tensor -- ^ input -> Tensor -- ^ packed_weight -> Tensor -- ^ bias -> Tensor fbgemm_linear_fp16_weight_fp32_activation _input _packed_weight _bias = unsafePerformIO $ (cast3 ATen.fbgemm_linear_fp16_weight_fp32_activation_ttt) _input _packed_weight _bias fbgemm_linear_fp16_weight :: Tensor -- ^ input -> Tensor -- ^ packed_weight -> Tensor -- ^ bias -> Tensor fbgemm_linear_fp16_weight _input _packed_weight _bias = unsafePerformIO $ (cast3 ATen.fbgemm_linear_fp16_weight_ttt) _input _packed_weight _bias quantizeFbgemm' :: Tensor -- ^ input -> Tensor quantizeFbgemm' _input = unsafePerformIO $ (cast1 ATen.fbgemm_pack_quantized_matrix_t) _input quantizeFbgemm :: Tensor -- ^ input -> Int -- ^ K -> Int -- ^ N -> Tensor quantizeFbgemm _input _K _N = unsafePerformIO $ (cast3 ATen.fbgemm_pack_quantized_matrix_tll) _input _K _N ldexp :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor ldexp _self _other = unsafePerformIO $ (cast2 ATen.ldexp_tt) _self _other log :: Tensor -- ^ self -> Tensor log _self = unsafePerformIO $ (cast1 ATen.log_t) _self log10 :: Tensor -- ^ self -> Tensor log10 _self = unsafePerformIO $ (cast1 ATen.log10_t) _self log1p :: Tensor -- ^ self -> Tensor log1p _self = unsafePerformIO $ (cast1 ATen.log1p_t) _self log2 :: Tensor -- ^ self -> Tensor log2 _self = unsafePerformIO $ (cast1 ATen.log2_t) _self logaddexp :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor logaddexp _self _other = unsafePerformIO $ (cast2 ATen.logaddexp_tt) _self _other logaddexp2 :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor logaddexp2 _self _other = unsafePerformIO $ (cast2 ATen.logaddexp2_tt) _self _other xlogy_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor xlogy_tt _self _other = unsafePerformIO $ (cast2 ATen.xlogy_tt) _self _other xlogy_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor xlogy_st _self _other = unsafePerformIO $ (cast2 ATen.xlogy_st) _self _other xlogy_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor xlogy_ts _self _other = unsafePerformIO $ (cast2 ATen.xlogy_ts) _self _other logSoftmax :: Tensor -- ^ self -> Int -- ^ dim -> DType -- ^ dtype -> Tensor logSoftmax _self _dim _dtype = unsafePerformIO $ (cast3 ATen.log_softmax_tls) _self _dim _dtype logSoftmaxWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> DType -- ^ dtype -> Tensor logSoftmaxWithDimname _self _dim _dtype = unsafePerformIO $ (cast3 ATen.log_softmax_tns) _self _dim _dtype logcumsumexp_tl :: Tensor -- ^ self -> Int -- ^ dim -> Tensor logcumsumexp_tl _self _dim = unsafePerformIO $ (cast2 ATen.logcumsumexp_tl) _self _dim logcumsumexp_tn :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor logcumsumexp_tn _self _dim = unsafePerformIO $ (cast2 ATen.logcumsumexp_tn) _self _dim logsumexp :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor logsumexp _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.logsumexp_tlb) _self _dim _keepdim logsumexpWithDimnameList :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ keepdim -> Tensor logsumexpWithDimnameList _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.logsumexp_tNb) _self _dim _keepdim margin_ranking_loss :: Tensor -- ^ input1 -> Tensor -- ^ input2 -> Tensor -- ^ target -> Double -- ^ margin -> Int -- ^ reduction -> Tensor margin_ranking_loss _input1 _input2 _target _margin _reduction = unsafePerformIO $ (cast5 ATen.margin_ranking_loss_tttdl) _input1 _input2 _target _margin _reduction matmul :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor matmul _self _other = unsafePerformIO $ (cast2 ATen.matmul_tt) _self _other matrix_power :: Tensor -- ^ self -> Int -- ^ n -> Tensor matrix_power _self _n = unsafePerformIO $ (cast2 ATen.matrix_power_tl) _self _n matrix_exp :: Tensor -- ^ self -> Tensor matrix_exp _self = unsafePerformIO $ (cast1 ATen.matrix_exp_t) _self aminmax :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) aminmax _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.aminmax_tlb) _self _dim _keepdim maxDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) maxDim _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.max_tlb) _self _dim _keepdim maxWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) maxWithDimname _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.max_tnb) _self _dim _keepdim amax :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor amax _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.amax_tlb) _self _dim _keepdim max_pool1d_with_indices :: Tensor -- ^ self -> Int -- ^ kernel_size -> Int -- ^ stride -> Int -- ^ padding -> Int -- ^ dilation -> Bool -- ^ ceil_mode -> (Tensor,Tensor) max_pool1d_with_indices _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.max_pool1d_with_indices_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode max_pool1d :: Tensor -- ^ self -> Int -- ^ kernel_size -> Int -- ^ stride -> Int -- ^ padding -> Int -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor max_pool1d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.max_pool1d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode max_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor max_pool2d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.max_pool2d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode mkldnn_max_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor mkldnn_max_pool2d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.mkldnn_max_pool2d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode mkldnn_max_pool3d :: Tensor -- ^ self -> (Int,Int,Int) -- ^ kernel_size -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor mkldnn_max_pool3d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.mkldnn_max_pool3d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode quantized_max_pool1d :: Tensor -- ^ self -> Int -- ^ kernel_size -> Int -- ^ stride -> Int -- ^ padding -> Int -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor quantized_max_pool1d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.quantized_max_pool1d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode quantized_max_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor quantized_max_pool2d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.quantized_max_pool2d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode max_pool3d :: Tensor -- ^ self -> (Int,Int,Int) -- ^ kernel_size -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> Tensor max_pool3d _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.max_pool3d_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode meanAll :: Tensor -- ^ self -> DType -- ^ dtype -> Tensor meanAll _self _dtype = unsafePerformIO $ (cast2 ATen.mean_ts) _self _dtype meanDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor meanDim _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.mean_tlbs) _self _dim _keepdim _dtype meanWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor meanWithDimnames _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.mean_tNbs) _self _dim _keepdim _dtype nanmean :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor nanmean _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.nanmean_tlbs) _self _dim _keepdim _dtype medianAll :: Tensor -- ^ self -> Tensor medianAll _self = unsafePerformIO $ (cast1 ATen.median_t) _self medianDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) medianDim _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.median_tlb) _self _dim _keepdim medianWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) medianWithDimname _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.median_tnb) _self _dim _keepdim nanmedian_t :: Tensor -- ^ self -> Tensor nanmedian_t _self = unsafePerformIO $ (cast1 ATen.nanmedian_t) _self nanmedian_tlb :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) nanmedian_tlb _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.nanmedian_tlb) _self _dim _keepdim nanmedian_tnb :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) nanmedian_tnb _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.nanmedian_tnb) _self _dim _keepdim minDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) minDim _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.min_tlb) _self _dim _keepdim minWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) minWithDimname _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.min_tnb) _self _dim _keepdim amin :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor amin _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.amin_tlb) _self _dim _keepdim mkldnn_convolution :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ padding -> [Int] -- ^ stride -> [Int] -- ^ dilation -> Int -- ^ groups -> Tensor mkldnn_convolution _self _weight _bias _padding _stride _dilation _groups = unsafePerformIO $ (cast7 ATen.mkldnn_convolution_tttllll) _self _weight _bias _padding _stride _dilation _groups mkldnn_rnn_layer :: Tensor -- ^ input -> Tensor -- ^ weight0 -> Tensor -- ^ weight1 -> Tensor -- ^ weight2 -> Tensor -- ^ weight3 -> Tensor -- ^ hx_ -> Tensor -- ^ cx_ -> Bool -- ^ reverse -> [Int] -- ^ batch_sizes -> Int -- ^ mode -> Int -- ^ hidden_size -> Int -- ^ num_layers -> Bool -- ^ has_biases -> Bool -- ^ bidirectional -> Bool -- ^ batch_first -> Bool -- ^ train -> (Tensor,Tensor,Tensor,Tensor) mkldnn_rnn_layer _input _weight0 _weight1 _weight2 _weight3 _hx_ _cx_ _reverse _batch_sizes _mode _hidden_size _num_layers _has_biases _bidirectional _batch_first _train = unsafePerformIO $ (cast16 ATen.mkldnn_rnn_layer_tttttttbllllbbbb) _input _weight0 _weight1 _weight2 _weight3 _hx_ _cx_ _reverse _batch_sizes _mode _hidden_size _num_layers _has_biases _bidirectional _batch_first _train miopen_batch_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Bool -- ^ training -> Double -- ^ exponential_average_factor -> Double -- ^ epsilon -> (Tensor,Tensor,Tensor) miopen_batch_norm _input _weight _bias _running_mean _running_var _training _exponential_average_factor _epsilon = unsafePerformIO $ (cast8 ATen.miopen_batch_norm_tttttbdd) _input _weight _bias _running_mean _running_var _training _exponential_average_factor _epsilon miopen_convolution :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ padding -> [Int] -- ^ stride -> [Int] -- ^ dilation -> Int -- ^ groups -> Bool -- ^ benchmark -> Bool -- ^ deterministic -> Tensor miopen_convolution _self _weight _bias _padding _stride _dilation _groups _benchmark _deterministic = unsafePerformIO $ (cast9 ATen.miopen_convolution_tttllllbb) _self _weight _bias _padding _stride _dilation _groups _benchmark _deterministic miopen_convolution_transpose :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ padding -> [Int] -- ^ output_padding -> [Int] -- ^ stride -> [Int] -- ^ dilation -> Int -- ^ groups -> Bool -- ^ benchmark -> Bool -- ^ deterministic -> Tensor miopen_convolution_transpose _self _weight _bias _padding _output_padding _stride _dilation _groups _benchmark _deterministic = unsafePerformIO $ (cast10 ATen.miopen_convolution_transpose_tttlllllbb) _self _weight _bias _padding _output_padding _stride _dilation _groups _benchmark _deterministic miopen_depthwise_convolution :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ padding -> [Int] -- ^ stride -> [Int] -- ^ dilation -> Int -- ^ groups -> Bool -- ^ benchmark -> Bool -- ^ deterministic -> Tensor miopen_depthwise_convolution _self _weight _bias _padding _stride _dilation _groups _benchmark _deterministic = unsafePerformIO $ (cast9 ATen.miopen_depthwise_convolution_tttllllbb) _self _weight _bias _padding _stride _dilation _groups _benchmark _deterministic miopen_convolution_relu :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ bias -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Int -- ^ groups -> Tensor miopen_convolution_relu _self _weight _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast7 ATen.miopen_convolution_relu_tttllll) _self _weight _bias _stride _padding _dilation _groups miopen_convolution_add_relu :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor -- ^ z -> Float -- ^ alpha -> Tensor -- ^ bias -> [Int] -- ^ stride -> [Int] -- ^ padding -> [Int] -- ^ dilation -> Int -- ^ groups -> Tensor miopen_convolution_add_relu _self _weight _z _alpha _bias _stride _padding _dilation _groups = unsafePerformIO $ (cast9 ATen.miopen_convolution_add_relu_tttstllll) _self _weight _z _alpha _bias _stride _padding _dilation _groups miopen_rnn :: Tensor -- ^ input -> [Tensor] -- ^ weight -> Int -- ^ weight_stride0 -> Tensor -- ^ hx -> Tensor -- ^ cx -> Int -- ^ mode -> Int -- ^ hidden_size -> Int -- ^ num_layers -> Bool -- ^ batch_first -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> [Int] -- ^ batch_sizes -> Tensor -- ^ dropout_state -> (Tensor,Tensor,Tensor,Tensor,Tensor) miopen_rnn _input _weight _weight_stride0 _hx _cx _mode _hidden_size _num_layers _batch_first _dropout _train _bidirectional _batch_sizes _dropout_state = unsafePerformIO $ (cast14 ATen.miopen_rnn_tllttlllbdbblt) _input _weight _weight_stride0 _hx _cx _mode _hidden_size _num_layers _batch_first _dropout _train _bidirectional _batch_sizes _dropout_state mm :: Tensor -- ^ self -> Tensor -- ^ mat2 -> Tensor mm _self _mat2 = unsafePerformIO $ (cast2 ATen.mm_tt) _self _mat2 mode :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) mode _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.mode_tlb) _self _dim _keepdim modeWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> (Tensor,Tensor) modeWithDimname _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.mode_tnb) _self _dim _keepdim mul :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor mul _self _other = unsafePerformIO $ (cast2 ATen.mul_tt) _self _other mulScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor mulScalar _self _other = unsafePerformIO $ (cast2 ATen.mul_ts) _self _other multiply_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor multiply_tt _self _other = unsafePerformIO $ (cast2 ATen.multiply_tt) _self _other multiply_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor multiply_ts _self _other = unsafePerformIO $ (cast2 ATen.multiply_ts) _self _other mv :: Tensor -- ^ self -> Tensor -- ^ vec -> Tensor mv _self _vec = unsafePerformIO $ (cast2 ATen.mv_tt) _self _vec mvlgamma :: Tensor -- ^ self -> Int -- ^ p -> Tensor mvlgamma _self _p = unsafePerformIO $ (cast2 ATen.mvlgamma_tl) _self _p narrow_copy :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ start -> Int -- ^ length -> Tensor narrow_copy _self _dim _start _length = unsafePerformIO $ (cast4 ATen.narrow_copy_tlll) _self _dim _start _length narrow_tlll :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ start -> Int -- ^ length -> Tensor narrow_tlll _self _dim _start _length = unsafePerformIO $ (cast4 ATen.narrow_tlll) _self _dim _start _length narrow_tltl :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ start -> Int -- ^ length -> Tensor narrow_tltl _self _dim _start _length = unsafePerformIO $ (cast4 ATen.narrow_tltl) _self _dim _start _length native_batch_norm :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Bool -- ^ training -> Double -- ^ momentum -> Double -- ^ eps -> (Tensor,Tensor,Tensor) native_batch_norm _input _weight _bias _running_mean _running_var _training _momentum _eps = unsafePerformIO $ (cast8 ATen.native_batch_norm_tttttbdd) _input _weight _bias _running_mean _running_var _training _momentum _eps batch_norm_stats :: Tensor -- ^ input -> Double -- ^ eps -> (Tensor,Tensor) batch_norm_stats _input _eps = unsafePerformIO $ (cast2 ATen.batch_norm_stats_td) _input _eps batch_norm_elemt :: Tensor -- ^ input -> Tensor -- ^ weight -> Tensor -- ^ bias -> Tensor -- ^ mean -> Tensor -- ^ invstd -> Double -- ^ eps -> Tensor batch_norm_elemt _input _weight _bias _mean _invstd _eps = unsafePerformIO $ (cast6 ATen.batch_norm_elemt_tttttd) _input _weight _bias _mean _invstd _eps batch_norm_gather_stats :: Tensor -- ^ input -> Tensor -- ^ mean -> Tensor -- ^ invstd -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Double -- ^ momentum -> Double -- ^ eps -> Int -- ^ count -> (Tensor,Tensor) batch_norm_gather_stats _input _mean _invstd _running_mean _running_var _momentum _eps _count = unsafePerformIO $ (cast8 ATen.batch_norm_gather_stats_tttttddl) _input _mean _invstd _running_mean _running_var _momentum _eps _count batch_norm_gather_stats_with_counts :: Tensor -- ^ input -> Tensor -- ^ mean -> Tensor -- ^ invstd -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Double -- ^ momentum -> Double -- ^ eps -> Tensor -- ^ counts -> (Tensor,Tensor) batch_norm_gather_stats_with_counts _input _mean _invstd _running_mean _running_var _momentum _eps _counts = unsafePerformIO $ (cast8 ATen.batch_norm_gather_stats_with_counts_tttttddt) _input _mean _invstd _running_mean _running_var _momentum _eps _counts batch_norm_backward_reduce :: Tensor -- ^ grad_out -> Tensor -- ^ input -> Tensor -- ^ mean -> Tensor -- ^ invstd -> Tensor -- ^ weight -> Bool -- ^ input_g -> Bool -- ^ weight_g -> Bool -- ^ bias_g -> (Tensor,Tensor,Tensor,Tensor) batch_norm_backward_reduce _grad_out _input _mean _invstd _weight _input_g _weight_g _bias_g = unsafePerformIO $ (cast8 ATen.batch_norm_backward_reduce_tttttbbb) _grad_out _input _mean _invstd _weight _input_g _weight_g _bias_g batch_norm_backward_elemt :: Tensor -- ^ grad_out -> Tensor -- ^ input -> Tensor -- ^ mean -> Tensor -- ^ invstd -> Tensor -- ^ weight -> Tensor -- ^ mean_dy -> Tensor -- ^ mean_dy_xmu -> Tensor -- ^ count -> Tensor batch_norm_backward_elemt _grad_out _input _mean _invstd _weight _mean_dy _mean_dy_xmu _count = unsafePerformIO $ (cast8 ATen.batch_norm_backward_elemt_tttttttt) _grad_out _input _mean _invstd _weight _mean_dy _mean_dy_xmu _count batch_norm_update_stats :: Tensor -- ^ input -> Tensor -- ^ running_mean -> Tensor -- ^ running_var -> Double -- ^ momentum -> (Tensor,Tensor) batch_norm_update_stats _input _running_mean _running_var _momentum = unsafePerformIO $ (cast4 ATen.batch_norm_update_stats_tttd) _input _running_mean _running_var _momentum is_vulkan_available :: Bool is_vulkan_available = unsafePerformIO $ (cast0 ATen.is_vulkan_available) pairwise_distance :: Tensor -- ^ x1 -> Tensor -- ^ x2 -> Double -- ^ p -> Double -- ^ eps -> Bool -- ^ keepdim -> Tensor pairwise_distance _x1 _x2 _p _eps _keepdim = unsafePerformIO $ (cast5 ATen.pairwise_distance_ttddb) _x1 _x2 _p _eps _keepdim cdist :: Tensor -- ^ x1 -> Tensor -- ^ x2 -> Double -- ^ p -> Int -- ^ compute_mode -> Tensor cdist _x1 _x2 _p _compute_mode = unsafePerformIO $ (cast4 ATen.cdist_ttdl) _x1 _x2 _p _compute_mode pdist :: Tensor -- ^ self -> Double -- ^ p -> Tensor pdist _self _p = unsafePerformIO $ (cast2 ATen.pdist_td) _self _p cosine_similarity :: Tensor -- ^ x1 -> Tensor -- ^ x2 -> Int -- ^ dim -> Double -- ^ eps -> Tensor cosine_similarity _x1 _x2 _dim _eps = unsafePerformIO $ (cast4 ATen.cosine_similarity_ttld) _x1 _x2 _dim _eps permute :: Tensor -- ^ self -> [Int] -- ^ dims -> Tensor permute _self _dims = unsafePerformIO $ (cast2 ATen.permute_tl) _self _dims -- movedim_tll -- :: Tensor -- ^ self -- -> [Int] -- ^ source -- -> [Int] -- ^ destination -- -> Tensor -- movedim_tll _self _source _destination = unsafePerformIO $ (cast3 ATen.movedim_tll) _self _source _destination movedim_tll :: Tensor -- ^ self -> Int -- ^ source -> Int -- ^ destination -> Tensor movedim_tll _self _source _destination = unsafePerformIO $ (cast3 ATen.movedim_tll) _self _source _destination -- moveaxis_tll -- :: Tensor -- ^ self -- -> [Int] -- ^ source -- -> [Int] -- ^ destination -- -> Tensor -- moveaxis_tll _self _source _destination = unsafePerformIO $ (cast3 ATen.moveaxis_tll) _self _source _destination moveaxis_tll :: Tensor -- ^ self -> Int -- ^ source -> Int -- ^ destination -> Tensor moveaxis_tll _self _source _destination = unsafePerformIO $ (cast3 ATen.moveaxis_tll) _self _source _destination adjoint :: Tensor -- ^ self -> Tensor adjoint _self = unsafePerformIO $ (cast1 ATen.adjoint_t) _self pixel_shuffle :: Tensor -- ^ self -> Int -- ^ upscale_factor -> Tensor pixel_shuffle _self _upscale_factor = unsafePerformIO $ (cast2 ATen.pixel_shuffle_tl) _self _upscale_factor pixel_unshuffle :: Tensor -- ^ self -> Int -- ^ downscale_factor -> Tensor pixel_unshuffle _self _downscale_factor = unsafePerformIO $ (cast2 ATen.pixel_unshuffle_tl) _self _downscale_factor channel_shuffle :: Tensor -- ^ self -> Int -- ^ groups -> Tensor channel_shuffle _self _groups = unsafePerformIO $ (cast2 ATen.channel_shuffle_tl) _self _groups native_channel_shuffle :: Tensor -- ^ self -> Int -- ^ groups -> Tensor native_channel_shuffle _self _groups = unsafePerformIO $ (cast2 ATen.native_channel_shuffle_tl) _self _groups pinverse :: Tensor -- ^ self -> Double -- ^ rcond -> Tensor pinverse _self _rcond = unsafePerformIO $ (cast2 ATen.pinverse_td) _self _rcond poisson_nll_loss :: Tensor -- ^ input -> Tensor -- ^ target -> Bool -- ^ log_input -> Bool -- ^ full -> Double -- ^ eps -> Int -- ^ reduction -> Tensor poisson_nll_loss _input _target _log_input _full _eps _reduction = unsafePerformIO $ (cast6 ATen.poisson_nll_loss_ttbbdl) _input _target _log_input _full _eps _reduction rad2deg :: Tensor -- ^ self -> Tensor rad2deg _self = unsafePerformIO $ (cast1 ATen.rad2deg_t) _self deg2rad :: Tensor -- ^ self -> Tensor deg2rad _self = unsafePerformIO $ (cast1 ATen.deg2rad_t) _self ravel :: Tensor -- ^ self -> Tensor ravel _self = unsafePerformIO $ (cast1 ATen.ravel_t) _self reciprocal :: Tensor -- ^ self -> Tensor reciprocal _self = unsafePerformIO $ (cast1 ATen.reciprocal_t) _self neg :: Tensor -- ^ self -> Tensor neg _self = unsafePerformIO $ (cast1 ATen.neg_t) _self negative :: Tensor -- ^ self -> Tensor negative _self = unsafePerformIO $ (cast1 ATen.negative_t) _self repeat_interleave_tl :: Tensor -- ^ repeats -> Int -- ^ output_size -> Tensor repeat_interleave_tl _repeats _output_size = unsafePerformIO $ (cast2 ATen.repeat_interleave_tl) _repeats _output_size repeat_interleave_ttll :: Tensor -- ^ self -> Tensor -- ^ repeats -> Int -- ^ dim -> Int -- ^ output_size -> Tensor repeat_interleave_ttll _self _repeats _dim _output_size = unsafePerformIO $ (cast4 ATen.repeat_interleave_ttll) _self _repeats _dim _output_size repeat_interleave_tlll :: Tensor -- ^ self -> Int -- ^ repeats -> Int -- ^ dim -> Int -- ^ output_size -> Tensor repeat_interleave_tlll _self _repeats _dim _output_size = unsafePerformIO $ (cast4 ATen.repeat_interleave_tlll) _self _repeats _dim _output_size reshape :: Tensor -- ^ self -> [Int] -- ^ shape -> Tensor reshape _self _shape = unsafePerformIO $ (cast2 ATen.reshape_tl) _self _shape round_t :: Tensor -- ^ self -> Tensor round_t _self = unsafePerformIO $ (cast1 ATen.round_t) _self round_tl :: Tensor -- ^ self -> Int -- ^ decimals -> Tensor round_tl _self _decimals = unsafePerformIO $ (cast2 ATen.round_tl) _self _decimals relu :: Tensor -- ^ self -> Tensor relu _self = unsafePerformIO $ (cast1 ATen.relu_t) _self relu6 :: Tensor -- ^ self -> Tensor relu6 _self = unsafePerformIO $ (cast1 ATen.relu6_t) _self prelu :: Tensor -- ^ self -> Tensor -- ^ weight -> Tensor prelu _self _weight = unsafePerformIO $ (cast2 ATen.prelu_tt) _self _weight gelu :: Tensor -- ^ self -> String -- ^ approximate -> Tensor gelu _self _approximate = unsafePerformIO $ (cast2 ATen.gelu_ts) _self _approximate hardshrink :: Tensor -- ^ self -> Float -- ^ lambd -> Tensor hardshrink _self _lambd = unsafePerformIO $ (cast2 ATen.hardshrink_ts) _self _lambd rsqrt :: Tensor -- ^ self -> Tensor rsqrt _self = unsafePerformIO $ (cast1 ATen.rsqrt_t) _self selectWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Int -- ^ index -> Tensor selectWithDimname _self _dim _index = unsafePerformIO $ (cast3 ATen.select_tnl) _self _dim _index select :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ index -> Tensor select _self _dim _index = unsafePerformIO $ (cast3 ATen.select_tll) _self _dim _index selu :: Tensor -- ^ self -> Tensor selu _self = unsafePerformIO $ (cast1 ATen.selu_t) _self celu :: Tensor -- ^ self -> Float -- ^ alpha -> Tensor celu _self _alpha = unsafePerformIO $ (cast2 ATen.celu_ts) _self _alpha silu :: Tensor -- ^ self -> Tensor silu _self = unsafePerformIO $ (cast1 ATen.silu_t) _self mish :: Tensor -- ^ self -> Tensor mish _self = unsafePerformIO $ (cast1 ATen.mish_t) _self sigmoid :: Tensor -- ^ self -> Tensor sigmoid _self = unsafePerformIO $ (cast1 ATen.sigmoid_t) _self logit :: Tensor -- ^ self -> Double -- ^ eps -> Tensor logit _self _eps = unsafePerformIO $ (cast2 ATen.logit_td) _self _eps sin :: Tensor -- ^ self -> Tensor sin _self = unsafePerformIO $ (cast1 ATen.sin_t) _self sinc :: Tensor -- ^ self -> Tensor sinc _self = unsafePerformIO $ (cast1 ATen.sinc_t) _self sinh :: Tensor -- ^ self -> Tensor sinh _self = unsafePerformIO $ (cast1 ATen.sinh_t) _self size :: Tensor -- ^ self -> Int -- ^ dim -> Int size _self _dim = unsafePerformIO $ (cast2 ATen.size_tl) _self _dim sizeWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Int sizeWithDimname _self _dim = unsafePerformIO $ (cast2 ATen.size_tn) _self _dim slice :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ start -> Int -- ^ end -> Int -- ^ step -> Tensor slice _self _dim _start _end _step = unsafePerformIO $ (cast5 ATen.slice_tllll) _self _dim _start _end _step slice_scatter :: Tensor -- ^ self -> Tensor -- ^ src -> Int -- ^ dim -> Int -- ^ start -> Int -- ^ end -> Int -- ^ step -> Tensor slice_scatter _self _src _dim _start _end _step = unsafePerformIO $ (cast6 ATen.slice_scatter_ttllll) _self _src _dim _start _end _step select_scatter :: Tensor -- ^ self -> Tensor -- ^ src -> Int -- ^ dim -> Int -- ^ index -> Tensor select_scatter _self _src _dim _index = unsafePerformIO $ (cast4 ATen.select_scatter_ttll) _self _src _dim _index diagonal_scatter :: Tensor -- ^ self -> Tensor -- ^ src -> Int -- ^ offset -> Int -- ^ dim1 -> Int -- ^ dim2 -> Tensor diagonal_scatter _self _src _offset _dim1 _dim2 = unsafePerformIO $ (cast5 ATen.diagonal_scatter_ttlll) _self _src _offset _dim1 _dim2 as_strided_scatter :: Tensor -- ^ self -> Tensor -- ^ src -> [Int] -- ^ size -> [Int] -- ^ stride -> Int -- ^ storage_offset -> Tensor as_strided_scatter _self _src _size _stride _storage_offset = unsafePerformIO $ (cast5 ATen.as_strided_scatter_ttlll) _self _src _size _stride _storage_offset smm :: Tensor -- ^ self -> Tensor -- ^ mat2 -> Tensor smm _self _mat2 = unsafePerformIO $ (cast2 ATen.smm_tt) _self _mat2 softmax :: Tensor -- ^ self -> Int -- ^ dim -> DType -- ^ dtype -> Tensor softmax _self _dim _dtype = unsafePerformIO $ (cast3 ATen.softmax_tls) _self _dim _dtype softmaxWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> DType -- ^ dtype -> Tensor softmaxWithDimname _self _dim _dtype = unsafePerformIO $ (cast3 ATen.softmax_tns) _self _dim _dtype unsafe_split :: Tensor -- ^ self -> Int -- ^ split_size -> Int -- ^ dim -> [Tensor] unsafe_split _self _split_size _dim = unsafePerformIO $ (cast3 ATen.unsafe_split_tll) _self _split_size _dim split_tll :: Tensor -- ^ self -> Int -- ^ split_size -> Int -- ^ dim -> [Tensor] split_tll _self _split_size _dim = unsafePerformIO $ (cast3 ATen.split_tll) _self _split_size _dim -- split_tll -- :: Tensor -- ^ self -- -> [Int] -- ^ split_size -- -> Int -- ^ dim -- -> [Tensor] -- split_tll _self _split_size _dim = unsafePerformIO $ (cast3 ATen.split_tll) _self _split_size _dim unsafe_split_with_sizes :: Tensor -- ^ self -> [Int] -- ^ split_sizes -> Int -- ^ dim -> [Tensor] unsafe_split_with_sizes _self _split_sizes _dim = unsafePerformIO $ (cast3 ATen.unsafe_split_with_sizes_tll) _self _split_sizes _dim split_with_sizes :: Tensor -- ^ self -> [Int] -- ^ split_sizes -> Int -- ^ dim -> [Tensor] split_with_sizes _self _split_sizes _dim = unsafePerformIO $ (cast3 ATen.split_with_sizes_tll) _self _split_sizes _dim hsplit_tl :: Tensor -- ^ self -> Int -- ^ sections -> [Tensor] hsplit_tl _self _sections = unsafePerformIO $ (cast2 ATen.hsplit_tl) _self _sections -- hsplit_tl -- :: Tensor -- ^ self -- -> [Int] -- ^ indices -- -> [Tensor] -- hsplit_tl _self _indices = unsafePerformIO $ (cast2 ATen.hsplit_tl) _self _indices vsplit_tl :: Tensor -- ^ self -> Int -- ^ sections -> [Tensor] vsplit_tl _self _sections = unsafePerformIO $ (cast2 ATen.vsplit_tl) _self _sections -- vsplit_tl -- :: Tensor -- ^ self -- -> [Int] -- ^ indices -- -> [Tensor] -- vsplit_tl _self _indices = unsafePerformIO $ (cast2 ATen.vsplit_tl) _self _indices dsplit_tl :: Tensor -- ^ self -> Int -- ^ sections -> [Tensor] dsplit_tl _self _sections = unsafePerformIO $ (cast2 ATen.dsplit_tl) _self _sections -- dsplit_tl -- :: Tensor -- ^ self -- -> [Int] -- ^ indices -- -> [Tensor] -- dsplit_tl _self _indices = unsafePerformIO $ (cast2 ATen.dsplit_tl) _self _indices squeezeAll :: Tensor -- ^ self -> Tensor squeezeAll _self = unsafePerformIO $ (cast1 ATen.squeeze_t) _self squeezeDim :: Tensor -- ^ self -> Int -- ^ dim -> Tensor squeezeDim _self _dim = unsafePerformIO $ (cast2 ATen.squeeze_tl) _self _dim squeezeWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor squeezeWithDimname _self _dim = unsafePerformIO $ (cast2 ATen.squeeze_tn) _self _dim -- squeezeDim -- :: Tensor -- ^ self -- -> [Int] -- ^ dim -- -> Tensor -- squeezeDim _self _dim = unsafePerformIO $ (cast2 ATen.squeeze_tl) _self _dim sspaddmm :: Tensor -- ^ self -> Tensor -- ^ mat1 -> Tensor -- ^ mat2 -> Float -- ^ beta -> Float -- ^ alpha -> Tensor sspaddmm _self _mat1 _mat2 _beta _alpha = unsafePerformIO $ (cast5 ATen.sspaddmm_tttss) _self _mat1 _mat2 _beta _alpha stack :: [Tensor] -- ^ tensors -> Int -- ^ dim -> Tensor stack _tensors _dim = unsafePerformIO $ (cast2 ATen.stack_ll) _tensors _dim hstack :: [Tensor] -- ^ tensors -> Tensor hstack _tensors = unsafePerformIO $ (cast1 ATen.hstack_l) _tensors vstack :: [Tensor] -- ^ tensors -> Tensor vstack _tensors = unsafePerformIO $ (cast1 ATen.vstack_l) _tensors dstack :: [Tensor] -- ^ tensors -> Tensor dstack _tensors = unsafePerformIO $ (cast1 ATen.dstack_l) _tensors stft_tllltbbb :: Tensor -- ^ self -> Int -- ^ n_fft -> Int -- ^ hop_length -> Int -- ^ win_length -> Tensor -- ^ window -> Bool -- ^ normalized -> Bool -- ^ onesided -> Bool -- ^ return_complex -> Tensor stft_tllltbbb _self _n_fft _hop_length _win_length _window _normalized _onesided _return_complex = unsafePerformIO $ (cast8 ATen.stft_tllltbbb) _self _n_fft _hop_length _win_length _window _normalized _onesided _return_complex stft_tllltbsbbb :: Tensor -- ^ self -> Int -- ^ n_fft -> Int -- ^ hop_length -> Int -- ^ win_length -> Tensor -- ^ window -> Bool -- ^ center -> String -- ^ pad_mode -> Bool -- ^ normalized -> Bool -- ^ onesided -> Bool -- ^ return_complex -> Tensor stft_tllltbsbbb _self _n_fft _hop_length _win_length _window _center _pad_mode _normalized _onesided _return_complex = unsafePerformIO $ (cast10 ATen.stft_tllltbsbbb) _self _n_fft _hop_length _win_length _window _center _pad_mode _normalized _onesided _return_complex istft :: Tensor -- ^ self -> Int -- ^ n_fft -> Int -- ^ hop_length -> Int -- ^ win_length -> Tensor -- ^ window -> Bool -- ^ center -> Bool -- ^ normalized -> Bool -- ^ onesided -> Int -- ^ length -> Bool -- ^ return_complex -> Tensor istft _self _n_fft _hop_length _win_length _window _center _normalized _onesided _length _return_complex = unsafePerformIO $ (cast10 ATen.istft_tllltbbblb) _self _n_fft _hop_length _win_length _window _center _normalized _onesided _length _return_complex stride :: Tensor -- ^ self -> Int -- ^ dim -> Int stride _self _dim = unsafePerformIO $ (cast2 ATen.stride_tl) _self _dim strideWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Int strideWithDimname _self _dim = unsafePerformIO $ (cast2 ATen.stride_tn) _self _dim sumAll :: Tensor -- ^ self -> DType -- ^ dtype -> Tensor sumAll _self _dtype = unsafePerformIO $ (cast2 ATen.sum_ts) _self _dtype sumDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor sumDim _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.sum_tlbs) _self _dim _keepdim _dtype sumWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor sumWithDimnames _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.sum_tNbs) _self _dim _keepdim _dtype nansum :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor nansum _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.nansum_tlbs) _self _dim _keepdim _dtype sqrt :: Tensor -- ^ self -> Tensor sqrt _self = unsafePerformIO $ (cast1 ATen.sqrt_t) _self square :: Tensor -- ^ self -> Tensor square _self = unsafePerformIO $ (cast1 ATen.square_t) _self stdAll :: Tensor -- ^ self -> Bool -- ^ unbiased -> Tensor stdAll _self _unbiased = unsafePerformIO $ (cast2 ATen.std_tb) _self _unbiased stdDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> Tensor stdDim _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.std_tlbb) _self _dim _unbiased _keepdim std_tllb :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> Tensor std_tllb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.std_tllb) _self _dim _correction _keepdim stdMeanAll :: Tensor -- ^ self -> Bool -- ^ unbiased -> (Tensor,Tensor) stdMeanAll _self _unbiased = unsafePerformIO $ (cast2 ATen.std_mean_tb) _self _unbiased stdMeanDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> (Tensor,Tensor) stdMeanDim _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.std_mean_tlbb) _self _dim _unbiased _keepdim std_mean_tllb :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> (Tensor,Tensor) std_mean_tllb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.std_mean_tllb) _self _dim _correction _keepdim stdMeanWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> (Tensor,Tensor) stdMeanWithDimnames _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.std_mean_tNbb) _self _dim _unbiased _keepdim std_mean_tNlb :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> (Tensor,Tensor) std_mean_tNlb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.std_mean_tNlb) _self _dim _correction _keepdim stdWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> Tensor stdWithDimnames _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.std_tNbb) _self _dim _unbiased _keepdim std_tNlb :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> Tensor std_tNlb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.std_tNlb) _self _dim _correction _keepdim prodAll :: Tensor -- ^ self -> DType -- ^ dtype -> Tensor prodAll _self _dtype = unsafePerformIO $ (cast2 ATen.prod_ts) _self _dtype prodDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor prodDim _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.prod_tlbs) _self _dim _keepdim _dtype prodWithDimnames :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor prodWithDimnames _self _dim _keepdim _dtype = unsafePerformIO $ (cast4 ATen.prod_tnbs) _self _dim _keepdim _dtype t :: Tensor -- ^ self -> Tensor t _self = unsafePerformIO $ (cast1 ATen.t_t) _self tan :: Tensor -- ^ self -> Tensor tan _self = unsafePerformIO $ (cast1 ATen.tan_t) _self tanh :: Tensor -- ^ self -> Tensor tanh _self = unsafePerformIO $ (cast1 ATen.tanh_t) _self tensordot :: Tensor -- ^ self -> Tensor -- ^ other -> [Int] -- ^ dims_self -> [Int] -- ^ dims_other -> Tensor tensordot _self _other _dims_self _dims_other = unsafePerformIO $ (cast4 ATen.tensordot_ttll) _self _other _dims_self _dims_other threshold :: Tensor -- ^ self -> Float -- ^ threshold -> Float -- ^ value -> Tensor threshold _self _threshold _value = unsafePerformIO $ (cast3 ATen.threshold_tss) _self _threshold _value tile :: Tensor -- ^ self -> [Int] -- ^ dims -> Tensor tile _self _dims = unsafePerformIO $ (cast2 ATen.tile_tl) _self _dims transpose :: Tensor -- ^ self -> Int -- ^ dim0 -> Int -- ^ dim1 -> Tensor transpose _self _dim0 _dim1 = unsafePerformIO $ (cast3 ATen.transpose_tll) _self _dim0 _dim1 transposeWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim0 -> Dimname -- ^ dim1 -> Tensor transposeWithDimname _self _dim0 _dim1 = unsafePerformIO $ (cast3 ATen.transpose_tnn) _self _dim0 _dim1 one_hot :: Tensor -- ^ self -> Int -- ^ num_classes -> Tensor one_hot _self _num_classes = unsafePerformIO $ (cast2 ATen.one_hot_tl) _self _num_classes flip :: Tensor -- ^ self -> [Int] -- ^ dims -> Tensor flip _self _dims = unsafePerformIO $ (cast2 ATen.flip_tl) _self _dims fliplr :: Tensor -- ^ self -> Tensor fliplr _self = unsafePerformIO $ (cast1 ATen.fliplr_t) _self flipud :: Tensor -- ^ self -> Tensor flipud _self = unsafePerformIO $ (cast1 ATen.flipud_t) _self roll :: Tensor -- ^ self -> Int -- ^ shifts -> Int -- ^ dims -> Tensor roll _self _shifts _dims = unsafePerformIO $ (cast3 ATen.roll_tll) _self _shifts _dims rot90 :: Tensor -- ^ self -> Int -- ^ k -> [Int] -- ^ dims -> Tensor rot90 _self _k _dims = unsafePerformIO $ (cast3 ATen.rot90_tll) _self _k _dims trapezoid_ttl :: Tensor -- ^ y -> Tensor -- ^ x -> Int -- ^ dim -> Tensor trapezoid_ttl _y _x _dim = unsafePerformIO $ (cast3 ATen.trapezoid_ttl) _y _x _dim trapezoid_tsl :: Tensor -- ^ y -> Float -- ^ dx -> Int -- ^ dim -> Tensor trapezoid_tsl _y _dx _dim = unsafePerformIO $ (cast3 ATen.trapezoid_tsl) _y _dx _dim trapz :: Tensor -- ^ y -> Tensor -- ^ x -> Int -- ^ dim -> Tensor trapz _y _x _dim = unsafePerformIO $ (cast3 ATen.trapz_ttl) _y _x _dim trapzScalar :: Tensor -- ^ y -> Double -- ^ dx -> Int -- ^ dim -> Tensor trapzScalar _y _dx _dim = unsafePerformIO $ (cast3 ATen.trapz_tdl) _y _dx _dim triplet_margin_loss :: Tensor -- ^ anchor -> Tensor -- ^ positive -> Tensor -- ^ negative -> Double -- ^ margin -> Double -- ^ p -> Double -- ^ eps -> Bool -- ^ swap -> Int -- ^ reduction -> Tensor triplet_margin_loss _anchor _positive _negative _margin _p _eps _swap _reduction = unsafePerformIO $ (cast8 ATen.triplet_margin_loss_tttdddbl) _anchor _positive _negative _margin _p _eps _swap _reduction trunc :: Tensor -- ^ self -> Tensor trunc _self = unsafePerformIO $ (cast1 ATen.trunc_t) _self fix :: Tensor -- ^ self -> Tensor fix _self = unsafePerformIO $ (cast1 ATen.fix_t) _self unique_dim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ sorted -> Bool -- ^ return_inverse -> Bool -- ^ return_counts -> (Tensor,Tensor,Tensor) unique_dim _self _dim _sorted _return_inverse _return_counts = unsafePerformIO $ (cast5 ATen.unique_dim_tlbbb) _self _dim _sorted _return_inverse _return_counts unique_consecutive :: Tensor -- ^ self -> Bool -- ^ return_inverse -> Bool -- ^ return_counts -> Int -- ^ dim -> (Tensor,Tensor,Tensor) unique_consecutive _self _return_inverse _return_counts _dim = unsafePerformIO $ (cast4 ATen.unique_consecutive_tbbl) _self _return_inverse _return_counts _dim unique_dim_consecutive :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ return_inverse -> Bool -- ^ return_counts -> (Tensor,Tensor,Tensor) unique_dim_consecutive _self _dim _return_inverse _return_counts = unsafePerformIO $ (cast4 ATen.unique_dim_consecutive_tlbb) _self _dim _return_inverse _return_counts unsqueeze :: Tensor -- ^ self -> Int -- ^ dim -> Tensor unsqueeze _self _dim = unsafePerformIO $ (cast2 ATen.unsqueeze_tl) _self _dim vander :: Tensor -- ^ x -> Int -- ^ N -> Bool -- ^ increasing -> Tensor vander _x _N _increasing = unsafePerformIO $ (cast3 ATen.vander_tlb) _x _N _increasing var :: Tensor -- ^ self -> Bool -- ^ unbiased -> Tensor var _self _unbiased = unsafePerformIO $ (cast2 ATen.var_tb) _self _unbiased varDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> Tensor varDim _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.var_tlbb) _self _dim _unbiased _keepdim var_tllb :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> Tensor var_tllb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.var_tllb) _self _dim _correction _keepdim varWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> Tensor varWithDimnames _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.var_tNbb) _self _dim _unbiased _keepdim var_tNlb :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> Tensor var_tNlb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.var_tNlb) _self _dim _correction _keepdim varMean :: Tensor -- ^ self -> Bool -- ^ unbiased -> (Tensor,Tensor) varMean _self _unbiased = unsafePerformIO $ (cast2 ATen.var_mean_tb) _self _unbiased varMeanDim :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> (Tensor,Tensor) varMeanDim _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.var_mean_tlbb) _self _dim _unbiased _keepdim var_mean_tllb :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> (Tensor,Tensor) var_mean_tllb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.var_mean_tllb) _self _dim _correction _keepdim varMeanWithDimnames :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Bool -- ^ unbiased -> Bool -- ^ keepdim -> (Tensor,Tensor) varMeanWithDimnames _self _dim _unbiased _keepdim = unsafePerformIO $ (cast4 ATen.var_mean_tNbb) _self _dim _unbiased _keepdim var_mean_tNlb :: Tensor -- ^ self -> [Dimname] -- ^ dim -> Int -- ^ correction -> Bool -- ^ keepdim -> (Tensor,Tensor) var_mean_tNlb _self _dim _correction _keepdim = unsafePerformIO $ (cast4 ATen.var_mean_tNlb) _self _dim _correction _keepdim where' :: Tensor -- ^ condition -> Tensor -- ^ self -> Tensor -- ^ other -> Tensor where' _condition _self _other = unsafePerformIO $ (cast3 ATen.where_ttt) _condition _self _other where_tst :: Tensor -- ^ condition -> Float -- ^ self -> Tensor -- ^ other -> Tensor where_tst _condition _self _other = unsafePerformIO $ (cast3 ATen.where_tst) _condition _self _other where_tts :: Tensor -- ^ condition -> Tensor -- ^ self -> Float -- ^ other -> Tensor where_tts _condition _self _other = unsafePerformIO $ (cast3 ATen.where_tts) _condition _self _other where_tss :: Tensor -- ^ condition -> Float -- ^ self -> Float -- ^ other -> Tensor where_tss _condition _self _other = unsafePerformIO $ (cast3 ATen.where_tss) _condition _self _other isNonZero :: Tensor -- ^ condition -> [Tensor] isNonZero _condition = unsafePerformIO $ (cast1 ATen.where_t) _condition norm_except_dim :: Tensor -- ^ v -> Int -- ^ pow -> Int -- ^ dim -> Tensor norm_except_dim _v _pow _dim = unsafePerformIO $ (cast3 ATen.norm_except_dim_tll) _v _pow _dim native_norm_ts :: Tensor -- ^ self -> Float -- ^ p -> Tensor native_norm_ts _self _p = unsafePerformIO $ (cast2 ATen.native_norm_ts) _self _p native_norm_tslbs :: Tensor -- ^ self -> Float -- ^ p -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor native_norm_tslbs _self _p _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.native_norm_tslbs) _self _p _dim _keepdim _dtype normCastAll :: Tensor -- ^ self -> Float -- ^ p -> DType -- ^ dtype -> Tensor normCastAll _self _p _dtype = unsafePerformIO $ (cast3 ATen.norm_tss) _self _p _dtype normAll :: Tensor -- ^ self -> Float -- ^ p -> Tensor normAll _self _p = unsafePerformIO $ (cast2 ATen.norm_ts) _self _p normCastDim :: Tensor -- ^ self -> Float -- ^ p -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor normCastDim _self _p _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.norm_tslbs) _self _p _dim _keepdim _dtype normDim :: Tensor -- ^ self -> Float -- ^ p -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor normDim _self _p _dim _keepdim = unsafePerformIO $ (cast4 ATen.norm_tslb) _self _p _dim _keepdim norm_tsNbs :: Tensor -- ^ self -> Float -- ^ p -> [Dimname] -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor norm_tsNbs _self _p _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.norm_tsNbs) _self _p _dim _keepdim _dtype norm_tsNb :: Tensor -- ^ self -> Float -- ^ p -> [Dimname] -- ^ dim -> Bool -- ^ keepdim -> Tensor norm_tsNb _self _p _dim _keepdim = unsafePerformIO $ (cast4 ATen.norm_tsNb) _self _p _dim _keepdim frexp :: Tensor -- ^ self -> (Tensor,Tensor) frexp _self = unsafePerformIO $ (cast1 ATen.frexp_t) _self frobenius_norm :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor frobenius_norm _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.frobenius_norm_tlb) _self _dim _keepdim nuclearNormAll :: Tensor -- ^ self -> Bool -- ^ keepdim -> Tensor nuclearNormAll _self _keepdim = unsafePerformIO $ (cast2 ATen.nuclear_norm_tb) _self _keepdim nuclearNormDim :: Tensor -- ^ self -> (Int,Int) -- ^ dim -> Bool -- ^ keepdim -> Tensor nuclearNormDim _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.nuclear_norm_tlb) _self _dim _keepdim clone :: Tensor -- ^ self -> ATen.MemoryFormat -- ^ memory_format -> Tensor clone _self _memory_format = unsafePerformIO $ (cast2 ATen.clone_tM) _self _memory_format positive :: Tensor -- ^ self -> Tensor positive _self = unsafePerformIO $ (cast1 ATen.positive_t) _self sub :: Tensor -- ^ self -> Tensor -- ^ other -> Float -- ^ alpha -> Tensor sub _self _other _alpha = unsafePerformIO $ (cast3 ATen.sub_tts) _self _other _alpha subScalar :: Tensor -- ^ self -> Float -- ^ other -> Float -- ^ alpha -> Tensor subScalar _self _other _alpha = unsafePerformIO $ (cast3 ATen.sub_tss) _self _other _alpha subtract_tts :: Tensor -- ^ self -> Tensor -- ^ other -> Float -- ^ alpha -> Tensor subtract_tts _self _other _alpha = unsafePerformIO $ (cast3 ATen.subtract_tts) _self _other _alpha subtract_tss :: Tensor -- ^ self -> Float -- ^ other -> Float -- ^ alpha -> Tensor subtract_tss _self _other _alpha = unsafePerformIO $ (cast3 ATen.subtract_tss) _self _other _alpha rsub :: Tensor -- ^ self -> Tensor -- ^ other -> Float -- ^ alpha -> Tensor rsub _self _other _alpha = unsafePerformIO $ (cast3 ATen.rsub_tts) _self _other _alpha heaviside :: Tensor -- ^ self -> Tensor -- ^ values -> Tensor heaviside _self _values = unsafePerformIO $ (cast2 ATen.heaviside_tt) _self _values rsubScalar :: Tensor -- ^ self -> Float -- ^ other -> Float -- ^ alpha -> Tensor rsubScalar _self _other _alpha = unsafePerformIO $ (cast3 ATen.rsub_tss) _self _other _alpha sparse_sampled_addmm :: Tensor -- ^ self -> Tensor -- ^ mat1 -> Tensor -- ^ mat2 -> Float -- ^ beta -> Float -- ^ alpha -> Tensor sparse_sampled_addmm _self _mat1 _mat2 _beta _alpha = unsafePerformIO $ (cast5 ATen.sparse_sampled_addmm_tttss) _self _mat1 _mat2 _beta _alpha addmm :: Tensor -- ^ self -> Tensor -- ^ mat1 -> Tensor -- ^ mat2 -> Float -- ^ beta -> Float -- ^ alpha -> Tensor addmm _self _mat1 _mat2 _beta _alpha = unsafePerformIO $ (cast5 ATen.addmm_tttss) _self _mat1 _mat2 _beta _alpha hspmm :: Tensor -- ^ mat1 -> Tensor -- ^ mat2 -> Tensor hspmm _mat1 _mat2 = unsafePerformIO $ (cast2 ATen.hspmm_tt) _mat1 _mat2 unbind :: Tensor -- ^ self -> Int -- ^ dim -> [Tensor] unbind _self _dim = unsafePerformIO $ (cast2 ATen.unbind_tl) _self _dim unbindWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> [Tensor] unbindWithDimname _self _dim = unsafePerformIO $ (cast2 ATen.unbind_tn) _self _dim mkldnn_reorder_conv2d_weight :: Tensor -- ^ self -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ dilation -> Int -- ^ groups -> [Int] -- ^ input_size -> Tensor mkldnn_reorder_conv2d_weight _self _padding _stride _dilation _groups _input_size = unsafePerformIO $ (cast6 ATen.mkldnn_reorder_conv2d_weight_tlllll) _self _padding _stride _dilation _groups _input_size mkldnn_reorder_conv3d_weight :: Tensor -- ^ self -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ dilation -> Int -- ^ groups -> Tensor mkldnn_reorder_conv3d_weight _self _padding _stride _dilation _groups = unsafePerformIO $ (cast5 ATen.mkldnn_reorder_conv3d_weight_tllll) _self _padding _stride _dilation _groups quantize_per_tensor_dynamic :: Tensor -- ^ self -> DType -- ^ dtype -> Bool -- ^ reduce_range -> Tensor quantize_per_tensor_dynamic _self _dtype _reduce_range = unsafePerformIO $ (cast3 ATen.quantize_per_tensor_dynamic_tsb) _self _dtype _reduce_range quantize_per_tensor_tdls :: Tensor -- ^ self -> Double -- ^ scale -> Int -- ^ zero_point -> DType -- ^ dtype -> Tensor quantize_per_tensor_tdls _self _scale _zero_point _dtype = unsafePerformIO $ (cast4 ATen.quantize_per_tensor_tdls) _self _scale _zero_point _dtype quantize_per_tensor_ttts :: Tensor -- ^ self -> Tensor -- ^ scale -> Tensor -- ^ zero_point -> DType -- ^ dtype -> Tensor quantize_per_tensor_ttts _self _scale _zero_point _dtype = unsafePerformIO $ (cast4 ATen.quantize_per_tensor_ttts) _self _scale _zero_point _dtype quantize_per_tensor_ltts :: [Tensor] -- ^ tensors -> Tensor -- ^ scales -> Tensor -- ^ zero_points -> DType -- ^ dtype -> [Tensor] quantize_per_tensor_ltts _tensors _scales _zero_points _dtype = unsafePerformIO $ (cast4 ATen.quantize_per_tensor_ltts) _tensors _scales _zero_points _dtype quantize_per_channel :: Tensor -- ^ self -> Tensor -- ^ scales -> Tensor -- ^ zero_points -> Int -- ^ axis -> DType -- ^ dtype -> Tensor quantize_per_channel _self _scales _zero_points _axis _dtype = unsafePerformIO $ (cast5 ATen.quantize_per_channel_tttls) _self _scales _zero_points _axis _dtype dequantize_t :: Tensor -- ^ self -> Tensor dequantize_t _self = unsafePerformIO $ (cast1 ATen.dequantize_t) _self dequantize_l :: [Tensor] -- ^ tensors -> [Tensor] dequantize_l _tensors = unsafePerformIO $ (cast1 ATen.dequantize_l) _tensors q_scale :: Tensor -- ^ self -> Double q_scale _self = unsafePerformIO $ (cast1 ATen.q_scale_t) _self q_zero_point :: Tensor -- ^ self -> Int q_zero_point _self = unsafePerformIO $ (cast1 ATen.q_zero_point_t) _self q_per_channel_scales :: Tensor -- ^ self -> Tensor q_per_channel_scales _self = unsafePerformIO $ (cast1 ATen.q_per_channel_scales_t) _self q_per_channel_zero_points :: Tensor -- ^ self -> Tensor q_per_channel_zero_points _self = unsafePerformIO $ (cast1 ATen.q_per_channel_zero_points_t) _self q_per_channel_axis :: Tensor -- ^ self -> Int q_per_channel_axis _self = unsafePerformIO $ (cast1 ATen.q_per_channel_axis_t) _self int_repr :: Tensor -- ^ self -> Tensor int_repr _self = unsafePerformIO $ (cast1 ATen.int_repr_t) _self fake_quantize_per_tensor_affine_tdlll :: Tensor -- ^ self -> Double -- ^ scale -> Int -- ^ zero_point -> Int -- ^ quant_min -> Int -- ^ quant_max -> Tensor fake_quantize_per_tensor_affine_tdlll _self _scale _zero_point _quant_min _quant_max = unsafePerformIO $ (cast5 ATen.fake_quantize_per_tensor_affine_tdlll) _self _scale _zero_point _quant_min _quant_max fake_quantize_per_tensor_affine_tttll :: Tensor -- ^ self -> Tensor -- ^ scale -> Tensor -- ^ zero_point -> Int -- ^ quant_min -> Int -- ^ quant_max -> Tensor fake_quantize_per_tensor_affine_tttll _self _scale _zero_point _quant_min _quant_max = unsafePerformIO $ (cast5 ATen.fake_quantize_per_tensor_affine_tttll) _self _scale _zero_point _quant_min _quant_max fake_quantize_per_tensor_affine_cachemask :: Tensor -- ^ self -> Double -- ^ scale -> Int -- ^ zero_point -> Int -- ^ quant_min -> Int -- ^ quant_max -> (Tensor,Tensor) fake_quantize_per_tensor_affine_cachemask _self _scale _zero_point _quant_min _quant_max = unsafePerformIO $ (cast5 ATen.fake_quantize_per_tensor_affine_cachemask_tdlll) _self _scale _zero_point _quant_min _quant_max fake_quantize_per_channel_affine :: Tensor -- ^ self -> Tensor -- ^ scale -> Tensor -- ^ zero_point -> Int -- ^ axis -> Int -- ^ quant_min -> Int -- ^ quant_max -> Tensor fake_quantize_per_channel_affine _self _scale _zero_point _axis _quant_min _quant_max = unsafePerformIO $ (cast6 ATen.fake_quantize_per_channel_affine_tttlll) _self _scale _zero_point _axis _quant_min _quant_max fake_quantize_per_channel_affine_cachemask :: Tensor -- ^ self -> Tensor -- ^ scale -> Tensor -- ^ zero_point -> Int -- ^ axis -> Int -- ^ quant_min -> Int -- ^ quant_max -> (Tensor,Tensor) fake_quantize_per_channel_affine_cachemask _self _scale _zero_point _axis _quant_min _quant_max = unsafePerformIO $ (cast6 ATen.fake_quantize_per_channel_affine_cachemask_tttlll) _self _scale _zero_point _axis _quant_min _quant_max fused_moving_avg_obs_fake_quant :: Tensor -- ^ self -> Tensor -- ^ observer_on -> Tensor -- ^ fake_quant_on -> Tensor -- ^ running_min -> Tensor -- ^ running_max -> Tensor -- ^ scale -> Tensor -- ^ zero_point -> Double -- ^ averaging_const -> Int -- ^ quant_min -> Int -- ^ quant_max -> Int -- ^ ch_axis -> Bool -- ^ per_row_fake_quant -> Bool -- ^ symmetric_quant -> Tensor fused_moving_avg_obs_fake_quant _self _observer_on _fake_quant_on _running_min _running_max _scale _zero_point _averaging_const _quant_min _quant_max _ch_axis _per_row_fake_quant _symmetric_quant = unsafePerformIO $ (cast13 ATen.fused_moving_avg_obs_fake_quant_tttttttdlllbb) _self _observer_on _fake_quant_on _running_min _running_max _scale _zero_point _averaging_const _quant_min _quant_max _ch_axis _per_row_fake_quant _symmetric_quant choose_qparams_optimized :: Tensor -- ^ input -> Int -- ^ numel -> Int -- ^ n_bins -> Double -- ^ ratio -> Int -- ^ bit_width -> (Tensor,Tensor) choose_qparams_optimized _input _numel _n_bins _ratio _bit_width = unsafePerformIO $ (cast5 ATen.choose_qparams_optimized_tlldl) _input _numel _n_bins _ratio _bit_width meshgrid_l :: [Tensor] -- ^ tensors -> [Tensor] meshgrid_l _tensors = unsafePerformIO $ (cast1 ATen.meshgrid_l) _tensors meshgrid_ls :: [Tensor] -- ^ tensors -> String -- ^ indexing -> [Tensor] meshgrid_ls _tensors _indexing = unsafePerformIO $ (cast2 ATen.meshgrid_ls) _tensors _indexing cartesian_prod :: [Tensor] -- ^ tensors -> Tensor cartesian_prod _tensors = unsafePerformIO $ (cast1 ATen.cartesian_prod_l) _tensors combinations :: Tensor -- ^ self -> Int -- ^ r -> Bool -- ^ with_replacement -> Tensor combinations _self _r _with_replacement = unsafePerformIO $ (cast3 ATen.combinations_tlb) _self _r _with_replacement resultType :: Tensor -- ^ tensor -> Tensor -- ^ other -> DType resultType _tensor _other = unsafePerformIO $ (cast2 ATen.result_type_tt) _tensor _other resultTypeScalar :: Tensor -- ^ tensor -> Float -- ^ other -> DType resultTypeScalar _tensor _other = unsafePerformIO $ (cast2 ATen.result_type_ts) _tensor _other resultTypeScalar' :: Float -- ^ scalar -> Tensor -- ^ tensor -> DType resultTypeScalar' _scalar _tensor = unsafePerformIO $ (cast2 ATen.result_type_st) _scalar _tensor resultTypeScalars :: Float -- ^ scalar1 -> Float -- ^ scalar2 -> DType resultTypeScalars _scalar1 _scalar2 = unsafePerformIO $ (cast2 ATen.result_type_ss) _scalar1 _scalar2 can_cast :: DType -- ^ from -> DType -- ^ to -> Bool can_cast _from _to = unsafePerformIO $ (cast2 ATen.can_cast_ss) _from _to promote_types :: DType -- ^ type1 -> DType -- ^ type2 -> DType promote_types _type1 _type2 = unsafePerformIO $ (cast2 ATen.promote_types_ss) _type1 _type2 lstm :: Tensor -- ^ input -> [Tensor] -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> Bool -- ^ batch_first -> (Tensor,Tensor,Tensor) lstm _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first = unsafePerformIO $ (cast9 ATen.lstm_tllbldbbb) _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first lstm' :: Tensor -- ^ data -> Tensor -- ^ batch_sizes -> [Tensor] -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> (Tensor,Tensor,Tensor) lstm' _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional = unsafePerformIO $ (cast9 ATen.lstm_ttllbldbb) _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional gru :: Tensor -- ^ input -> Tensor -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> Bool -- ^ batch_first -> (Tensor,Tensor) gru _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first = unsafePerformIO $ (cast9 ATen.gru_ttlbldbbb) _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first gru' :: Tensor -- ^ data -> Tensor -- ^ batch_sizes -> Tensor -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> (Tensor,Tensor) gru' _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional = unsafePerformIO $ (cast9 ATen.gru_tttlbldbb) _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional rnnTanh :: Tensor -- ^ input -> Tensor -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> Bool -- ^ batch_first -> (Tensor,Tensor) rnnTanh _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first = unsafePerformIO $ (cast9 ATen.rnn_tanh_ttlbldbbb) _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first rnnTanh' :: Tensor -- ^ data -> Tensor -- ^ batch_sizes -> Tensor -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> (Tensor,Tensor) rnnTanh' _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional = unsafePerformIO $ (cast9 ATen.rnn_tanh_tttlbldbb) _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional rnnRelu :: Tensor -- ^ input -> Tensor -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> Bool -- ^ batch_first -> (Tensor,Tensor) rnnRelu _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first = unsafePerformIO $ (cast9 ATen.rnn_relu_ttlbldbbb) _input _hx _params _has_biases _num_layers _dropout _train _bidirectional _batch_first rnnRelu' :: Tensor -- ^ data -> Tensor -- ^ batch_sizes -> Tensor -- ^ hx -> [Tensor] -- ^ params -> Bool -- ^ has_biases -> Int -- ^ num_layers -> Double -- ^ dropout -> Bool -- ^ train -> Bool -- ^ bidirectional -> (Tensor,Tensor) rnnRelu' _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional = unsafePerformIO $ (cast9 ATen.rnn_relu_tttlbldbb) _data _batch_sizes _hx _params _has_biases _num_layers _dropout _train _bidirectional lstm_cell :: Tensor -- ^ input -> [Tensor] -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> (Tensor,Tensor) lstm_cell _input _hx _w_ih _w_hh _b_ih _b_hh = unsafePerformIO $ (cast6 ATen.lstm_cell_tltttt) _input _hx _w_ih _w_hh _b_ih _b_hh gru_cell :: Tensor -- ^ input -> Tensor -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor gru_cell _input _hx _w_ih _w_hh _b_ih _b_hh = unsafePerformIO $ (cast6 ATen.gru_cell_tttttt) _input _hx _w_ih _w_hh _b_ih _b_hh rnn_tanh_cell :: Tensor -- ^ input -> Tensor -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor rnn_tanh_cell _input _hx _w_ih _w_hh _b_ih _b_hh = unsafePerformIO $ (cast6 ATen.rnn_tanh_cell_tttttt) _input _hx _w_ih _w_hh _b_ih _b_hh rnn_relu_cell :: Tensor -- ^ input -> Tensor -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor rnn_relu_cell _input _hx _w_ih _w_hh _b_ih _b_hh = unsafePerformIO $ (cast6 ATen.rnn_relu_cell_tttttt) _input _hx _w_ih _w_hh _b_ih _b_hh quantized_lstm_cell :: Tensor -- ^ input -> [Tensor] -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor -- ^ packed_ih -> Tensor -- ^ packed_hh -> Tensor -- ^ col_offsets_ih -> Tensor -- ^ col_offsets_hh -> Float -- ^ scale_ih -> Float -- ^ scale_hh -> Float -- ^ zero_point_ih -> Float -- ^ zero_point_hh -> (Tensor,Tensor) quantized_lstm_cell _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh = unsafePerformIO $ (cast14 ATen.quantized_lstm_cell_tlttttttttssss) _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh quantized_gru_cell :: Tensor -- ^ input -> Tensor -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor -- ^ packed_ih -> Tensor -- ^ packed_hh -> Tensor -- ^ col_offsets_ih -> Tensor -- ^ col_offsets_hh -> Float -- ^ scale_ih -> Float -- ^ scale_hh -> Float -- ^ zero_point_ih -> Float -- ^ zero_point_hh -> Tensor quantized_gru_cell _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh = unsafePerformIO $ (cast14 ATen.quantized_gru_cell_ttttttttttssss) _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh quantized_rnn_relu_cell :: Tensor -- ^ input -> Tensor -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor -- ^ packed_ih -> Tensor -- ^ packed_hh -> Tensor -- ^ col_offsets_ih -> Tensor -- ^ col_offsets_hh -> Float -- ^ scale_ih -> Float -- ^ scale_hh -> Float -- ^ zero_point_ih -> Float -- ^ zero_point_hh -> Tensor quantized_rnn_relu_cell _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh = unsafePerformIO $ (cast14 ATen.quantized_rnn_relu_cell_ttttttttttssss) _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh quantized_rnn_tanh_cell :: Tensor -- ^ input -> Tensor -- ^ hx -> Tensor -- ^ w_ih -> Tensor -- ^ w_hh -> Tensor -- ^ b_ih -> Tensor -- ^ b_hh -> Tensor -- ^ packed_ih -> Tensor -- ^ packed_hh -> Tensor -- ^ col_offsets_ih -> Tensor -- ^ col_offsets_hh -> Float -- ^ scale_ih -> Float -- ^ scale_hh -> Float -- ^ zero_point_ih -> Float -- ^ zero_point_hh -> Tensor quantized_rnn_tanh_cell _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh = unsafePerformIO $ (cast14 ATen.quantized_rnn_tanh_cell_ttttttttttssss) _input _hx _w_ih _w_hh _b_ih _b_hh _packed_ih _packed_hh _col_offsets_ih _col_offsets_hh _scale_ih _scale_hh _zero_point_ih _zero_point_hh lift :: Tensor -- ^ self -> Tensor lift _self = unsafePerformIO $ (cast1 ATen.lift_t) _self lift_fresh :: Tensor -- ^ self -> Tensor lift_fresh _self = unsafePerformIO $ (cast1 ATen.lift_fresh_t) _self lift_fresh_copy :: Tensor -- ^ self -> Tensor lift_fresh_copy _self = unsafePerformIO $ (cast1 ATen.lift_fresh_copy_t) _self maskedFillScalar :: Tensor -- ^ self -> Tensor -- ^ mask -> Float -- ^ value -> Tensor maskedFillScalar _self _mask _value = unsafePerformIO $ (cast3 ATen.masked_fill_tts) _self _mask _value maskedFill :: Tensor -- ^ self -> Tensor -- ^ mask -> Tensor -- ^ value -> Tensor maskedFill _self _mask _value = unsafePerformIO $ (cast3 ATen.masked_fill_ttt) _self _mask _value masked_scatter :: Tensor -- ^ self -> Tensor -- ^ mask -> Tensor -- ^ source -> Tensor masked_scatter _self _mask _source = unsafePerformIO $ (cast3 ATen.masked_scatter_ttt) _self _mask _source put :: Tensor -- ^ self -> Tensor -- ^ index -> Tensor -- ^ source -> Bool -- ^ accumulate -> Tensor put _self _index _source _accumulate = unsafePerformIO $ (cast4 ATen.put_tttb) _self _index _source _accumulate index_add_tltts :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ source -> Float -- ^ alpha -> Tensor index_add_tltts _self _dim _index _source _alpha = unsafePerformIO $ (cast5 ATen.index_add_tltts) _self _dim _index _source _alpha index_add_tntts :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ source -> Float -- ^ alpha -> Tensor index_add_tntts _self _dim _index _source _alpha = unsafePerformIO $ (cast5 ATen.index_add_tntts) _self _dim _index _source _alpha index_reduce :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ source -> String -- ^ reduce -> Bool -- ^ include_self -> Tensor index_reduce _self _dim _index _source _reduce _include_self = unsafePerformIO $ (cast6 ATen.index_reduce_tlttsb) _self _dim _index _source _reduce _include_self indexFillScalar :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Float -- ^ value -> Tensor indexFillScalar _self _dim _index _value = unsafePerformIO $ (cast4 ATen.index_fill_tlts) _self _dim _index _value indexFill :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ value -> Tensor indexFill _self _dim _index _value = unsafePerformIO $ (cast4 ATen.index_fill_tltt) _self _dim _index _value indexFillScalarWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Float -- ^ value -> Tensor indexFillScalarWithDimname _self _dim _index _value = unsafePerformIO $ (cast4 ATen.index_fill_tnts) _self _dim _index _value indexFillWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ value -> Tensor indexFillWithDimname _self _dim _index _value = unsafePerformIO $ (cast4 ATen.index_fill_tntt) _self _dim _index _value scatter :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ src -> Tensor scatter _self _dim _index _src = unsafePerformIO $ (cast4 ATen.scatter_tltt) _self _dim _index _src scatterScalar :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Float -- ^ value -> Tensor scatterScalar _self _dim _index _value = unsafePerformIO $ (cast4 ATen.scatter_tlts) _self _dim _index _value scatter_tltts :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ src -> String -- ^ reduce -> Tensor scatter_tltts _self _dim _index _src _reduce = unsafePerformIO $ (cast5 ATen.scatter_tltts) _self _dim _index _src _reduce scatter_tltss :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Float -- ^ value -> String -- ^ reduce -> Tensor scatter_tltss _self _dim _index _value _reduce = unsafePerformIO $ (cast5 ATen.scatter_tltss) _self _dim _index _value _reduce scatterWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ src -> Tensor scatterWithDimname _self _dim _index _src = unsafePerformIO $ (cast4 ATen.scatter_tntt) _self _dim _index _src scatterScalarWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Float -- ^ value -> Tensor scatterScalarWithDimname _self _dim _index _value = unsafePerformIO $ (cast4 ATen.scatter_tnts) _self _dim _index _value scatterAdd :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ src -> Tensor scatterAdd _self _dim _index _src = unsafePerformIO $ (cast4 ATen.scatter_add_tltt) _self _dim _index _src scatterAddWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ src -> Tensor scatterAddWithDimname _self _dim _index _src = unsafePerformIO $ (cast4 ATen.scatter_add_tntt) _self _dim _index _src scatter_reduce :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor -- ^ src -> String -- ^ reduce -> Bool -- ^ include_self -> Tensor scatter_reduce _self _dim _index _src _reduce _include_self = unsafePerformIO $ (cast6 ATen.scatter_reduce_tlttsb) _self _dim _index _src _reduce _include_self bitwise_and_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor bitwise_and_ts _self _other = unsafePerformIO $ (cast2 ATen.bitwise_and_ts) _self _other bitwise_and_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor bitwise_and_st _self _other = unsafePerformIO $ (cast2 ATen.bitwise_and_st) _self _other bitwise_and_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor bitwise_and_tt _self _other = unsafePerformIO $ (cast2 ATen.bitwise_and_tt) _self _other bitwise_or_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor bitwise_or_ts _self _other = unsafePerformIO $ (cast2 ATen.bitwise_or_ts) _self _other bitwise_or_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor bitwise_or_st _self _other = unsafePerformIO $ (cast2 ATen.bitwise_or_st) _self _other bitwise_or_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor bitwise_or_tt _self _other = unsafePerformIO $ (cast2 ATen.bitwise_or_tt) _self _other bitwiseXorScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor bitwiseXorScalar _self _other = unsafePerformIO $ (cast2 ATen.bitwise_xor_ts) _self _other bitwise_xor_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor bitwise_xor_st _self _other = unsafePerformIO $ (cast2 ATen.bitwise_xor_st) _self _other bitwiseXor :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor bitwiseXor _self _other = unsafePerformIO $ (cast2 ATen.bitwise_xor_tt) _self _other bitwise_left_shift_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor bitwise_left_shift_tt _self _other = unsafePerformIO $ (cast2 ATen.bitwise_left_shift_tt) _self _other bitwise_left_shift_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor bitwise_left_shift_ts _self _other = unsafePerformIO $ (cast2 ATen.bitwise_left_shift_ts) _self _other bitwise_left_shift_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor bitwise_left_shift_st _self _other = unsafePerformIO $ (cast2 ATen.bitwise_left_shift_st) _self _other bitwise_right_shift_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor bitwise_right_shift_tt _self _other = unsafePerformIO $ (cast2 ATen.bitwise_right_shift_tt) _self _other bitwise_right_shift_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor bitwise_right_shift_ts _self _other = unsafePerformIO $ (cast2 ATen.bitwise_right_shift_ts) _self _other bitwise_right_shift_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor bitwise_right_shift_st _self _other = unsafePerformIO $ (cast2 ATen.bitwise_right_shift_st) _self _other addbmm :: Tensor -- ^ self -> Tensor -- ^ batch1 -> Tensor -- ^ batch2 -> Float -- ^ beta -> Float -- ^ alpha -> Tensor addbmm _self _batch1 _batch2 _beta _alpha = unsafePerformIO $ (cast5 ATen.addbmm_tttss) _self _batch1 _batch2 _beta _alpha diag :: Tensor -- ^ self -> Int -- ^ diagonal -> Tensor diag _self _diagonal = unsafePerformIO $ (cast2 ATen.diag_tl) _self _diagonal cross :: Tensor -- ^ self -> Tensor -- ^ other -> Int -- ^ dim -> Tensor cross _self _other _dim = unsafePerformIO $ (cast3 ATen.cross_ttl) _self _other _dim triu :: Tensor -- ^ self -> Int -- ^ diagonal -> Tensor triu _self _diagonal = unsafePerformIO $ (cast2 ATen.triu_tl) _self _diagonal tril :: Tensor -- ^ self -> Int -- ^ diagonal -> Tensor tril _self _diagonal = unsafePerformIO $ (cast2 ATen.tril_tl) _self _diagonal trace :: Tensor -- ^ self -> Tensor trace _self = unsafePerformIO $ (cast1 ATen.trace_t) _self neScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor neScalar _self _other = unsafePerformIO $ (cast2 ATen.ne_ts) _self _other ne :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor ne _self _other = unsafePerformIO $ (cast2 ATen.ne_tt) _self _other not_equal_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor not_equal_ts _self _other = unsafePerformIO $ (cast2 ATen.not_equal_ts) _self _other not_equal_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor not_equal_tt _self _other = unsafePerformIO $ (cast2 ATen.not_equal_tt) _self _other eqScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor eqScalar _self _other = unsafePerformIO $ (cast2 ATen.eq_ts) _self _other eq :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor eq _self _other = unsafePerformIO $ (cast2 ATen.eq_tt) _self _other geScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor geScalar _self _other = unsafePerformIO $ (cast2 ATen.ge_ts) _self _other ge :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor ge _self _other = unsafePerformIO $ (cast2 ATen.ge_tt) _self _other greater_equal_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor greater_equal_ts _self _other = unsafePerformIO $ (cast2 ATen.greater_equal_ts) _self _other greater_equal_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor greater_equal_tt _self _other = unsafePerformIO $ (cast2 ATen.greater_equal_tt) _self _other leScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor leScalar _self _other = unsafePerformIO $ (cast2 ATen.le_ts) _self _other le :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor le _self _other = unsafePerformIO $ (cast2 ATen.le_tt) _self _other less_equal_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor less_equal_ts _self _other = unsafePerformIO $ (cast2 ATen.less_equal_ts) _self _other less_equal_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor less_equal_tt _self _other = unsafePerformIO $ (cast2 ATen.less_equal_tt) _self _other gtScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor gtScalar _self _other = unsafePerformIO $ (cast2 ATen.gt_ts) _self _other gt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor gt _self _other = unsafePerformIO $ (cast2 ATen.gt_tt) _self _other greater_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor greater_ts _self _other = unsafePerformIO $ (cast2 ATen.greater_ts) _self _other greater_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor greater_tt _self _other = unsafePerformIO $ (cast2 ATen.greater_tt) _self _other ltScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor ltScalar _self _other = unsafePerformIO $ (cast2 ATen.lt_ts) _self _other lt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor lt _self _other = unsafePerformIO $ (cast2 ATen.lt_tt) _self _other less_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor less_ts _self _other = unsafePerformIO $ (cast2 ATen.less_ts) _self _other less_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor less_tt _self _other = unsafePerformIO $ (cast2 ATen.less_tt) _self _other take :: Tensor -- ^ self -> Tensor -- ^ index -> Tensor take _self _index = unsafePerformIO $ (cast2 ATen.take_tt) _self _index take_along_dim :: Tensor -- ^ self -> Tensor -- ^ indices -> Int -- ^ dim -> Tensor take_along_dim _self _indices _dim = unsafePerformIO $ (cast3 ATen.take_along_dim_ttl) _self _indices _dim indexSelect :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Tensor indexSelect _self _dim _index = unsafePerformIO $ (cast3 ATen.index_select_tlt) _self _dim _index indexSelectWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Tensor indexSelectWithDimname _self _dim _index = unsafePerformIO $ (cast3 ATen.index_select_tnt) _self _dim _index masked_select :: Tensor -- ^ self -> Tensor -- ^ mask -> Tensor masked_select _self _mask = unsafePerformIO $ (cast2 ATen.masked_select_tt) _self _mask nonzero :: Tensor -- ^ self -> Tensor nonzero _self = unsafePerformIO $ (cast1 ATen.nonzero_t) _self nonzero_numpy :: Tensor -- ^ self -> [Tensor] nonzero_numpy _self = unsafePerformIO $ (cast1 ATen.nonzero_numpy_t) _self argwhere :: Tensor -- ^ self -> Tensor argwhere _self = unsafePerformIO $ (cast1 ATen.argwhere_t) _self gather :: Tensor -- ^ self -> Int -- ^ dim -> Tensor -- ^ index -> Bool -- ^ sparse_grad -> Tensor gather _self _dim _index _sparse_grad = unsafePerformIO $ (cast4 ATen.gather_tltb) _self _dim _index _sparse_grad gatherWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Tensor -- ^ index -> Bool -- ^ sparse_grad -> Tensor gatherWithDimname _self _dim _index _sparse_grad = unsafePerformIO $ (cast4 ATen.gather_tntb) _self _dim _index _sparse_grad addcmul :: Tensor -- ^ self -> Tensor -- ^ tensor1 -> Tensor -- ^ tensor2 -> Float -- ^ value -> Tensor addcmul _self _tensor1 _tensor2 _value = unsafePerformIO $ (cast4 ATen.addcmul_ttts) _self _tensor1 _tensor2 _value addcdiv :: Tensor -- ^ self -> Tensor -- ^ tensor1 -> Tensor -- ^ tensor2 -> Float -- ^ value -> Tensor addcdiv _self _tensor1 _tensor2 _value = unsafePerformIO $ (cast4 ATen.addcdiv_ttts) _self _tensor1 _tensor2 _value cross_entropy_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Int -- ^ ignore_index -> Double -- ^ label_smoothing -> Tensor cross_entropy_loss _self _target _weight _reduction _ignore_index _label_smoothing = unsafePerformIO $ (cast6 ATen.cross_entropy_loss_tttlld) _self _target _weight _reduction _ignore_index _label_smoothing triangular_solve :: Tensor -- ^ self -> Tensor -- ^ A -> Bool -- ^ upper -> Bool -- ^ transpose -> Bool -- ^ unitriangular -> (Tensor,Tensor) triangular_solve _self _A _upper _transpose _unitriangular = unsafePerformIO $ (cast5 ATen.triangular_solve_ttbbb) _self _A _upper _transpose _unitriangular linalg_solve_triangular :: Tensor -- ^ self -> Tensor -- ^ B -> Bool -- ^ upper -> Bool -- ^ left -> Bool -- ^ unitriangular -> Tensor linalg_solve_triangular _self _B _upper _left _unitriangular = unsafePerformIO $ (cast5 ATen.linalg_solve_triangular_ttbbb) _self _B _upper _left _unitriangular linalg_vander :: Tensor -- ^ x -> Int -- ^ N -> Tensor linalg_vander _x _N = unsafePerformIO $ (cast2 ATen.linalg_vander_tl) _x _N svd :: Tensor -- ^ self -> Bool -- ^ some -> Bool -- ^ compute_uv -> (Tensor,Tensor,Tensor) svd _self _some _compute_uv = unsafePerformIO $ (cast3 ATen.svd_tbb) _self _some _compute_uv swapaxes :: Tensor -- ^ self -> Int -- ^ axis0 -> Int -- ^ axis1 -> Tensor swapaxes _self _axis0 _axis1 = unsafePerformIO $ (cast3 ATen.swapaxes_tll) _self _axis0 _axis1 swapdims :: Tensor -- ^ self -> Int -- ^ dim0 -> Int -- ^ dim1 -> Tensor swapdims _self _dim0 _dim1 = unsafePerformIO $ (cast3 ATen.swapdims_tll) _self _dim0 _dim1 cholesky :: Tensor -- ^ self -> Bool -- ^ upper -> Tensor cholesky _self _upper = unsafePerformIO $ (cast2 ATen.cholesky_tb) _self _upper cholesky_solve :: Tensor -- ^ self -> Tensor -- ^ input2 -> Bool -- ^ upper -> Tensor cholesky_solve _self _input2 _upper = unsafePerformIO $ (cast3 ATen.cholesky_solve_ttb) _self _input2 _upper cholesky_inverse :: Tensor -- ^ self -> Bool -- ^ upper -> Tensor cholesky_inverse _self _upper = unsafePerformIO $ (cast2 ATen.cholesky_inverse_tb) _self _upper qr :: Tensor -- ^ self -> Bool -- ^ some -> (Tensor,Tensor) qr _self _some = unsafePerformIO $ (cast2 ATen.qr_tb) _self _some geqrf :: Tensor -- ^ self -> (Tensor,Tensor) geqrf _self = unsafePerformIO $ (cast1 ATen.geqrf_t) _self orgqr :: Tensor -- ^ self -> Tensor -- ^ input2 -> Tensor orgqr _self _input2 = unsafePerformIO $ (cast2 ATen.orgqr_tt) _self _input2 ormqr :: Tensor -- ^ self -> Tensor -- ^ input2 -> Tensor -- ^ input3 -> Bool -- ^ left -> Bool -- ^ transpose -> Tensor ormqr _self _input2 _input3 _left _transpose = unsafePerformIO $ (cast5 ATen.ormqr_tttbb) _self _input2 _input3 _left _transpose lu_solve :: Tensor -- ^ self -> Tensor -- ^ LU_data -> Tensor -- ^ LU_pivots -> Tensor lu_solve _self _LU_data _LU_pivots = unsafePerformIO $ (cast3 ATen.lu_solve_ttt) _self _LU_data _LU_pivots lu_unpack :: Tensor -- ^ LU_data -> Tensor -- ^ LU_pivots -> Bool -- ^ unpack_data -> Bool -- ^ unpack_pivots -> (Tensor,Tensor,Tensor) lu_unpack _LU_data _LU_pivots _unpack_data _unpack_pivots = unsafePerformIO $ (cast4 ATen.lu_unpack_ttbb) _LU_data _LU_pivots _unpack_data _unpack_pivots lgamma :: Tensor -- ^ self -> Tensor lgamma _self = unsafePerformIO $ (cast1 ATen.lgamma_t) _self digamma :: Tensor -- ^ self -> Tensor digamma _self = unsafePerformIO $ (cast1 ATen.digamma_t) _self polygamma :: Int -- ^ n -> Tensor -- ^ self -> Tensor polygamma _n _self = unsafePerformIO $ (cast2 ATen.polygamma_lt) _n _self erfinv :: Tensor -- ^ self -> Tensor erfinv _self = unsafePerformIO $ (cast1 ATen.erfinv_t) _self i0 :: Tensor -- ^ self -> Tensor i0 _self = unsafePerformIO $ (cast1 ATen.i0_t) _self sign :: Tensor -- ^ self -> Tensor sign _self = unsafePerformIO $ (cast1 ATen.sign_t) _self signbit :: Tensor -- ^ self -> Tensor signbit _self = unsafePerformIO $ (cast1 ATen.signbit_t) _self dist :: Tensor -- ^ self -> Tensor -- ^ other -> Float -- ^ p -> Tensor dist _self _other _p = unsafePerformIO $ (cast3 ATen.dist_tts) _self _other _p atan2 :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor atan2 _self _other = unsafePerformIO $ (cast2 ATen.atan2_tt) _self _other arctan2 :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor arctan2 _self _other = unsafePerformIO $ (cast2 ATen.arctan2_tt) _self _other lerpScalar :: Tensor -- ^ self -> Tensor -- ^ end -> Float -- ^ weight -> Tensor lerpScalar _self _end _weight = unsafePerformIO $ (cast3 ATen.lerp_tts) _self _end _weight lerp :: Tensor -- ^ self -> Tensor -- ^ end -> Tensor -- ^ weight -> Tensor lerp _self _end _weight = unsafePerformIO $ (cast3 ATen.lerp_ttt) _self _end _weight histc :: Tensor -- ^ self -> Int -- ^ bins -> Float -- ^ min -> Float -- ^ max -> Tensor histc _self _bins _min _max = unsafePerformIO $ (cast4 ATen.histc_tlss) _self _bins _min _max histogram_tttb :: Tensor -- ^ self -> Tensor -- ^ bins -> Tensor -- ^ weight -> Bool -- ^ density -> (Tensor,Tensor) histogram_tttb _self _bins _weight _density = unsafePerformIO $ (cast4 ATen.histogram_tttb) _self _bins _weight _density histogram_tlatb :: Tensor -- ^ self -> Int -- ^ bins -> ([Double]) -- ^ range -> Tensor -- ^ weight -> Bool -- ^ density -> (Tensor,Tensor) histogram_tlatb _self _bins _range _weight _density = unsafePerformIO $ (cast5 ATen.histogram_tlatb) _self _bins _range _weight _density -- histogramdd_tlatb -- :: Tensor -- ^ self -- -> [Int] -- ^ bins -- -> ([Double]) -- ^ range -- -> Tensor -- ^ weight -- -> Bool -- ^ density -- -> (Tensor,[Tensor]) -- histogramdd_tlatb _self _bins _range _weight _density = unsafePerformIO $ (cast5 ATen.histogramdd_tlatb) _self _bins _range _weight _density histogramdd_tlatb :: Tensor -- ^ self -> Int -- ^ bins -> ([Double]) -- ^ range -> Tensor -- ^ weight -> Bool -- ^ density -> (Tensor,[Tensor]) histogramdd_tlatb _self _bins _range _weight _density = unsafePerformIO $ (cast5 ATen.histogramdd_tlatb) _self _bins _range _weight _density -- histogramdd_tlatb -- :: Tensor -- ^ self -- -> [Tensor] -- ^ bins -- -> ([Double]) -- ^ range -- -> Tensor -- ^ weight -- -> Bool -- ^ density -- -> (Tensor,[Tensor]) -- histogramdd_tlatb _self _bins _range _weight _density = unsafePerformIO $ (cast5 ATen.histogramdd_tlatb) _self _bins _range _weight _density fmodScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor fmodScalar _self _other = unsafePerformIO $ (cast2 ATen.fmod_ts) _self _other fmod :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor fmod _self _other = unsafePerformIO $ (cast2 ATen.fmod_tt) _self _other hypot :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor hypot _self _other = unsafePerformIO $ (cast2 ATen.hypot_tt) _self _other igamma :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor igamma _self _other = unsafePerformIO $ (cast2 ATen.igamma_tt) _self _other igammac :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor igammac _self _other = unsafePerformIO $ (cast2 ATen.igammac_tt) _self _other nextafter :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor nextafter _self _other = unsafePerformIO $ (cast2 ATen.nextafter_tt) _self _other remainderScalar :: Tensor -- ^ self -> Float -- ^ other -> Tensor remainderScalar _self _other = unsafePerformIO $ (cast2 ATen.remainder_ts) _self _other remainder :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor remainder _self _other = unsafePerformIO $ (cast2 ATen.remainder_tt) _self _other remainder_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor remainder_st _self _other = unsafePerformIO $ (cast2 ATen.remainder_st) _self _other minAll :: Tensor -- ^ self -> Tensor minAll _self = unsafePerformIO $ (cast1 ATen.min_t) _self fmin :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor fmin _self _other = unsafePerformIO $ (cast2 ATen.fmin_tt) _self _other maxAll :: Tensor -- ^ self -> Tensor maxAll _self = unsafePerformIO $ (cast1 ATen.max_t) _self fmax :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor fmax _self _other = unsafePerformIO $ (cast2 ATen.fmax_tt) _self _other maximum :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor maximum _self _other = unsafePerformIO $ (cast2 ATen.maximum_tt) _self _other max :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor max _self _other = unsafePerformIO $ (cast2 ATen.max_tt) _self _other minimum :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor minimum _self _other = unsafePerformIO $ (cast2 ATen.minimum_tt) _self _other min :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor min _self _other = unsafePerformIO $ (cast2 ATen.min_tt) _self _other quantile_ttlbs :: Tensor -- ^ self -> Tensor -- ^ q -> Int -- ^ dim -> Bool -- ^ keepdim -> String -- ^ interpolation -> Tensor quantile_ttlbs _self _q _dim _keepdim _interpolation = unsafePerformIO $ (cast5 ATen.quantile_ttlbs) _self _q _dim _keepdim _interpolation quantile_tdlbs :: Tensor -- ^ self -> Double -- ^ q -> Int -- ^ dim -> Bool -- ^ keepdim -> String -- ^ interpolation -> Tensor quantile_tdlbs _self _q _dim _keepdim _interpolation = unsafePerformIO $ (cast5 ATen.quantile_tdlbs) _self _q _dim _keepdim _interpolation nanquantile_ttlbs :: Tensor -- ^ self -> Tensor -- ^ q -> Int -- ^ dim -> Bool -- ^ keepdim -> String -- ^ interpolation -> Tensor nanquantile_ttlbs _self _q _dim _keepdim _interpolation = unsafePerformIO $ (cast5 ATen.nanquantile_ttlbs) _self _q _dim _keepdim _interpolation nanquantile_tdlbs :: Tensor -- ^ self -> Double -- ^ q -> Int -- ^ dim -> Bool -- ^ keepdim -> String -- ^ interpolation -> Tensor nanquantile_tdlbs _self _q _dim _keepdim _interpolation = unsafePerformIO $ (cast5 ATen.nanquantile_tdlbs) _self _q _dim _keepdim _interpolation sort :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ descending -> (Tensor,Tensor) sort _self _dim _descending = unsafePerformIO $ (cast3 ATen.sort_tlb) _self _dim _descending sort_tblb :: Tensor -- ^ self -> Bool -- ^ stable -> Int -- ^ dim -> Bool -- ^ descending -> (Tensor,Tensor) sort_tblb _self _stable _dim _descending = unsafePerformIO $ (cast4 ATen.sort_tblb) _self _stable _dim _descending sortWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ descending -> (Tensor,Tensor) sortWithDimname _self _dim _descending = unsafePerformIO $ (cast3 ATen.sort_tnb) _self _dim _descending sort_tbnb :: Tensor -- ^ self -> Bool -- ^ stable -> Dimname -- ^ dim -> Bool -- ^ descending -> (Tensor,Tensor) sort_tbnb _self _stable _dim _descending = unsafePerformIO $ (cast4 ATen.sort_tbnb) _self _stable _dim _descending msort :: Tensor -- ^ self -> Tensor msort _self = unsafePerformIO $ (cast1 ATen.msort_t) _self argsort :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ descending -> Tensor argsort _self _dim _descending = unsafePerformIO $ (cast3 ATen.argsort_tlb) _self _dim _descending argsort_tblb :: Tensor -- ^ self -> Bool -- ^ stable -> Int -- ^ dim -> Bool -- ^ descending -> Tensor argsort_tblb _self _stable _dim _descending = unsafePerformIO $ (cast4 ATen.argsort_tblb) _self _stable _dim _descending argsortWithDimname :: Tensor -- ^ self -> Dimname -- ^ dim -> Bool -- ^ descending -> Tensor argsortWithDimname _self _dim _descending = unsafePerformIO $ (cast3 ATen.argsort_tnb) _self _dim _descending topk :: Tensor -- ^ self -> Int -- ^ k -> Int -- ^ dim -> Bool -- ^ largest -> Bool -- ^ sorted -> (Tensor,Tensor) topk _self _k _dim _largest _sorted = unsafePerformIO $ (cast5 ATen.topk_tllbb) _self _k _dim _largest _sorted all :: Tensor -- ^ self -> Tensor all _self = unsafePerformIO $ (cast1 ATen.all_t) _self any :: Tensor -- ^ self -> Tensor any _self = unsafePerformIO $ (cast1 ATen.any_t) _self renorm :: Tensor -- ^ self -> Float -- ^ p -> Int -- ^ dim -> Float -- ^ maxnorm -> Tensor renorm _self _p _dim _maxnorm = unsafePerformIO $ (cast4 ATen.renorm_tsls) _self _p _dim _maxnorm equal :: Tensor -- ^ self -> Tensor -- ^ other -> Bool equal _self _other = unsafePerformIO $ (cast2 ATen.equal_tt) _self _other pow :: Tensor -- ^ self -> Tensor -- ^ exponent -> Tensor pow _self _exponent = unsafePerformIO $ (cast2 ATen.pow_tt) _self _exponent powScalar' :: Float -- ^ self -> Tensor -- ^ exponent -> Tensor powScalar' _self _exponent = unsafePerformIO $ (cast2 ATen.pow_st) _self _exponent powScalar :: Tensor -- ^ self -> Float -- ^ exponent -> Tensor powScalar _self _exponent = unsafePerformIO $ (cast2 ATen.pow_ts) _self _exponent float_power_tt :: Tensor -- ^ self -> Tensor -- ^ exponent -> Tensor float_power_tt _self _exponent = unsafePerformIO $ (cast2 ATen.float_power_tt) _self _exponent float_power_st :: Float -- ^ self -> Tensor -- ^ exponent -> Tensor float_power_st _self _exponent = unsafePerformIO $ (cast2 ATen.float_power_st) _self _exponent float_power_ts :: Tensor -- ^ self -> Float -- ^ exponent -> Tensor float_power_ts _self _exponent = unsafePerformIO $ (cast2 ATen.float_power_ts) _self _exponent alias :: Tensor -- ^ self -> Tensor alias _self = unsafePerformIO $ (cast1 ATen.alias_t) _self bucketize_ttbb :: Tensor -- ^ self -> Tensor -- ^ boundaries -> Bool -- ^ out_int32 -> Bool -- ^ right -> Tensor bucketize_ttbb _self _boundaries _out_int32 _right = unsafePerformIO $ (cast4 ATen.bucketize_ttbb) _self _boundaries _out_int32 _right bucketize_stbb :: Float -- ^ self -> Tensor -- ^ boundaries -> Bool -- ^ out_int32 -> Bool -- ^ right -> Tensor bucketize_stbb _self _boundaries _out_int32 _right = unsafePerformIO $ (cast4 ATen.bucketize_stbb) _self _boundaries _out_int32 _right searchsorted_ttbbst :: Tensor -- ^ sorted_sequence -> Tensor -- ^ self -> Bool -- ^ out_int32 -> Bool -- ^ right -> String -- ^ side -> Tensor -- ^ sorter -> Tensor searchsorted_ttbbst _sorted_sequence _self _out_int32 _right _side _sorter = unsafePerformIO $ (cast6 ATen.searchsorted_ttbbst) _sorted_sequence _self _out_int32 _right _side _sorter searchsorted_tsbbst :: Tensor -- ^ sorted_sequence -> Float -- ^ self -> Bool -- ^ out_int32 -> Bool -- ^ right -> String -- ^ side -> Tensor -- ^ sorter -> Tensor searchsorted_tsbbst _sorted_sequence _self _out_int32 _right _side _sorter = unsafePerformIO $ (cast6 ATen.searchsorted_tsbbst) _sorted_sequence _self _out_int32 _right _side _sorter mse_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Tensor mse_loss _self _target _reduction = unsafePerformIO $ (cast3 ATen.mse_loss_ttl) _self _target _reduction l1_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Tensor l1_loss _self _target _reduction = unsafePerformIO $ (cast3 ATen.l1_loss_ttl) _self _target _reduction multi_margin_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Float -- ^ p -> Float -- ^ margin -> Tensor -- ^ weight -> Int -- ^ reduction -> Tensor multi_margin_loss _self _target _p _margin _weight _reduction = unsafePerformIO $ (cast6 ATen.multi_margin_loss_ttsstl) _self _target _p _margin _weight _reduction multilabel_margin_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Tensor multilabel_margin_loss _self _target _reduction = unsafePerformIO $ (cast3 ATen.multilabel_margin_loss_ttl) _self _target _reduction multilabel_margin_loss_forward :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> (Tensor,Tensor) multilabel_margin_loss_forward _self _target _reduction = unsafePerformIO $ (cast3 ATen.multilabel_margin_loss_forward_ttl) _self _target _reduction nll_loss_nd :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Int -- ^ ignore_index -> Tensor nll_loss_nd _self _target _weight _reduction _ignore_index = unsafePerformIO $ (cast5 ATen.nll_loss_nd_tttll) _self _target _weight _reduction _ignore_index nll_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Int -- ^ ignore_index -> Tensor nll_loss _self _target _weight _reduction _ignore_index = unsafePerformIO $ (cast5 ATen.nll_loss_tttll) _self _target _weight _reduction _ignore_index nll_loss_forward :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Int -- ^ ignore_index -> (Tensor,Tensor) nll_loss_forward _self _target _weight _reduction _ignore_index = unsafePerformIO $ (cast5 ATen.nll_loss_forward_tttll) _self _target _weight _reduction _ignore_index nll_loss2d :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Int -- ^ ignore_index -> Tensor nll_loss2d _self _target _weight _reduction _ignore_index = unsafePerformIO $ (cast5 ATen.nll_loss2d_tttll) _self _target _weight _reduction _ignore_index nll_loss2d_forward :: Tensor -- ^ self -> Tensor -- ^ target -> Tensor -- ^ weight -> Int -- ^ reduction -> Int -- ^ ignore_index -> (Tensor,Tensor) nll_loss2d_forward _self _target _weight _reduction _ignore_index = unsafePerformIO $ (cast5 ATen.nll_loss2d_forward_tttll) _self _target _weight _reduction _ignore_index smooth_l1_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Double -- ^ beta -> Tensor smooth_l1_loss _self _target _reduction _beta = unsafePerformIO $ (cast4 ATen.smooth_l1_loss_ttld) _self _target _reduction _beta huber_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Double -- ^ delta -> Tensor huber_loss _self _target _reduction _delta = unsafePerformIO $ (cast4 ATen.huber_loss_ttld) _self _target _reduction _delta soft_margin_loss :: Tensor -- ^ self -> Tensor -- ^ target -> Int -- ^ reduction -> Tensor soft_margin_loss _self _target _reduction = unsafePerformIO $ (cast3 ATen.soft_margin_loss_ttl) _self _target _reduction elu :: Tensor -- ^ self -> Float -- ^ alpha -> Float -- ^ scale -> Float -- ^ input_scale -> Tensor elu _self _alpha _scale _input_scale = unsafePerformIO $ (cast4 ATen.elu_tsss) _self _alpha _scale _input_scale glu :: Tensor -- ^ self -> Int -- ^ dim -> Tensor glu _self _dim = unsafePerformIO $ (cast2 ATen.glu_tl) _self _dim glu_jvp :: Tensor -- ^ glu -> Tensor -- ^ x -> Tensor -- ^ dx -> Int -- ^ dim -> Tensor glu_jvp _glu _x _dx _dim = unsafePerformIO $ (cast4 ATen.glu_jvp_tttl) _glu _x _dx _dim glu_backward_jvp :: Tensor -- ^ grad_x -> Tensor -- ^ grad_glu -> Tensor -- ^ x -> Tensor -- ^ dgrad_glu -> Tensor -- ^ dx -> Int -- ^ dim -> Tensor glu_backward_jvp _grad_x _grad_glu _x _dgrad_glu _dx _dim = unsafePerformIO $ (cast6 ATen.glu_backward_jvp_tttttl) _grad_x _grad_glu _x _dgrad_glu _dx _dim hardsigmoid :: Tensor -- ^ self -> Tensor hardsigmoid _self = unsafePerformIO $ (cast1 ATen.hardsigmoid_t) _self hardtanh :: Tensor -- ^ self -> Float -- ^ min_val -> Float -- ^ max_val -> Tensor hardtanh _self _min_val _max_val = unsafePerformIO $ (cast3 ATen.hardtanh_tss) _self _min_val _max_val hardswish :: Tensor -- ^ self -> Tensor hardswish _self = unsafePerformIO $ (cast1 ATen.hardswish_t) _self leaky_relu :: Tensor -- ^ self -> Float -- ^ negative_slope -> Tensor leaky_relu _self _negative_slope = unsafePerformIO $ (cast2 ATen.leaky_relu_ts) _self _negative_slope log_sigmoid :: Tensor -- ^ self -> Tensor log_sigmoid _self = unsafePerformIO $ (cast1 ATen.log_sigmoid_t) _self log_sigmoid_forward :: Tensor -- ^ self -> (Tensor,Tensor) log_sigmoid_forward _self = unsafePerformIO $ (cast1 ATen.log_sigmoid_forward_t) _self softplus :: Tensor -- ^ self -> Float -- ^ beta -> Float -- ^ threshold -> Tensor softplus _self _beta _threshold = unsafePerformIO $ (cast3 ATen.softplus_tss) _self _beta _threshold softshrink :: Tensor -- ^ self -> Float -- ^ lambd -> Tensor softshrink _self _lambd = unsafePerformIO $ (cast2 ATen.softshrink_ts) _self _lambd adaptive_avg_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> Tensor adaptive_avg_pool2d _self _output_size = unsafePerformIO $ (cast2 ATen.adaptive_avg_pool2d_tl) _self _output_size mkldnn_adaptive_avg_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> Tensor mkldnn_adaptive_avg_pool2d _self _output_size = unsafePerformIO $ (cast2 ATen.mkldnn_adaptive_avg_pool2d_tl) _self _output_size adaptive_avg_pool3d :: Tensor -- ^ self -> (Int,Int,Int) -- ^ output_size -> Tensor adaptive_avg_pool3d _self _output_size = unsafePerformIO $ (cast2 ATen.adaptive_avg_pool3d_tl) _self _output_size adaptive_max_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> (Tensor,Tensor) adaptive_max_pool2d _self _output_size = unsafePerformIO $ (cast2 ATen.adaptive_max_pool2d_tl) _self _output_size adaptive_max_pool3d :: Tensor -- ^ self -> (Int,Int,Int) -- ^ output_size -> (Tensor,Tensor) adaptive_max_pool3d _self _output_size = unsafePerformIO $ (cast2 ATen.adaptive_max_pool3d_tl) _self _output_size avg_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> Bool -- ^ ceil_mode -> Bool -- ^ count_include_pad -> Int -- ^ divisor_override -> Tensor avg_pool2d _self _kernel_size _stride _padding _ceil_mode _count_include_pad _divisor_override = unsafePerformIO $ (cast7 ATen.avg_pool2d_tlllbbl) _self _kernel_size _stride _padding _ceil_mode _count_include_pad _divisor_override avg_pool3d :: Tensor -- ^ self -> (Int,Int,Int) -- ^ kernel_size -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> Bool -- ^ ceil_mode -> Bool -- ^ count_include_pad -> Int -- ^ divisor_override -> Tensor avg_pool3d _self _kernel_size _stride _padding _ceil_mode _count_include_pad _divisor_override = unsafePerformIO $ (cast7 ATen.avg_pool3d_tlllbbl) _self _kernel_size _stride _padding _ceil_mode _count_include_pad _divisor_override fractional_max_pool2d :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ output_size -> Tensor -- ^ random_samples -> (Tensor,Tensor) fractional_max_pool2d _self _kernel_size _output_size _random_samples = unsafePerformIO $ (cast4 ATen.fractional_max_pool2d_tllt) _self _kernel_size _output_size _random_samples fractional_max_pool3d :: Tensor -- ^ self -> (Int,Int,Int) -- ^ kernel_size -> (Int,Int,Int) -- ^ output_size -> Tensor -- ^ random_samples -> (Tensor,Tensor) fractional_max_pool3d _self _kernel_size _output_size _random_samples = unsafePerformIO $ (cast4 ATen.fractional_max_pool3d_tllt) _self _kernel_size _output_size _random_samples max_pool2d_with_indices :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> (Tensor,Tensor) max_pool2d_with_indices _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.max_pool2d_with_indices_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode max_pool3d_with_indices :: Tensor -- ^ self -> (Int,Int,Int) -- ^ kernel_size -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Bool -- ^ ceil_mode -> (Tensor,Tensor) max_pool3d_with_indices _self _kernel_size _stride _padding _dilation _ceil_mode = unsafePerformIO $ (cast6 ATen.max_pool3d_with_indices_tllllb) _self _kernel_size _stride _padding _dilation _ceil_mode max_unpool2d :: Tensor -- ^ self -> Tensor -- ^ indices -> (Int,Int) -- ^ output_size -> Tensor max_unpool2d _self _indices _output_size = unsafePerformIO $ (cast3 ATen.max_unpool2d_ttl) _self _indices _output_size max_unpool3d :: Tensor -- ^ self -> Tensor -- ^ indices -> (Int,Int,Int) -- ^ output_size -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> Tensor max_unpool3d _self _indices _output_size _stride _padding = unsafePerformIO $ (cast5 ATen.max_unpool3d_ttlll) _self _indices _output_size _stride _padding reflection_pad1d :: Tensor -- ^ self -> (Int,Int) -- ^ padding -> Tensor reflection_pad1d _self _padding = unsafePerformIO $ (cast2 ATen.reflection_pad1d_tl) _self _padding reflection_pad2d :: Tensor -- ^ self -> (Int,Int,Int,Int) -- ^ padding -> Tensor reflection_pad2d _self _padding = unsafePerformIO $ (cast2 ATen.reflection_pad2d_tl) _self _padding reflection_pad3d :: Tensor -- ^ self -> (Int,Int,Int,Int,Int,Int) -- ^ padding -> Tensor reflection_pad3d _self _padding = unsafePerformIO $ (cast2 ATen.reflection_pad3d_tl) _self _padding replication_pad1d :: Tensor -- ^ self -> (Int,Int) -- ^ padding -> Tensor replication_pad1d _self _padding = unsafePerformIO $ (cast2 ATen.replication_pad1d_tl) _self _padding replication_pad2d :: Tensor -- ^ self -> (Int,Int,Int,Int) -- ^ padding -> Tensor replication_pad2d _self _padding = unsafePerformIO $ (cast2 ATen.replication_pad2d_tl) _self _padding replication_pad3d :: Tensor -- ^ self -> (Int,Int,Int,Int,Int,Int) -- ^ padding -> Tensor replication_pad3d _self _padding = unsafePerformIO $ (cast2 ATen.replication_pad3d_tl) _self _padding pad :: Tensor -- ^ self -> [Int] -- ^ pad -> String -- ^ mode -> Double -- ^ value -> Tensor pad _self _pad _mode _value = unsafePerformIO $ (cast4 ATen.pad_tlsd) _self _pad _mode _value upsample_linear1d_tlba :: Tensor -- ^ input -> [Int] -- ^ output_size -> Bool -- ^ align_corners -> ([Double]) -- ^ scale_factors -> Tensor upsample_linear1d_tlba _input _output_size _align_corners _scale_factors = unsafePerformIO $ (cast4 ATen.upsample_linear1d_tlba) _input _output_size _align_corners _scale_factors upsample_bilinear2d_tlba :: Tensor -- ^ input -> [Int] -- ^ output_size -> Bool -- ^ align_corners -> ([Double]) -- ^ scale_factors -> Tensor upsample_bilinear2d_tlba _input _output_size _align_corners _scale_factors = unsafePerformIO $ (cast4 ATen.upsample_bilinear2d_tlba) _input _output_size _align_corners _scale_factors upsample_trilinear3d_tlba :: Tensor -- ^ input -> [Int] -- ^ output_size -> Bool -- ^ align_corners -> ([Double]) -- ^ scale_factors -> Tensor upsample_trilinear3d_tlba _input _output_size _align_corners _scale_factors = unsafePerformIO $ (cast4 ATen.upsample_trilinear3d_tlba) _input _output_size _align_corners _scale_factors upsample_bicubic2d_tlba :: Tensor -- ^ input -> [Int] -- ^ output_size -> Bool -- ^ align_corners -> ([Double]) -- ^ scale_factors -> Tensor upsample_bicubic2d_tlba _input _output_size _align_corners _scale_factors = unsafePerformIO $ (cast4 ATen.upsample_bicubic2d_tlba) _input _output_size _align_corners _scale_factors upsample_nearest1d_tla :: Tensor -- ^ input -> [Int] -- ^ output_size -> ([Double]) -- ^ scale_factors -> Tensor upsample_nearest1d_tla _input _output_size _scale_factors = unsafePerformIO $ (cast3 ATen.upsample_nearest1d_tla) _input _output_size _scale_factors upsample_nearest2d_tla :: Tensor -- ^ input -> [Int] -- ^ output_size -> ([Double]) -- ^ scale_factors -> Tensor upsample_nearest2d_tla _input _output_size _scale_factors = unsafePerformIO $ (cast3 ATen.upsample_nearest2d_tla) _input _output_size _scale_factors upsample_nearest3d_tla :: Tensor -- ^ input -> [Int] -- ^ output_size -> ([Double]) -- ^ scale_factors -> Tensor upsample_nearest3d_tla _input _output_size _scale_factors = unsafePerformIO $ (cast3 ATen.upsample_nearest3d_tla) _input _output_size _scale_factors -- upsample_linear1d_tlbd -- :: Tensor -- ^ self -- -> Int -- ^ output_size -- -> Bool -- ^ align_corners -- -> Double -- ^ scales -- -> Tensor -- upsample_linear1d_tlbd _self _output_size _align_corners _scales = unsafePerformIO $ (cast4 ATen.upsample_linear1d_tlbd) _self _output_size _align_corners _scales upsample_bilinear2d_tlbdd :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> Bool -- ^ align_corners -> Double -- ^ scales_h -> Double -- ^ scales_w -> Tensor upsample_bilinear2d_tlbdd _self _output_size _align_corners _scales_h _scales_w = unsafePerformIO $ (cast5 ATen.upsample_bilinear2d_tlbdd) _self _output_size _align_corners _scales_h _scales_w upsample_bicubic2d_tlbdd :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> Bool -- ^ align_corners -> Double -- ^ scales_h -> Double -- ^ scales_w -> Tensor upsample_bicubic2d_tlbdd _self _output_size _align_corners _scales_h _scales_w = unsafePerformIO $ (cast5 ATen.upsample_bicubic2d_tlbdd) _self _output_size _align_corners _scales_h _scales_w upsample_trilinear3d_tlbddd :: Tensor -- ^ self -> (Int,Int,Int) -- ^ output_size -> Bool -- ^ align_corners -> Double -- ^ scales_d -> Double -- ^ scales_h -> Double -- ^ scales_w -> Tensor upsample_trilinear3d_tlbddd _self _output_size _align_corners _scales_d _scales_h _scales_w = unsafePerformIO $ (cast6 ATen.upsample_trilinear3d_tlbddd) _self _output_size _align_corners _scales_d _scales_h _scales_w -- upsample_nearest1d_tld -- :: Tensor -- ^ self -- -> Int -- ^ output_size -- -> Double -- ^ scales -- -> Tensor -- upsample_nearest1d_tld _self _output_size _scales = unsafePerformIO $ (cast3 ATen.upsample_nearest1d_tld) _self _output_size _scales upsample_nearest2d_tldd :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> Double -- ^ scales_h -> Double -- ^ scales_w -> Tensor upsample_nearest2d_tldd _self _output_size _scales_h _scales_w = unsafePerformIO $ (cast4 ATen.upsample_nearest2d_tldd) _self _output_size _scales_h _scales_w upsample_nearest3d_tlddd :: Tensor -- ^ self -> (Int,Int,Int) -- ^ output_size -> Double -- ^ scales_d -> Double -- ^ scales_h -> Double -- ^ scales_w -> Tensor upsample_nearest3d_tlddd _self _output_size _scales_d _scales_h _scales_w = unsafePerformIO $ (cast5 ATen.upsample_nearest3d_tlddd) _self _output_size _scales_d _scales_h _scales_w slow_conv_transpose2d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ output_padding -> (Int,Int) -- ^ dilation -> Tensor slow_conv_transpose2d _self _weight _kernel_size _bias _stride _padding _output_padding _dilation = unsafePerformIO $ (cast8 ATen.slow_conv_transpose2d_ttltllll) _self _weight _kernel_size _bias _stride _padding _output_padding _dilation slow_conv_transpose3d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ output_padding -> (Int,Int,Int) -- ^ dilation -> Tensor slow_conv_transpose3d _self _weight _kernel_size _bias _stride _padding _output_padding _dilation = unsafePerformIO $ (cast8 ATen.slow_conv_transpose3d_ttltllll) _self _weight _kernel_size _bias _stride _padding _output_padding _dilation thnn_conv2d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> Tensor thnn_conv2d _self _weight _kernel_size _bias _stride _padding = unsafePerformIO $ (cast6 ATen.thnn_conv2d_ttltll) _self _weight _kernel_size _bias _stride _padding conv_depthwise3d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Tensor conv_depthwise3d _self _weight _kernel_size _bias _stride _padding _dilation = unsafePerformIO $ (cast7 ATen.conv_depthwise3d_ttltlll) _self _weight _kernel_size _bias _stride _padding _dilation slow_conv3d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> Tensor slow_conv3d _self _weight _kernel_size _bias _stride _padding = unsafePerformIO $ (cast6 ATen.slow_conv3d_ttltll) _self _weight _kernel_size _bias _stride _padding slow_conv3d_forward :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> Tensor slow_conv3d_forward _self _weight _kernel_size _bias _stride _padding = unsafePerformIO $ (cast6 ATen.slow_conv3d_forward_ttltll) _self _weight _kernel_size _bias _stride _padding slow_conv_dilated2d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int) -- ^ stride -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ dilation -> Tensor slow_conv_dilated2d _self _weight _kernel_size _bias _stride _padding _dilation = unsafePerformIO $ (cast7 ATen.slow_conv_dilated2d_ttltlll) _self _weight _kernel_size _bias _stride _padding _dilation slow_conv_dilated3d :: Tensor -- ^ self -> Tensor -- ^ weight -> (Int,Int,Int) -- ^ kernel_size -> Tensor -- ^ bias -> (Int,Int,Int) -- ^ stride -> (Int,Int,Int) -- ^ padding -> (Int,Int,Int) -- ^ dilation -> Tensor slow_conv_dilated3d _self _weight _kernel_size _bias _stride _padding _dilation = unsafePerformIO $ (cast7 ATen.slow_conv_dilated3d_ttltlll) _self _weight _kernel_size _bias _stride _padding _dilation col2im :: Tensor -- ^ self -> (Int,Int) -- ^ output_size -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ dilation -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ stride -> Tensor col2im _self _output_size _kernel_size _dilation _padding _stride = unsafePerformIO $ (cast6 ATen.col2im_tlllll) _self _output_size _kernel_size _dilation _padding _stride column_stack :: [Tensor] -- ^ tensors -> Tensor column_stack _tensors = unsafePerformIO $ (cast1 ATen.column_stack_l) _tensors im2col :: Tensor -- ^ self -> (Int,Int) -- ^ kernel_size -> (Int,Int) -- ^ dilation -> (Int,Int) -- ^ padding -> (Int,Int) -- ^ stride -> Tensor im2col _self _kernel_size _dilation _padding _stride = unsafePerformIO $ (cast5 ATen.im2col_tllll) _self _kernel_size _dilation _padding _stride isfinite :: Tensor -- ^ self -> Tensor isfinite _self = unsafePerformIO $ (cast1 ATen.isfinite_t) _self isinf :: Tensor -- ^ self -> Tensor isinf _self = unsafePerformIO $ (cast1 ATen.isinf_t) _self isposinf :: Tensor -- ^ self -> Tensor isposinf _self = unsafePerformIO $ (cast1 ATen.isposinf_t) _self isneginf :: Tensor -- ^ self -> Tensor isneginf _self = unsafePerformIO $ (cast1 ATen.isneginf_t) _self special_entr :: Tensor -- ^ self -> Tensor special_entr _self = unsafePerformIO $ (cast1 ATen.special_entr_t) _self special_ndtri :: Tensor -- ^ self -> Tensor special_ndtri _self = unsafePerformIO $ (cast1 ATen.special_ndtri_t) _self special_log_ndtr :: Tensor -- ^ self -> Tensor special_log_ndtr _self = unsafePerformIO $ (cast1 ATen.special_log_ndtr_t) _self special_expm1 :: Tensor -- ^ self -> Tensor special_expm1 _self = unsafePerformIO $ (cast1 ATen.special_expm1_t) _self special_exp2 :: Tensor -- ^ self -> Tensor special_exp2 _self = unsafePerformIO $ (cast1 ATen.special_exp2_t) _self special_psi :: Tensor -- ^ self -> Tensor special_psi _self = unsafePerformIO $ (cast1 ATen.special_psi_t) _self special_digamma :: Tensor -- ^ self -> Tensor special_digamma _self = unsafePerformIO $ (cast1 ATen.special_digamma_t) _self special_gammaln :: Tensor -- ^ self -> Tensor special_gammaln _self = unsafePerformIO $ (cast1 ATen.special_gammaln_t) _self special_erf :: Tensor -- ^ self -> Tensor special_erf _self = unsafePerformIO $ (cast1 ATen.special_erf_t) _self special_erfc :: Tensor -- ^ self -> Tensor special_erfc _self = unsafePerformIO $ (cast1 ATen.special_erfc_t) _self special_erfcx :: Tensor -- ^ self -> Tensor special_erfcx _self = unsafePerformIO $ (cast1 ATen.special_erfcx_t) _self special_erfinv :: Tensor -- ^ self -> Tensor special_erfinv _self = unsafePerformIO $ (cast1 ATen.special_erfinv_t) _self special_ndtr :: Tensor -- ^ self -> Tensor special_ndtr _self = unsafePerformIO $ (cast1 ATen.special_ndtr_t) _self special_xlog1py_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor special_xlog1py_tt _self _other = unsafePerformIO $ (cast2 ATen.special_xlog1py_tt) _self _other special_xlog1py_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor special_xlog1py_st _self _other = unsafePerformIO $ (cast2 ATen.special_xlog1py_st) _self _other special_xlog1py_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor special_xlog1py_ts _self _other = unsafePerformIO $ (cast2 ATen.special_xlog1py_ts) _self _other special_xlogy_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor special_xlogy_tt _self _other = unsafePerformIO $ (cast2 ATen.special_xlogy_tt) _self _other special_xlogy_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor special_xlogy_st _self _other = unsafePerformIO $ (cast2 ATen.special_xlogy_st) _self _other special_xlogy_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor special_xlogy_ts _self _other = unsafePerformIO $ (cast2 ATen.special_xlogy_ts) _self _other special_zeta_tt :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor special_zeta_tt _self _other = unsafePerformIO $ (cast2 ATen.special_zeta_tt) _self _other special_zeta_st :: Float -- ^ self -> Tensor -- ^ other -> Tensor special_zeta_st _self _other = unsafePerformIO $ (cast2 ATen.special_zeta_st) _self _other special_zeta_ts :: Tensor -- ^ self -> Float -- ^ other -> Tensor special_zeta_ts _self _other = unsafePerformIO $ (cast2 ATen.special_zeta_ts) _self _other special_i0 :: Tensor -- ^ self -> Tensor special_i0 _self = unsafePerformIO $ (cast1 ATen.special_i0_t) _self special_i0e :: Tensor -- ^ self -> Tensor special_i0e _self = unsafePerformIO $ (cast1 ATen.special_i0e_t) _self special_i1 :: Tensor -- ^ self -> Tensor special_i1 _self = unsafePerformIO $ (cast1 ATen.special_i1_t) _self special_i1e :: Tensor -- ^ self -> Tensor special_i1e _self = unsafePerformIO $ (cast1 ATen.special_i1e_t) _self special_logit :: Tensor -- ^ self -> Double -- ^ eps -> Tensor special_logit _self _eps = unsafePerformIO $ (cast2 ATen.special_logit_td) _self _eps special_polygamma :: Int -- ^ n -> Tensor -- ^ self -> Tensor special_polygamma _n _self = unsafePerformIO $ (cast2 ATen.special_polygamma_lt) _n _self special_logsumexp :: Tensor -- ^ self -> Int -- ^ dim -> Bool -- ^ keepdim -> Tensor special_logsumexp _self _dim _keepdim = unsafePerformIO $ (cast3 ATen.special_logsumexp_tlb) _self _dim _keepdim special_expit :: Tensor -- ^ self -> Tensor special_expit _self = unsafePerformIO $ (cast1 ATen.special_expit_t) _self special_sinc :: Tensor -- ^ self -> Tensor special_sinc _self = unsafePerformIO $ (cast1 ATen.special_sinc_t) _self special_round :: Tensor -- ^ self -> Int -- ^ decimals -> Tensor special_round _self _decimals = unsafePerformIO $ (cast2 ATen.special_round_tl) _self _decimals special_log1p :: Tensor -- ^ self -> Tensor special_log1p _self = unsafePerformIO $ (cast1 ATen.special_log1p_t) _self special_log_softmax :: Tensor -- ^ self -> Int -- ^ dim -> DType -- ^ dtype -> Tensor special_log_softmax _self _dim _dtype = unsafePerformIO $ (cast3 ATen.special_log_softmax_tls) _self _dim _dtype special_gammainc :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor special_gammainc _self _other = unsafePerformIO $ (cast2 ATen.special_gammainc_tt) _self _other special_gammaincc :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor special_gammaincc _self _other = unsafePerformIO $ (cast2 ATen.special_gammaincc_tt) _self _other special_multigammaln :: Tensor -- ^ self -> Int -- ^ p -> Tensor special_multigammaln _self _p = unsafePerformIO $ (cast2 ATen.special_multigammaln_tl) _self _p special_softmax :: Tensor -- ^ self -> Int -- ^ dim -> DType -- ^ dtype -> Tensor special_softmax _self _dim _dtype = unsafePerformIO $ (cast3 ATen.special_softmax_tls) _self _dim _dtype fft_fft :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_fft _self _n _dim _norm = unsafePerformIO $ (cast4 ATen.fft_fft_tlls) _self _n _dim _norm fft_ifft :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_ifft _self _n _dim _norm = unsafePerformIO $ (cast4 ATen.fft_ifft_tlls) _self _n _dim _norm fft_rfft :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_rfft _self _n _dim _norm = unsafePerformIO $ (cast4 ATen.fft_rfft_tlls) _self _n _dim _norm fft_irfft :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_irfft _self _n _dim _norm = unsafePerformIO $ (cast4 ATen.fft_irfft_tlls) _self _n _dim _norm fft_hfft :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_hfft _self _n _dim _norm = unsafePerformIO $ (cast4 ATen.fft_hfft_tlls) _self _n _dim _norm fft_ihfft :: Tensor -- ^ self -> Int -- ^ n -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_ihfft _self _n _dim _norm = unsafePerformIO $ (cast4 ATen.fft_ihfft_tlls) _self _n _dim _norm fft_fft2 :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_fft2 _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_fft2_tlls) _self _s _dim _norm fft_ifft2 :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_ifft2 _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_ifft2_tlls) _self _s _dim _norm fft_rfft2 :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_rfft2 _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_rfft2_tlls) _self _s _dim _norm fft_irfft2 :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_irfft2 _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_irfft2_tlls) _self _s _dim _norm fft_hfft2 :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_hfft2 _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_hfft2_tlls) _self _s _dim _norm fft_ihfft2 :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_ihfft2 _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_ihfft2_tlls) _self _s _dim _norm fft_fftn :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_fftn _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_fftn_tlls) _self _s _dim _norm fft_ifftn :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_ifftn _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_ifftn_tlls) _self _s _dim _norm fft_rfftn :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_rfftn _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_rfftn_tlls) _self _s _dim _norm fft_irfftn :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_irfftn _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_irfftn_tlls) _self _s _dim _norm fft_hfftn :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_hfftn _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_hfftn_tlls) _self _s _dim _norm fft_ihfftn :: Tensor -- ^ self -> Int -- ^ s -> Int -- ^ dim -> String -- ^ norm -> Tensor fft_ihfftn _self _s _dim _norm = unsafePerformIO $ (cast4 ATen.fft_ihfftn_tlls) _self _s _dim _norm fft_fftshift :: Tensor -- ^ self -> Int -- ^ dim -> Tensor fft_fftshift _self _dim = unsafePerformIO $ (cast2 ATen.fft_fftshift_tl) _self _dim fft_ifftshift :: Tensor -- ^ self -> Int -- ^ dim -> Tensor fft_ifftshift _self _dim = unsafePerformIO $ (cast2 ATen.fft_ifftshift_tl) _self _dim linalg_cholesky_ex :: Tensor -- ^ self -> Bool -- ^ upper -> Bool -- ^ check_errors -> (Tensor,Tensor) linalg_cholesky_ex _self _upper _check_errors = unsafePerformIO $ (cast3 ATen.linalg_cholesky_ex_tbb) _self _upper _check_errors linalg_cholesky :: Tensor -- ^ self -> Bool -- ^ upper -> Tensor linalg_cholesky _self _upper = unsafePerformIO $ (cast2 ATen.linalg_cholesky_tb) _self _upper linalg_cross :: Tensor -- ^ self -> Tensor -- ^ other -> Int -- ^ dim -> Tensor linalg_cross _self _other _dim = unsafePerformIO $ (cast3 ATen.linalg_cross_ttl) _self _other _dim linalg_lu_factor :: Tensor -- ^ A -> Bool -- ^ pivot -> (Tensor,Tensor) linalg_lu_factor _A _pivot = unsafePerformIO $ (cast2 ATen.linalg_lu_factor_tb) _A _pivot linalg_lu_factor_ex :: Tensor -- ^ A -> Bool -- ^ pivot -> Bool -- ^ check_errors -> (Tensor,Tensor,Tensor) linalg_lu_factor_ex _A _pivot _check_errors = unsafePerformIO $ (cast3 ATen.linalg_lu_factor_ex_tbb) _A _pivot _check_errors linalg_lu :: Tensor -- ^ A -> Bool -- ^ pivot -> (Tensor,Tensor,Tensor) linalg_lu _A _pivot = unsafePerformIO $ (cast2 ATen.linalg_lu_tb) _A _pivot linalg_lu_solve :: Tensor -- ^ LU -> Tensor -- ^ pivots -> Tensor -- ^ B -> Bool -- ^ left -> Bool -- ^ adjoint -> Tensor linalg_lu_solve _LU _pivots _B _left _adjoint = unsafePerformIO $ (cast5 ATen.linalg_lu_solve_tttbb) _LU _pivots _B _left _adjoint linalg_det :: Tensor -- ^ A -> Tensor linalg_det _A = unsafePerformIO $ (cast1 ATen.linalg_det_t) _A det :: Tensor -- ^ self -> Tensor det _self = unsafePerformIO $ (cast1 ATen.det_t) _self linalg_ldl_factor_ex :: Tensor -- ^ self -> Bool -- ^ hermitian -> Bool -- ^ check_errors -> (Tensor,Tensor,Tensor) linalg_ldl_factor_ex _self _hermitian _check_errors = unsafePerformIO $ (cast3 ATen.linalg_ldl_factor_ex_tbb) _self _hermitian _check_errors linalg_ldl_factor :: Tensor -- ^ self -> Bool -- ^ hermitian -> (Tensor,Tensor) linalg_ldl_factor _self _hermitian = unsafePerformIO $ (cast2 ATen.linalg_ldl_factor_tb) _self _hermitian linalg_ldl_solve :: Tensor -- ^ LD -> Tensor -- ^ pivots -> Tensor -- ^ B -> Bool -- ^ hermitian -> Tensor linalg_ldl_solve _LD _pivots _B _hermitian = unsafePerformIO $ (cast4 ATen.linalg_ldl_solve_tttb) _LD _pivots _B _hermitian linalg_lstsq :: Tensor -- ^ a -> Tensor -- ^ b -> Double -- ^ rcond -> String -- ^ driver -> (Tensor,Tensor,Tensor,Tensor) linalg_lstsq _a _b _rcond _driver = unsafePerformIO $ (cast4 ATen.linalg_lstsq_ttds) _a _b _rcond _driver lstsq :: Tensor -- ^ b -> Tensor -- ^ a -> Tensor lstsq _b _a = let (t0,_,_,_) = unsafePerformIO $ (cast2 ATen.linalg_lstsq_tt) _a _b :: (Tensor,Tensor,Tensor,Tensor) in t0 linalg_matmul :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor linalg_matmul _self _other = unsafePerformIO $ (cast2 ATen.linalg_matmul_tt) _self _other linalg_vecdot :: Tensor -- ^ x -> Tensor -- ^ y -> Int -- ^ dim -> Tensor linalg_vecdot _x _y _dim = unsafePerformIO $ (cast3 ATen.linalg_vecdot_ttl) _x _y _dim linalg_matrix_exp :: Tensor -- ^ self -> Tensor linalg_matrix_exp _self = unsafePerformIO $ (cast1 ATen.linalg_matrix_exp_t) _self linalg_slogdet :: Tensor -- ^ A -> (Tensor,Tensor) linalg_slogdet _A = unsafePerformIO $ (cast1 ATen.linalg_slogdet_t) _A slogdet :: Tensor -- ^ self -> (Tensor,Tensor) slogdet _self = unsafePerformIO $ (cast1 ATen.slogdet_t) _self logdet :: Tensor -- ^ self -> Tensor logdet _self = unsafePerformIO $ (cast1 ATen.logdet_t) _self linalg_eig :: Tensor -- ^ self -> (Tensor,Tensor) linalg_eig _self = unsafePerformIO $ (cast1 ATen.linalg_eig_t) _self linalg_eigvals :: Tensor -- ^ self -> Tensor linalg_eigvals _self = unsafePerformIO $ (cast1 ATen.linalg_eigvals_t) _self linalg_eigh :: Tensor -- ^ self -> String -- ^ UPLO -> (Tensor,Tensor) linalg_eigh _self _UPLO = unsafePerformIO $ (cast2 ATen.linalg_eigh_ts) _self _UPLO linalg_eigvalsh :: Tensor -- ^ self -> String -- ^ UPLO -> Tensor linalg_eigvalsh _self _UPLO = unsafePerformIO $ (cast2 ATen.linalg_eigvalsh_ts) _self _UPLO linalg_householder_product :: Tensor -- ^ input -> Tensor -- ^ tau -> Tensor linalg_householder_product _input _tau = unsafePerformIO $ (cast2 ATen.linalg_householder_product_tt) _input _tau linalg_inv_ex :: Tensor -- ^ A -> Bool -- ^ check_errors -> (Tensor,Tensor) linalg_inv_ex _A _check_errors = unsafePerformIO $ (cast2 ATen.linalg_inv_ex_tb) _A _check_errors linalg_inv :: Tensor -- ^ A -> Tensor linalg_inv _A = unsafePerformIO $ (cast1 ATen.linalg_inv_t) _A inverse :: Tensor -- ^ self -> Tensor inverse _self = unsafePerformIO $ (cast1 ATen.inverse_t) _self inner :: Tensor -- ^ self -> Tensor -- ^ other -> Tensor inner _self _other = unsafePerformIO $ (cast2 ATen.inner_tt) _self _other outer :: Tensor -- ^ self -> Tensor -- ^ vec2 -> Tensor outer _self _vec2 = unsafePerformIO $ (cast2 ATen.outer_tt) _self _vec2 ger :: Tensor -- ^ self -> Tensor -- ^ vec2 -> Tensor ger _self _vec2 = unsafePerformIO $ (cast2 ATen.ger_tt) _self _vec2 linalg_norm_tslbs :: Tensor -- ^ self -> Float -- ^ ord -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor linalg_norm_tslbs _self _ord _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.linalg_norm_tslbs) _self _ord _dim _keepdim _dtype -- linalg_norm_tslbs -- :: Tensor -- ^ self -- -> String -- ^ ord -- -> Int -- ^ dim -- -> Bool -- ^ keepdim -- -> DType -- ^ dtype -- -> Tensor -- linalg_norm_tslbs _self _ord _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.linalg_norm_tslbs) _self _ord _dim _keepdim _dtype linalg_vector_norm :: Tensor -- ^ self -> Float -- ^ ord -> Int -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor linalg_vector_norm _self _ord _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.linalg_vector_norm_tslbs) _self _ord _dim _keepdim _dtype linalg_matrix_norm_tslbs :: Tensor -- ^ self -> Float -- ^ ord -> [Int] -- ^ dim -> Bool -- ^ keepdim -> DType -- ^ dtype -> Tensor linalg_matrix_norm_tslbs _self _ord _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.linalg_matrix_norm_tslbs) _self _ord _dim _keepdim _dtype -- linalg_matrix_norm_tslbs -- :: Tensor -- ^ self -- -> String -- ^ ord -- -> [Int] -- ^ dim -- -> Bool -- ^ keepdim -- -> DType -- ^ dtype -- -> Tensor -- linalg_matrix_norm_tslbs _self _ord _dim _keepdim _dtype = unsafePerformIO $ (cast5 ATen.linalg_matrix_norm_tslbs) _self _ord _dim _keepdim _dtype linalg_svd :: Tensor -- ^ A -> Bool -- ^ full_matrices -> String -- ^ driver -> (Tensor,Tensor,Tensor) linalg_svd _A _full_matrices _driver = unsafePerformIO $ (cast3 ATen.linalg_svd_tbs) _A _full_matrices _driver linalg_svdvals :: Tensor -- ^ A -> String -- ^ driver -> Tensor linalg_svdvals _A _driver = unsafePerformIO $ (cast2 ATen.linalg_svdvals_ts) _A _driver linalg_cond_ts :: Tensor -- ^ self -> Float -- ^ p -> Tensor linalg_cond_ts _self _p = unsafePerformIO $ (cast2 ATen.linalg_cond_ts) _self _p -- linalg_cond_ts -- :: Tensor -- ^ self -- -> String -- ^ p -- -> Tensor -- linalg_cond_ts _self _p = unsafePerformIO $ (cast2 ATen.linalg_cond_ts) _self _p linalg_pinv_tttb :: Tensor -- ^ self -> Tensor -- ^ atol -> Tensor -- ^ rtol -> Bool -- ^ hermitian -> Tensor linalg_pinv_tttb _self _atol _rtol _hermitian = unsafePerformIO $ (cast4 ATen.linalg_pinv_tttb) _self _atol _rtol _hermitian linalg_pinv_tddb :: Tensor -- ^ self -> Double -- ^ atol -> Double -- ^ rtol -> Bool -- ^ hermitian -> Tensor linalg_pinv_tddb _self _atol _rtol _hermitian = unsafePerformIO $ (cast4 ATen.linalg_pinv_tddb) _self _atol _rtol _hermitian linalg_pinv_tdb :: Tensor -- ^ self -> Double -- ^ rcond -> Bool -- ^ hermitian -> Tensor linalg_pinv_tdb _self _rcond _hermitian = unsafePerformIO $ (cast3 ATen.linalg_pinv_tdb) _self _rcond _hermitian linalg_pinv_ttb :: Tensor -- ^ self -> Tensor -- ^ rcond -> Bool -- ^ hermitian -> Tensor linalg_pinv_ttb _self _rcond _hermitian = unsafePerformIO $ (cast3 ATen.linalg_pinv_ttb) _self _rcond _hermitian linalg_solve_ex :: Tensor -- ^ A -> Tensor -- ^ B -> Bool -- ^ left -> Bool -- ^ check_errors -> (Tensor,Tensor) linalg_solve_ex _A _B _left _check_errors = unsafePerformIO $ (cast4 ATen.linalg_solve_ex_ttbb) _A _B _left _check_errors linalg_solve :: Tensor -- ^ A -> Tensor -- ^ B -> Bool -- ^ left -> Tensor linalg_solve _A _B _left = unsafePerformIO $ (cast3 ATen.linalg_solve_ttb) _A _B _left linalg_tensorinv :: Tensor -- ^ self -> Int -- ^ ind -> Tensor linalg_tensorinv _self _ind = unsafePerformIO $ (cast2 ATen.linalg_tensorinv_tl) _self _ind linalg_tensorsolve :: Tensor -- ^ self -> Tensor -- ^ other -> [Int] -- ^ dims -> Tensor linalg_tensorsolve _self _other _dims = unsafePerformIO $ (cast3 ATen.linalg_tensorsolve_ttl) _self _other _dims linalg_qr :: Tensor -- ^ A -> String -- ^ mode -> (Tensor,Tensor) linalg_qr _A _mode = unsafePerformIO $ (cast2 ATen.linalg_qr_ts) _A _mode linalg_matrix_power :: Tensor -- ^ self -> Int -- ^ n -> Tensor linalg_matrix_power _self _n = unsafePerformIO $ (cast2 ATen.linalg_matrix_power_tl) _self _n linalg_matrix_rank_tttb :: Tensor -- ^ input -> Tensor -- ^ atol -> Tensor -- ^ rtol -> Bool -- ^ hermitian -> Tensor linalg_matrix_rank_tttb _input _atol _rtol _hermitian = unsafePerformIO $ (cast4 ATen.linalg_matrix_rank_tttb) _input _atol _rtol _hermitian linalg_matrix_rank_tddb :: Tensor -- ^ self -> Double -- ^ atol -> Double -- ^ rtol -> Bool -- ^ hermitian -> Tensor linalg_matrix_rank_tddb _self _atol _rtol _hermitian = unsafePerformIO $ (cast4 ATen.linalg_matrix_rank_tddb) _self _atol _rtol _hermitian linalg_matrix_rank_tdb :: Tensor -- ^ self -> Double -- ^ tol -> Bool -- ^ hermitian -> Tensor linalg_matrix_rank_tdb _self _tol _hermitian = unsafePerformIO $ (cast3 ATen.linalg_matrix_rank_tdb) _self _tol _hermitian linalg_matrix_rank_ttb :: Tensor -- ^ input -> Tensor -- ^ tol -> Bool -- ^ hermitian -> Tensor linalg_matrix_rank_ttb _input _tol _hermitian = unsafePerformIO $ (cast3 ATen.linalg_matrix_rank_ttb) _input _tol _hermitian linalg_multi_dot :: [Tensor] -- ^ tensors -> Tensor linalg_multi_dot _tensors = unsafePerformIO $ (cast1 ATen.linalg_multi_dot_l) _tensors nested_to_padded_tensor :: Tensor -- ^ self -> Double -- ^ padding -> [Int] -- ^ output_size -> Tensor nested_to_padded_tensor _self _padding _output_size = unsafePerformIO $ (cast3 ATen.nested_to_padded_tensor_tdl) _self _padding _output_size segment_reduce :: Tensor -- ^ data -> String -- ^ reduce -> Tensor -- ^ lengths -> Tensor -- ^ indices -> Tensor -- ^ offsets -> Int -- ^ axis -> Bool -- ^ unsafe -> Float -- ^ initial -> Tensor segment_reduce _data _reduce _lengths _indices _offsets _axis _unsafe _initial = unsafePerformIO $ (cast8 ATen.segment_reduce_tstttlbs) _data _reduce _lengths _indices _offsets _axis _unsafe _initial pad_sequence :: [Tensor] -- ^ sequences -> Bool -- ^ batch_first -> Double -- ^ padding_value -> Tensor pad_sequence _sequences _batch_first _padding_value = unsafePerformIO $ (cast3 ATen.pad_sequence_lbd) _sequences _batch_first _padding_value flatten_dense_tensors :: [Tensor] -- ^ tensors -> Tensor flatten_dense_tensors _tensors = unsafePerformIO $ (cast1 ATen.flatten_dense_tensors_l) _tensors unflatten_dense_tensors :: Tensor -- ^ flat -> [Tensor] -- ^ tensors -> [Tensor] unflatten_dense_tensors _flat _tensors = unsafePerformIO $ (cast2 ATen.unflatten_dense_tensors_tl) _flat _tensors view_as_real_copy :: Tensor -- ^ self -> Tensor view_as_real_copy _self = unsafePerformIO $ (cast1 ATen.view_as_real_copy_t) _self view_as_complex_copy :: Tensor -- ^ self -> Tensor view_as_complex_copy _self = unsafePerformIO $ (cast1 ATen.view_as_complex_copy_t) _self as_strided_copy :: Tensor -- ^ self -> [Int] -- ^ size -> [Int] -- ^ stride -> Int -- ^ storage_offset -> Tensor as_strided_copy _self _size _stride _storage_offset = unsafePerformIO $ (cast4 ATen.as_strided_copy_tlll) _self _size _stride _storage_offset diagonal_copy :: Tensor -- ^ self -> Int -- ^ offset -> Int -- ^ dim1 -> Int -- ^ dim2 -> Tensor diagonal_copy _self _offset _dim1 _dim2 = unsafePerformIO $ (cast4 ATen.diagonal_copy_tlll) _self _offset _dim1 _dim2 expand_copy :: Tensor -- ^ self -> [Int] -- ^ size -> Bool -- ^ implicit -> Tensor expand_copy _self _size _implicit = unsafePerformIO $ (cast3 ATen.expand_copy_tlb) _self _size _implicit permute_copy :: Tensor -- ^ self -> [Int] -- ^ dims -> Tensor permute_copy _self _dims = unsafePerformIO $ (cast2 ATen.permute_copy_tl) _self _dims select_copy :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ index -> Tensor select_copy _self _dim _index = unsafePerformIO $ (cast3 ATen.select_copy_tll) _self _dim _index detach_copy :: Tensor -- ^ self -> Tensor detach_copy _self = unsafePerformIO $ (cast1 ATen.detach_copy_t) _self slice_copy :: Tensor -- ^ self -> Int -- ^ dim -> Int -- ^ start -> Int -- ^ end -> Int -- ^ step -> Tensor slice_copy _self _dim _start _end _step = unsafePerformIO $ (cast5 ATen.slice_copy_tllll) _self _dim _start _end _step split_copy :: Tensor -- ^ self -> Int -- ^ split_size -> Int -- ^ dim -> [Tensor] split_copy _self _split_size _dim = unsafePerformIO $ (cast3 ATen.split_copy_tll) _self _split_size _dim split_with_sizes_copy :: Tensor -- ^ self -> [Int] -- ^ split_sizes -> Int -- ^ dim -> [Tensor] split_with_sizes_copy _self _split_sizes _dim = unsafePerformIO $ (cast3 ATen.split_with_sizes_copy_tll) _self _split_sizes _dim squeeze_copy_t :: Tensor -- ^ self -> Tensor squeeze_copy_t _self = unsafePerformIO $ (cast1 ATen.squeeze_copy_t) _self squeeze_copy_tl :: Tensor -- ^ self -> Int -- ^ dim -> Tensor squeeze_copy_tl _self _dim = unsafePerformIO $ (cast2 ATen.squeeze_copy_tl) _self _dim -- squeeze_copy_tl -- :: Tensor -- ^ self -- -> [Int] -- ^ dim -- -> Tensor -- squeeze_copy_tl _self _dim = unsafePerformIO $ (cast2 ATen.squeeze_copy_tl) _self _dim t_copy :: Tensor -- ^ self -> Tensor t_copy _self = unsafePerformIO $ (cast1 ATen.t_copy_t) _self transpose_copy :: Tensor -- ^ self -> Int -- ^ dim0 -> Int -- ^ dim1 -> Tensor transpose_copy _self _dim0 _dim1 = unsafePerformIO $ (cast3 ATen.transpose_copy_tll) _self _dim0 _dim1 unsqueeze_copy :: Tensor -- ^ self -> Int -- ^ dim -> Tensor unsqueeze_copy _self _dim = unsafePerformIO $ (cast2 ATen.unsqueeze_copy_tl) _self _dim indices_copy :: Tensor -- ^ self -> Tensor indices_copy _self = unsafePerformIO $ (cast1 ATen.indices_copy_t) _self values_copy :: Tensor -- ^ self -> Tensor values_copy _self = unsafePerformIO $ (cast1 ATen.values_copy_t) _self crow_indices_copy :: Tensor -- ^ self -> Tensor crow_indices_copy _self = unsafePerformIO $ (cast1 ATen.crow_indices_copy_t) _self col_indices_copy :: Tensor -- ^ self -> Tensor col_indices_copy _self = unsafePerformIO $ (cast1 ATen.col_indices_copy_t) _self ccol_indices_copy :: Tensor -- ^ self -> Tensor ccol_indices_copy _self = unsafePerformIO $ (cast1 ATen.ccol_indices_copy_t) _self row_indices_copy :: Tensor -- ^ self -> Tensor row_indices_copy _self = unsafePerformIO $ (cast1 ATen.row_indices_copy_t) _self unbind_copy :: Tensor -- ^ self -> Int -- ^ dim -> [Tensor] unbind_copy _self _dim = unsafePerformIO $ (cast2 ATen.unbind_copy_tl) _self _dim view_copy_tl :: Tensor -- ^ self -> [Int] -- ^ size -> Tensor view_copy_tl _self _size = unsafePerformIO $ (cast2 ATen.view_copy_tl) _self _size view_copy_ts :: Tensor -- ^ self -> DType -- ^ dtype -> Tensor view_copy_ts _self _dtype = unsafePerformIO $ (cast2 ATen.view_copy_ts) _self _dtype unfold_copy :: Tensor -- ^ self -> Int -- ^ dimension -> Int -- ^ size -> Int -- ^ step -> Tensor unfold_copy _self _dimension _size _step = unsafePerformIO $ (cast4 ATen.unfold_copy_tlll) _self _dimension _size _step alias_copy :: Tensor -- ^ self -> Tensor alias_copy _self = unsafePerformIO $ (cast1 ATen.alias_copy_t) _self scaled_dot_product_attention :: Tensor -- ^ query -> Tensor -- ^ key -> Tensor -- ^ value -> Maybe Tensor -- ^ attn_mask -> Double -- ^ dropout_p -> Bool -- ^ is_causal -> Double -- ^ scale -> Bool -- ^ enable_gqa -> Tensor scaled_dot_product_attention _query _key _value _attn_mask _dropout_p _is_causal _scale _enable_gqa = unsafePerformIO $ (cast8 ATen.scaled_dot_product_attention_tttqdbdb) _query _key _value _attn_mask _dropout_p _is_causal _scale _enable_gqa special_airy_ai :: Tensor -- ^ x -> Tensor special_airy_ai _x = unsafePerformIO $ (cast1 ATen.special_airy_ai_t) _x special_bessel_j0 :: Tensor -- ^ self -> Tensor special_bessel_j0 _self = unsafePerformIO $ (cast1 ATen.special_bessel_j0_t) _self special_bessel_j1 :: Tensor -- ^ self -> Tensor special_bessel_j1 _self = unsafePerformIO $ (cast1 ATen.special_bessel_j1_t) _self special_bessel_y0 :: Tensor -- ^ self -> Tensor special_bessel_y0 _self = unsafePerformIO $ (cast1 ATen.special_bessel_y0_t) _self special_bessel_y1 :: Tensor -- ^ self -> Tensor special_bessel_y1 _self = unsafePerformIO $ (cast1 ATen.special_bessel_y1_t) _self special_chebyshev_polynomial_t_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_t_tt _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_t_tt) _x _n special_chebyshev_polynomial_t_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_t_st _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_t_st) _x _n special_chebyshev_polynomial_t_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_chebyshev_polynomial_t_ts _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_t_ts) _x _n special_chebyshev_polynomial_u_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_u_tt _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_u_tt) _x _n special_chebyshev_polynomial_u_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_u_st _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_u_st) _x _n special_chebyshev_polynomial_u_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_chebyshev_polynomial_u_ts _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_u_ts) _x _n special_chebyshev_polynomial_v_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_v_tt _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_v_tt) _x _n special_chebyshev_polynomial_v_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_v_st _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_v_st) _x _n special_chebyshev_polynomial_v_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_chebyshev_polynomial_v_ts _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_v_ts) _x _n special_chebyshev_polynomial_w_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_w_tt _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_w_tt) _x _n special_chebyshev_polynomial_w_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_chebyshev_polynomial_w_st _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_w_st) _x _n special_chebyshev_polynomial_w_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_chebyshev_polynomial_w_ts _x _n = unsafePerformIO $ (cast2 ATen.special_chebyshev_polynomial_w_ts) _x _n special_hermite_polynomial_h_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_hermite_polynomial_h_tt _x _n = unsafePerformIO $ (cast2 ATen.special_hermite_polynomial_h_tt) _x _n special_hermite_polynomial_h_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_hermite_polynomial_h_st _x _n = unsafePerformIO $ (cast2 ATen.special_hermite_polynomial_h_st) _x _n special_hermite_polynomial_h_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_hermite_polynomial_h_ts _x _n = unsafePerformIO $ (cast2 ATen.special_hermite_polynomial_h_ts) _x _n special_hermite_polynomial_he_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_hermite_polynomial_he_tt _x _n = unsafePerformIO $ (cast2 ATen.special_hermite_polynomial_he_tt) _x _n special_hermite_polynomial_he_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_hermite_polynomial_he_st _x _n = unsafePerformIO $ (cast2 ATen.special_hermite_polynomial_he_st) _x _n special_hermite_polynomial_he_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_hermite_polynomial_he_ts _x _n = unsafePerformIO $ (cast2 ATen.special_hermite_polynomial_he_ts) _x _n special_laguerre_polynomial_l_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_laguerre_polynomial_l_tt _x _n = unsafePerformIO $ (cast2 ATen.special_laguerre_polynomial_l_tt) _x _n special_laguerre_polynomial_l_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_laguerre_polynomial_l_st _x _n = unsafePerformIO $ (cast2 ATen.special_laguerre_polynomial_l_st) _x _n special_laguerre_polynomial_l_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_laguerre_polynomial_l_ts _x _n = unsafePerformIO $ (cast2 ATen.special_laguerre_polynomial_l_ts) _x _n special_legendre_polynomial_p_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_legendre_polynomial_p_tt _x _n = unsafePerformIO $ (cast2 ATen.special_legendre_polynomial_p_tt) _x _n special_legendre_polynomial_p_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_legendre_polynomial_p_st _x _n = unsafePerformIO $ (cast2 ATen.special_legendre_polynomial_p_st) _x _n special_legendre_polynomial_p_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_legendre_polynomial_p_ts _x _n = unsafePerformIO $ (cast2 ATen.special_legendre_polynomial_p_ts) _x _n special_modified_bessel_i0 :: Tensor -- ^ self -> Tensor special_modified_bessel_i0 _self = unsafePerformIO $ (cast1 ATen.special_modified_bessel_i0_t) _self special_modified_bessel_i1 :: Tensor -- ^ self -> Tensor special_modified_bessel_i1 _self = unsafePerformIO $ (cast1 ATen.special_modified_bessel_i1_t) _self special_modified_bessel_k0 :: Tensor -- ^ self -> Tensor special_modified_bessel_k0 _self = unsafePerformIO $ (cast1 ATen.special_modified_bessel_k0_t) _self special_modified_bessel_k1 :: Tensor -- ^ self -> Tensor special_modified_bessel_k1 _self = unsafePerformIO $ (cast1 ATen.special_modified_bessel_k1_t) _self special_scaled_modified_bessel_k0 :: Tensor -- ^ x -> Tensor special_scaled_modified_bessel_k0 _x = unsafePerformIO $ (cast1 ATen.special_scaled_modified_bessel_k0_t) _x special_scaled_modified_bessel_k1 :: Tensor -- ^ x -> Tensor special_scaled_modified_bessel_k1 _x = unsafePerformIO $ (cast1 ATen.special_scaled_modified_bessel_k1_t) _x special_shifted_chebyshev_polynomial_t_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_t_tt _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_t_tt) _x _n special_shifted_chebyshev_polynomial_t_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_t_st _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_t_st) _x _n special_shifted_chebyshev_polynomial_t_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_shifted_chebyshev_polynomial_t_ts _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_t_ts) _x _n special_shifted_chebyshev_polynomial_u_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_u_tt _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_u_tt) _x _n special_shifted_chebyshev_polynomial_u_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_u_st _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_u_st) _x _n special_shifted_chebyshev_polynomial_u_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_shifted_chebyshev_polynomial_u_ts _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_u_ts) _x _n special_shifted_chebyshev_polynomial_v_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_v_tt _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_v_tt) _x _n special_shifted_chebyshev_polynomial_v_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_v_st _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_v_st) _x _n special_shifted_chebyshev_polynomial_v_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_shifted_chebyshev_polynomial_v_ts _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_v_ts) _x _n special_shifted_chebyshev_polynomial_w_tt :: Tensor -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_w_tt _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_w_tt) _x _n special_shifted_chebyshev_polynomial_w_st :: Float -- ^ x -> Tensor -- ^ n -> Tensor special_shifted_chebyshev_polynomial_w_st _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_w_st) _x _n special_shifted_chebyshev_polynomial_w_ts :: Tensor -- ^ x -> Float -- ^ n -> Tensor special_shifted_chebyshev_polynomial_w_ts _x _n = unsafePerformIO $ (cast2 ATen.special_shifted_chebyshev_polynomial_w_ts) _x _n special_spherical_bessel_j0 :: Tensor -- ^ x -> Tensor special_spherical_bessel_j0 _x = unsafePerformIO $ (cast1 ATen.special_spherical_bessel_j0_t) _x embedding_renorm :: Tensor -- ^ self -> Tensor -- ^ indices -> Double -- ^ max_norm -> Double -- ^ norm_type -> Tensor embedding_renorm _self _indices _max_norm _norm_type = unsafePerformIO $ (cast4 ATen.embedding_renorm_ttdd) _self _indices _max_norm _norm_type resize :: Tensor -- ^ self -> [Int] -- ^ size -> ATen.MemoryFormat -- ^ memory_format -> Tensor resize _self _size _memory_format = unsafePerformIO $ (cast3 ATen.resize_tlM) _self _size _memory_format resize_as :: Tensor -- ^ self -> Tensor -- ^ the_template -> ATen.MemoryFormat -- ^ memory_format -> Tensor resize_as _self _the_template _memory_format = unsafePerformIO $ (cast3 ATen.resize_as_ttM) _self _the_template _memory_format resize_as_sparse :: Tensor -- ^ self -> Tensor -- ^ the_template -> Tensor resize_as_sparse _self _the_template = unsafePerformIO $ (cast2 ATen.resize_as_sparse_tt) _self _the_template zero :: Tensor -- ^ self -> Tensor zero _self = unsafePerformIO $ (cast1 ATen.zero_t) _self sparse_resize :: Tensor -- ^ self -> [Int] -- ^ size -> Int -- ^ sparse_dim -> Int -- ^ dense_dim -> Tensor sparse_resize _self _size _sparse_dim _dense_dim = unsafePerformIO $ (cast4 ATen.sparse_resize_tlll) _self _size _sparse_dim _dense_dim sparse_resize_and_clear :: Tensor -- ^ self -> [Int] -- ^ size -> Int -- ^ sparse_dim -> Int -- ^ dense_dim -> Tensor sparse_resize_and_clear _self _size _sparse_dim _dense_dim = unsafePerformIO $ (cast4 ATen.sparse_resize_and_clear_tlll) _self _size _sparse_dim _dense_dim copy_sparse_to_sparse :: Tensor -- ^ self -> Tensor -- ^ src -> Bool -- ^ non_blocking -> Tensor copy_sparse_to_sparse _self _src _non_blocking = unsafePerformIO $ (cast3 ATen.copy_sparse_to_sparse_ttb) _self _src _non_blocking -- set_tS -- :: Tensor -- ^ self -- -> Storage -- ^ source -- -> Tensor -- set_tS _self _source = unsafePerformIO $ (cast2 ATen.set_tS) _self _source -- set_tSlll -- :: Tensor -- ^ self -- -> Storage -- ^ source -- -> Int -- ^ storage_offset -- -> [Int] -- ^ size -- -> [Int] -- ^ stride -- -> Tensor -- set_tSlll _self _source _storage_offset _size _stride = unsafePerformIO $ (cast5 ATen.set_tSlll) _self _source _storage_offset _size _stride set_tt :: Tensor -- ^ self -> Tensor -- ^ source -> Tensor set_tt _self _source = unsafePerformIO $ (cast2 ATen.set_tt) _self _source set_t :: Tensor -- ^ self -> Tensor set_t _self = unsafePerformIO $ (cast1 ATen.set_t) _self