-- generated by using spec/Declarations.yaml

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}

module Torch.Internal.Unmanaged.Native.Native2 where


import Foreign.C.String
import Foreign.C.Types
import Foreign
import Torch.Internal.Type

import qualified Language.C.Inline.Cpp as C
import qualified Language.C.Inline.Cpp.Unsafe as C
import qualified Language.C.Inline.Context as C
import qualified Language.C.Types as C

C.context $ C.cppCtx <> mempty { C.ctxTypesTable = typeTable }

C.include "<vector>"
C.include "<ATen/Tensor.h>"
C.include "<ATen/Functions.h>"


cosine_embedding_loss_tttdl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> Int64
  -> IO (Ptr Tensor)
cosine_embedding_loss_tttdl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor)
cosine_embedding_loss_tttdl Ptr Tensor
_input1 Ptr Tensor
_input2 Ptr Tensor
_target CDouble
_margin Int64
_reduction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cosine_embedding_loss(
    *$(at::Tensor* _input1)
  , *$(at::Tensor* _input2)
  , *$(at::Tensor* _target)
  , $(double _margin)
  , $(int64_t _reduction)));
  }|]

cosine_embedding_loss_tttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
cosine_embedding_loss_tttd :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
cosine_embedding_loss_tttd Ptr Tensor
_input1 Ptr Tensor
_input2 Ptr Tensor
_target CDouble
_margin =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cosine_embedding_loss(
    *$(at::Tensor* _input1)
  , *$(at::Tensor* _input2)
  , *$(at::Tensor* _target)
  , $(double _margin)));
  }|]

cosine_embedding_loss_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cosine_embedding_loss_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cosine_embedding_loss_ttt Ptr Tensor
_input1 Ptr Tensor
_input2 Ptr Tensor
_target =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cosine_embedding_loss(
    *$(at::Tensor* _input1)
  , *$(at::Tensor* _input2)
  , *$(at::Tensor* _target)));
  }|]

count_nonzero_tl
  :: Ptr Tensor
  -> Ptr IntArray
  -> IO (Ptr Tensor)
count_nonzero_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
count_nonzero_tl Ptr Tensor
_self Ptr IntArray
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::count_nonzero(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)));
  }|]

count_nonzero_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
count_nonzero_t :: Ptr Tensor -> IO (Ptr Tensor)
count_nonzero_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::count_nonzero(
    *$(at::Tensor* _self)));
  }|]

cov_tltt
  :: Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cov_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cov_tltt Ptr Tensor
_self Int64
_correction Ptr Tensor
_fweights Ptr Tensor
_aweights =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cov(
    *$(at::Tensor* _self)
  , $(int64_t _correction)
  , *$(at::Tensor* _fweights)
  , *$(at::Tensor* _aweights)));
  }|]

cov_tlt
  :: Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cov_tlt :: Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
cov_tlt Ptr Tensor
_self Int64
_correction Ptr Tensor
_fweights =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cov(
    *$(at::Tensor* _self)
  , $(int64_t _correction)
  , *$(at::Tensor* _fweights)));
  }|]

cov_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cov_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cov_tl Ptr Tensor
_self Int64
_correction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cov(
    *$(at::Tensor* _self)
  , $(int64_t _correction)));
  }|]

cov_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
cov_t :: Ptr Tensor -> IO (Ptr Tensor)
cov_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cov(
    *$(at::Tensor* _self)));
  }|]

corrcoef_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
corrcoef_t :: Ptr Tensor -> IO (Ptr Tensor)
corrcoef_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::corrcoef(
    *$(at::Tensor* _self)));
  }|]

cudnn_affine_grid_generator_tllll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
cudnn_affine_grid_generator_tllll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
cudnn_affine_grid_generator_tllll Ptr Tensor
_theta Int64
_N Int64
_C Int64
_H Int64
_W =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_affine_grid_generator(
    *$(at::Tensor* _theta)
  , $(int64_t _N)
  , $(int64_t _C)
  , $(int64_t _H)
  , $(int64_t _W)));
  }|]

cudnn_affine_grid_generator_backward_tllll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
cudnn_affine_grid_generator_backward_tllll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
cudnn_affine_grid_generator_backward_tllll Ptr Tensor
_grad Int64
_N Int64
_C Int64
_H Int64
_W =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_affine_grid_generator_backward(
    *$(at::Tensor* _grad)
  , $(int64_t _N)
  , $(int64_t _C)
  , $(int64_t _H)
  , $(int64_t _W)));
  }|]

cudnn_batch_norm_tttttbdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
cudnn_batch_norm_tttttbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
cudnn_batch_norm_tttttbdd Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr Tensor
_running_mean Ptr Tensor
_running_var CBool
_training CDouble
_exponential_average_factor CDouble
_epsilon =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::cudnn_batch_norm(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(at::Tensor* _running_mean)
  , *$(at::Tensor* _running_var)
  , $(bool _training)
  , $(double _exponential_average_factor)
  , $(double _epsilon)));
  }|]

cudnn_batch_norm_backward_tttttttdt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
cudnn_batch_norm_backward_tttttttdt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
cudnn_batch_norm_backward_tttttttdt Ptr Tensor
_input Ptr Tensor
_grad_output Ptr Tensor
_weight Ptr Tensor
_running_mean Ptr Tensor
_running_var Ptr Tensor
_save_mean Ptr Tensor
_save_var CDouble
_epsilon Ptr Tensor
_reserveSpace =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::cudnn_batch_norm_backward(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _running_mean)
  , *$(at::Tensor* _running_var)
  , *$(at::Tensor* _save_mean)
  , *$(at::Tensor* _save_var)
  , $(double _epsilon)
  , *$(at::Tensor* _reserveSpace)));
  }|]

cudnn_convolution_ttllllbbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
cudnn_convolution_ttllllbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
cudnn_convolution_ttllllbbb Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_padding Ptr IntArray
_stride Ptr IntArray
_dilation Int64
_groups CBool
_benchmark CBool
_deterministic CBool
_allow_tf32 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_convolution(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _weight)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _dilation)
  , $(int64_t _groups)
  , $(bool _benchmark)
  , $(bool _deterministic)
  , $(bool _allow_tf32)));
  }|]

cudnn_convolution_transpose_ttlllllbbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
cudnn_convolution_transpose_ttlllllbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
cudnn_convolution_transpose_ttlllllbbb Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_padding Ptr IntArray
_output_padding Ptr IntArray
_stride Ptr IntArray
_dilation Int64
_groups CBool
_benchmark CBool
_deterministic CBool
_allow_tf32 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_convolution_transpose(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _weight)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _output_padding)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _dilation)
  , $(int64_t _groups)
  , $(bool _benchmark)
  , $(bool _deterministic)
  , $(bool _allow_tf32)));
  }|]

cudnn_convolution_relu_tttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
cudnn_convolution_relu_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
cudnn_convolution_relu_tttllll Ptr Tensor
_self Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation Int64
_groups =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_convolution_relu(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(int64_t _groups)));
  }|]

cudnn_convolution_add_relu_tttstllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
cudnn_convolution_add_relu_tttstllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
cudnn_convolution_add_relu_tttstllll Ptr Tensor
_self Ptr Tensor
_weight Ptr Tensor
_z Ptr Scalar
_alpha Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation Int64
_groups =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_convolution_add_relu(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _z)
  , *$(at::Scalar* _alpha)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(int64_t _groups)));
  }|]

cudnn_grid_sampler_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cudnn_grid_sampler_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cudnn_grid_sampler_tt Ptr Tensor
_self Ptr Tensor
_grid =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_grid_sampler(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _grid)));
  }|]

cudnn_grid_sampler_backward_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cudnn_grid_sampler_backward_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
cudnn_grid_sampler_backward_ttt Ptr Tensor
_self Ptr Tensor
_grid Ptr Tensor
_grad_output =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cudnn_grid_sampler_backward(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _grid)
  , *$(at::Tensor* _grad_output)));
  }|]

cummax_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummax_tl :: Ptr Tensor -> Int64 -> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummax_tl Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummax(
    *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cummax_out_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummax_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummax_out_tttl Ptr Tensor
_values Ptr Tensor
_indices Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummax_out(
    *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cummax_tn
  :: Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummax_tn :: Ptr Tensor -> Ptr Dimname -> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummax_tn Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummax(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

cummax_out_tttn
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummax_out_tttn :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummax_out_tttn Ptr Tensor
_values Ptr Tensor
_indices Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummax_out(
    *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

_cummax_helper_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (())
_cummax_helper_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO ()
_cummax_helper_tttl Ptr Tensor
_self Ptr Tensor
_values Ptr Tensor
_indices Int64
_dim =
  [C.throwBlock| void {  (at::_cummax_helper(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , $(int64_t _dim)));
  }|]

cummin_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummin_tl :: Ptr Tensor -> Int64 -> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummin_tl Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummin(
    *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cummin_out_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummin_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummin_out_tttl Ptr Tensor
_values Ptr Tensor
_indices Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummin_out(
    *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cummin_tn
  :: Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummin_tn :: Ptr Tensor -> Ptr Dimname -> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummin_tn Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummin(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

cummin_out_tttn
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cummin_out_tttn :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
cummin_out_tttn Ptr Tensor
_values Ptr Tensor
_indices Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::cummin_out(
    *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

_cummin_helper_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (())
_cummin_helper_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO ()
_cummin_helper_tttl Ptr Tensor
_self Ptr Tensor
_values Ptr Tensor
_indices Int64
_dim =
  [C.throwBlock| void {  (at::_cummin_helper(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , $(int64_t _dim)));
  }|]

cummaxmin_backward_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cummaxmin_backward_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cummaxmin_backward_tttl Ptr Tensor
_grad Ptr Tensor
_input Ptr Tensor
_indices Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cummaxmin_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _indices)
  , $(int64_t _dim)));
  }|]

cumprod_tls
  :: Ptr Tensor
  -> Int64
  -> ScalarType
  -> IO (Ptr Tensor)
cumprod_tls :: Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
cumprod_tls Ptr Tensor
_self Int64
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod(
    *$(at::Tensor* _self)
  , $(int64_t _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumprod_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cumprod_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cumprod_tl Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod(
    *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cumprod_out_ttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> ScalarType
  -> IO (Ptr Tensor)
cumprod_out_ttls :: Ptr Tensor -> Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
cumprod_out_ttls Ptr Tensor
_out Ptr Tensor
_self Int64
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumprod_out_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cumprod_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cumprod_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cumprod_tns
  :: Ptr Tensor
  -> Ptr Dimname
  -> ScalarType
  -> IO (Ptr Tensor)
cumprod_tns :: Ptr Tensor -> Ptr Dimname -> ScalarType -> IO (Ptr Tensor)
cumprod_tns Ptr Tensor
_self Ptr Dimname
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumprod_tn
  :: Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr Tensor)
cumprod_tn :: Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
cumprod_tn Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

cumprod_out_ttns
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Dimname
  -> ScalarType
  -> IO (Ptr Tensor)
cumprod_out_ttns :: Ptr Tensor
-> Ptr Tensor -> Ptr Dimname -> ScalarType -> IO (Ptr Tensor)
cumprod_out_ttns Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumprod_out_ttn
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr Tensor)
cumprod_out_ttn :: Ptr Tensor -> Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
cumprod_out_ttn Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

cumprod_backward_ttlt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cumprod_backward_ttlt :: Ptr Tensor -> Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
cumprod_backward_ttlt Ptr Tensor
_grad Ptr Tensor
_input Int64
_dim Ptr Tensor
_output =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumprod_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _input)
  , $(int64_t _dim)
  , *$(at::Tensor* _output)));
  }|]

cumsum_tls
  :: Ptr Tensor
  -> Int64
  -> ScalarType
  -> IO (Ptr Tensor)
cumsum_tls :: Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
cumsum_tls Ptr Tensor
_self Int64
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum(
    *$(at::Tensor* _self)
  , $(int64_t _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumsum_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cumsum_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cumsum_tl Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum(
    *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cumsum_out_ttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> ScalarType
  -> IO (Ptr Tensor)
cumsum_out_ttls :: Ptr Tensor -> Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
cumsum_out_ttls Ptr Tensor
_out Ptr Tensor
_self Int64
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumsum_out_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cumsum_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cumsum_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _dim)));
  }|]

cumsum_tns
  :: Ptr Tensor
  -> Ptr Dimname
  -> ScalarType
  -> IO (Ptr Tensor)
cumsum_tns :: Ptr Tensor -> Ptr Dimname -> ScalarType -> IO (Ptr Tensor)
cumsum_tns Ptr Tensor
_self Ptr Dimname
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumsum_tn
  :: Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr Tensor)
cumsum_tn :: Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
cumsum_tn Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

cumsum_out_ttns
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Dimname
  -> ScalarType
  -> IO (Ptr Tensor)
cumsum_out_ttns :: Ptr Tensor
-> Ptr Tensor -> Ptr Dimname -> ScalarType -> IO (Ptr Tensor)
cumsum_out_ttns Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)
  , $(at::ScalarType _dtype)));
  }|]

cumsum_out_ttn
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Dimname
  -> IO (Ptr Tensor)
cumsum_out_ttn :: Ptr Tensor -> Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
cumsum_out_ttn Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumsum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)));
  }|]

cumulative_trapezoid_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
cumulative_trapezoid_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cumulative_trapezoid_ttl Ptr Tensor
_y Ptr Tensor
_x Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumulative_trapezoid(
    *$(at::Tensor* _y)
  , *$(at::Tensor* _x)
  , $(int64_t _dim)));
  }|]

cumulative_trapezoid_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cumulative_trapezoid_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cumulative_trapezoid_tt Ptr Tensor
_y Ptr Tensor
_x =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumulative_trapezoid(
    *$(at::Tensor* _y)
  , *$(at::Tensor* _x)));
  }|]

cumulative_trapezoid_tsl
  :: Ptr Tensor
  -> Ptr Scalar
  -> Int64
  -> IO (Ptr Tensor)
cumulative_trapezoid_tsl :: Ptr Tensor -> Ptr Scalar -> Int64 -> IO (Ptr Tensor)
cumulative_trapezoid_tsl Ptr Tensor
_y Ptr Scalar
_dx Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumulative_trapezoid(
    *$(at::Tensor* _y)
  , *$(at::Scalar* _dx)
  , $(int64_t _dim)));
  }|]

cumulative_trapezoid_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
cumulative_trapezoid_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
cumulative_trapezoid_ts Ptr Tensor
_y Ptr Scalar
_dx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumulative_trapezoid(
    *$(at::Tensor* _y)
  , *$(at::Scalar* _dx)));
  }|]

cumulative_trapezoid_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
cumulative_trapezoid_t :: Ptr Tensor -> IO (Ptr Tensor)
cumulative_trapezoid_t Ptr Tensor
_y =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cumulative_trapezoid(
    *$(at::Tensor* _y)));
  }|]

ctc_loss_ttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
ctc_loss_ttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Int64
-> CBool
-> IO (Ptr Tensor)
ctc_loss_ttllllb Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Int64
_blank Int64
_reduction CBool
_zero_infinity =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , $(int64_t _blank)
  , $(int64_t _reduction)
  , $(bool _zero_infinity)));
  }|]

ctc_loss_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
ctc_loss_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Int64
-> IO (Ptr Tensor)
ctc_loss_ttllll Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Int64
_blank Int64
_reduction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , $(int64_t _blank)
  , $(int64_t _reduction)));
  }|]

ctc_loss_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
ctc_loss_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
ctc_loss_ttlll Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Int64
_blank =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , $(int64_t _blank)));
  }|]

ctc_loss_ttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
ctc_loss_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
ctc_loss_ttll Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)));
  }|]

ctc_loss_ttttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
ctc_loss_ttttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CBool
-> IO (Ptr Tensor)
ctc_loss_ttttllb Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr Tensor
_input_lengths Ptr Tensor
_target_lengths Int64
_blank Int64
_reduction CBool
_zero_infinity =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)
  , $(int64_t _blank)
  , $(int64_t _reduction)
  , $(bool _zero_infinity)));
  }|]

ctc_loss_ttttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
ctc_loss_ttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
ctc_loss_ttttll Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr Tensor
_input_lengths Ptr Tensor
_target_lengths Int64
_blank Int64
_reduction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)
  , $(int64_t _blank)
  , $(int64_t _reduction)));
  }|]

ctc_loss_ttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
ctc_loss_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
ctc_loss_ttttl Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr Tensor
_input_lengths Ptr Tensor
_target_lengths Int64
_blank =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)
  , $(int64_t _blank)));
  }|]

ctc_loss_tttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
ctc_loss_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ctc_loss_tttt Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr Tensor
_input_lengths Ptr Tensor
_target_lengths =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)));
  }|]

_ctc_loss_ttlllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_ttlllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_ttlllb Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Int64
_blank CBool
_zero_infinity =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , $(int64_t _blank)
  , $(bool _zero_infinity)));
  }|]

_ctc_loss_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_ttlll Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Int64
_blank =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , $(int64_t _blank)));
  }|]

_ctc_loss_ttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_ttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_ttll Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_ctc_loss(
    *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)));
  }|]

_ctc_loss_backward_tttllttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
_ctc_loss_backward_tttllttlb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr Tensor)
_ctc_loss_backward_tttllttlb Ptr Tensor
_grad Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Ptr Tensor
_neg_log_likelihood Ptr Tensor
_log_alpha Int64
_blank CBool
_zero_infinity =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_ctc_loss_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , *$(at::Tensor* _neg_log_likelihood)
  , *$(at::Tensor* _log_alpha)
  , $(int64_t _blank)
  , $(bool _zero_infinity)));
  }|]

_ctc_loss_backward_tttllttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_ctc_loss_backward_tttllttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_ctc_loss_backward_tttllttl Ptr Tensor
_grad Ptr Tensor
_log_probs Ptr Tensor
_targets Ptr IntArray
_input_lengths Ptr IntArray
_target_lengths Ptr Tensor
_neg_log_likelihood Ptr Tensor
_log_alpha Int64
_blank =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_ctc_loss_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , *$(at::Tensor* _neg_log_likelihood)
  , *$(at::Tensor* _log_alpha)
  , $(int64_t _blank)));
  }|]

diag_embed_tlll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diag_embed_tlll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
diag_embed_tlll Ptr Tensor
_self Int64
_offset Int64
_dim1 Int64
_dim2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_embed(
    *$(at::Tensor* _self)
  , $(int64_t _offset)
  , $(int64_t _dim1)
  , $(int64_t _dim2)));
  }|]

diag_embed_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diag_embed_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
diag_embed_tll Ptr Tensor
_self Int64
_offset Int64
_dim1 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_embed(
    *$(at::Tensor* _self)
  , $(int64_t _offset)
  , $(int64_t _dim1)));
  }|]

diag_embed_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
diag_embed_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diag_embed_tl Ptr Tensor
_self Int64
_offset =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_embed(
    *$(at::Tensor* _self)
  , $(int64_t _offset)));
  }|]

diag_embed_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
diag_embed_t :: Ptr Tensor -> IO (Ptr Tensor)
diag_embed_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diag_embed(
    *$(at::Tensor* _self)));
  }|]

diagflat_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
diagflat_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diagflat_tl Ptr Tensor
_self Int64
_offset =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagflat(
    *$(at::Tensor* _self)
  , $(int64_t _offset)));
  }|]

diagflat_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
diagflat_t :: Ptr Tensor -> IO (Ptr Tensor)
diagflat_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagflat(
    *$(at::Tensor* _self)));
  }|]

diagonal_tlll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diagonal_tlll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
diagonal_tlll Ptr Tensor
_self Int64
_offset Int64
_dim1 Int64
_dim2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal(
    *$(at::Tensor* _self)
  , $(int64_t _offset)
  , $(int64_t _dim1)
  , $(int64_t _dim2)));
  }|]

diagonal_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diagonal_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
diagonal_tll Ptr Tensor
_self Int64
_offset Int64
_dim1 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal(
    *$(at::Tensor* _self)
  , $(int64_t _offset)
  , $(int64_t _dim1)));
  }|]

diagonal_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
diagonal_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diagonal_tl Ptr Tensor
_self Int64
_offset =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal(
    *$(at::Tensor* _self)
  , $(int64_t _offset)));
  }|]

diagonal_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
diagonal_t :: Ptr Tensor -> IO (Ptr Tensor)
diagonal_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal(
    *$(at::Tensor* _self)));
  }|]

linalg_diagonal_tlll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
linalg_diagonal_tlll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
linalg_diagonal_tlll Ptr Tensor
_A Int64
_offset Int64
_dim1 Int64
_dim2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_diagonal(
    *$(at::Tensor* _A)
  , $(int64_t _offset)
  , $(int64_t _dim1)
  , $(int64_t _dim2)));
  }|]

linalg_diagonal_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
linalg_diagonal_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
linalg_diagonal_tll Ptr Tensor
_A Int64
_offset Int64
_dim1 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_diagonal(
    *$(at::Tensor* _A)
  , $(int64_t _offset)
  , $(int64_t _dim1)));
  }|]

linalg_diagonal_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
linalg_diagonal_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
linalg_diagonal_tl Ptr Tensor
_A Int64
_offset =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_diagonal(
    *$(at::Tensor* _A)
  , $(int64_t _offset)));
  }|]

linalg_diagonal_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
linalg_diagonal_t :: Ptr Tensor -> IO (Ptr Tensor)
linalg_diagonal_t Ptr Tensor
_A =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_diagonal(
    *$(at::Tensor* _A)));
  }|]

diagonal_tnnnl
  :: Ptr Tensor
  -> Ptr Dimname
  -> Ptr Dimname
  -> Ptr Dimname
  -> Int64
  -> IO (Ptr Tensor)
diagonal_tnnnl :: Ptr Tensor
-> Ptr Dimname
-> Ptr Dimname
-> Ptr Dimname
-> Int64
-> IO (Ptr Tensor)
diagonal_tnnnl Ptr Tensor
_self Ptr Dimname
_outdim Ptr Dimname
_dim1 Ptr Dimname
_dim2 Int64
_offset =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _outdim)
  , *$(at::Dimname* _dim1)
  , *$(at::Dimname* _dim2)
  , $(int64_t _offset)));
  }|]

diagonal_tnnn
  :: Ptr Tensor
  -> Ptr Dimname
  -> Ptr Dimname
  -> Ptr Dimname
  -> IO (Ptr Tensor)
diagonal_tnnn :: Ptr Tensor
-> Ptr Dimname -> Ptr Dimname -> Ptr Dimname -> IO (Ptr Tensor)
diagonal_tnnn Ptr Tensor
_self Ptr Dimname
_outdim Ptr Dimname
_dim1 Ptr Dimname
_dim2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _outdim)
  , *$(at::Dimname* _dim1)
  , *$(at::Dimname* _dim2)));
  }|]

diagonal_backward_tllll
  :: Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diagonal_backward_tllll :: Ptr Tensor
-> Ptr IntArray -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
diagonal_backward_tllll Ptr Tensor
_grad_output Ptr IntArray
_input_sizes Int64
_offset Int64
_dim1 Int64
_dim2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diagonal_backward(
    *$(at::Tensor* _grad_output)
  , *$(std::vector<int64_t>* _input_sizes)
  , $(int64_t _offset)
  , $(int64_t _dim1)
  , $(int64_t _dim2)));
  }|]

diff_tlltt
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
diff_tlltt :: Ptr Tensor
-> Int64 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
diff_tlltt Ptr Tensor
_self Int64
_n Int64
_dim Ptr Tensor
_prepend Ptr Tensor
_append =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff(
    *$(at::Tensor* _self)
  , $(int64_t _n)
  , $(int64_t _dim)
  , *$(at::Tensor* _prepend)
  , *$(at::Tensor* _append)));
  }|]

diff_tllt
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
diff_tllt :: Ptr Tensor -> Int64 -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
diff_tllt Ptr Tensor
_self Int64
_n Int64
_dim Ptr Tensor
_prepend =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff(
    *$(at::Tensor* _self)
  , $(int64_t _n)
  , $(int64_t _dim)
  , *$(at::Tensor* _prepend)));
  }|]

diff_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diff_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
diff_tll Ptr Tensor
_self Int64
_n Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff(
    *$(at::Tensor* _self)
  , $(int64_t _n)
  , $(int64_t _dim)));
  }|]

diff_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
diff_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diff_tl Ptr Tensor
_self Int64
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff(
    *$(at::Tensor* _self)
  , $(int64_t _n)));
  }|]

diff_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
diff_t :: Ptr Tensor -> IO (Ptr Tensor)
diff_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff(
    *$(at::Tensor* _self)));
  }|]

diff_out_ttlltt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
diff_out_ttlltt :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
diff_out_ttlltt Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim Ptr Tensor
_prepend Ptr Tensor
_append =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _n)
  , $(int64_t _dim)
  , *$(at::Tensor* _prepend)
  , *$(at::Tensor* _append)));
  }|]

diff_out_ttllt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
diff_out_ttllt :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
diff_out_ttllt Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim Ptr Tensor
_prepend =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _n)
  , $(int64_t _dim)
  , *$(at::Tensor* _prepend)));
  }|]

diff_out_ttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diff_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
diff_out_ttll Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _n)
  , $(int64_t _dim)));
  }|]

diff_out_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
diff_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
diff_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _n)));
  }|]

diff_out_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
diff_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
diff_out_tt Ptr Tensor
_out Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::diff_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)));
  }|]

gradient_tsll
  :: Ptr Tensor
  -> Ptr Scalar
  -> Int64
  -> Int64
  -> IO (Ptr TensorList)
gradient_tsll :: Ptr Tensor -> Ptr Scalar -> Int64 -> Int64 -> IO (Ptr TensorList)
gradient_tsll Ptr Tensor
_self Ptr Scalar
_spacing Int64
_dim Int64
_edge_order =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::gradient(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _spacing)
  , $(int64_t _dim)
  , $(int64_t _edge_order)));
  }|]

gradient_tsl
  :: Ptr Tensor
  -> Ptr Scalar
  -> Int64
  -> IO (Ptr TensorList)
gradient_tsl :: Ptr Tensor -> Ptr Scalar -> Int64 -> IO (Ptr TensorList)
gradient_tsl Ptr Tensor
_self Ptr Scalar
_spacing Int64
_dim =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::gradient(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _spacing)
  , $(int64_t _dim)));
  }|]

gradient_t
  :: Ptr Tensor
  -> IO (Ptr TensorList)
gradient_t :: Ptr Tensor -> IO (Ptr TensorList)
gradient_t Ptr Tensor
_self =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::gradient(
    *$(at::Tensor* _self)));
  }|]

gradient_tll
  :: Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr TensorList)
gradient_tll :: Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr TensorList)
gradient_tll Ptr Tensor
_self Ptr IntArray
_dim Int64
_edge_order =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::gradient(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(int64_t _edge_order)));
  }|]

gradient_tl
  :: Ptr Tensor
  -> Ptr IntArray
  -> IO (Ptr TensorList)
gradient_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr TensorList)
gradient_tl Ptr Tensor
_self Ptr IntArray
_dim =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::gradient(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)));
  }|]

gradient_tA
  :: Ptr Tensor
  -> Ptr (StdVector Scalar)
  -> IO (Ptr TensorList)
gradient_tA :: Ptr Tensor -> Ptr (StdVector Scalar) -> IO (Ptr TensorList)
gradient_tA Ptr Tensor
_self Ptr (StdVector Scalar)
_spacing =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::gradient(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Scalar>* _spacing)));
  }|]

div_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
div_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
div_tt Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::div(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

div_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
div_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
div_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::div_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

div_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> IO (Ptr Tensor)
div_tts :: Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor)
div_tts Ptr Tensor
_self Ptr Tensor
_other Ptr StdString
_rounding_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::div(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::string* _rounding_mode)));
  }|]

div_out_ttts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> IO (Ptr Tensor)
div_out_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor)
div_out_ttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other Ptr StdString
_rounding_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::div_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::string* _rounding_mode)));
  }|]

div_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
div_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
div_ts Ptr Tensor
_self Ptr Scalar
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::div(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _other)));
  }|]

div_tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr StdString
  -> IO (Ptr Tensor)
div_tss :: Ptr Tensor -> Ptr Scalar -> Ptr StdString -> IO (Ptr Tensor)
div_tss Ptr Tensor
_self Ptr Scalar
_other Ptr StdString
_rounding_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::div(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _other)
  , *$(std::string* _rounding_mode)));
  }|]

divide_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
divide_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
divide_tt Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::divide(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

divide_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
divide_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
divide_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::divide_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

divide_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
divide_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
divide_ts Ptr Tensor
_self Ptr Scalar
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::divide(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _other)));
  }|]

divide_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> IO (Ptr Tensor)
divide_tts :: Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor)
divide_tts Ptr Tensor
_self Ptr Tensor
_other Ptr StdString
_rounding_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::divide(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::string* _rounding_mode)));
  }|]

divide_out_ttts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> IO (Ptr Tensor)
divide_out_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor)
divide_out_ttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other Ptr StdString
_rounding_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::divide_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::string* _rounding_mode)));
  }|]

divide_tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr StdString
  -> IO (Ptr Tensor)
divide_tss :: Ptr Tensor -> Ptr Scalar -> Ptr StdString -> IO (Ptr Tensor)
divide_tss Ptr Tensor
_self Ptr Scalar
_other Ptr StdString
_rounding_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::divide(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _other)
  , *$(std::string* _rounding_mode)));
  }|]

true_divide_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
true_divide_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
true_divide_tt Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::true_divide(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

true_divide_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
true_divide_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
true_divide_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::true_divide_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

true_divide_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
true_divide_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
true_divide_ts Ptr Tensor
_self Ptr Scalar
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::true_divide(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _other)));
  }|]

dot_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
dot_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
dot_tt Ptr Tensor
_self Ptr Tensor
_tensor =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::dot(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _tensor)));
  }|]

dot_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
dot_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
dot_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_tensor =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::dot_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _tensor)));
  }|]

vdot_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
vdot_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
vdot_tt Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::vdot(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

vdot_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
vdot_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
vdot_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::vdot_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)));
  }|]

einsum_sl
  :: Ptr StdString
  -> Ptr TensorList
  -> IO (Ptr Tensor)
einsum_sl :: Ptr StdString -> Ptr TensorList -> IO (Ptr Tensor)
einsum_sl Ptr StdString
_equation Ptr TensorList
_tensors =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::einsum(
    *$(std::string* _equation)
  , *$(std::vector<at::Tensor>* _tensors)));
  }|]

embedding_ttlbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
embedding_ttlbb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> CBool -> CBool -> IO (Ptr Tensor)
embedding_ttlbb Ptr Tensor
_weight Ptr Tensor
_indices Int64
_padding_idx CBool
_scale_grad_by_freq CBool
_sparse =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , $(int64_t _padding_idx)
  , $(bool _scale_grad_by_freq)
  , $(bool _sparse)));
  }|]

embedding_ttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
embedding_ttlb :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor)
embedding_ttlb Ptr Tensor
_weight Ptr Tensor
_indices Int64
_padding_idx CBool
_scale_grad_by_freq =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , $(int64_t _padding_idx)
  , $(bool _scale_grad_by_freq)));
  }|]

embedding_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
embedding_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
embedding_ttl Ptr Tensor
_weight Ptr Tensor
_indices Int64
_padding_idx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , $(int64_t _padding_idx)));
  }|]

embedding_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
embedding_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
embedding_tt Ptr Tensor
_weight Ptr Tensor
_indices =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)));
  }|]

embedding_backward_ttllbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
embedding_backward_ttllbb :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
embedding_backward_ttllbb Ptr Tensor
_grad Ptr Tensor
_indices Int64
_num_weights Int64
_padding_idx CBool
_scale_grad_by_freq CBool
_sparse =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , $(int64_t _num_weights)
  , $(int64_t _padding_idx)
  , $(bool _scale_grad_by_freq)
  , $(bool _sparse)));
  }|]

embedding_dense_backward_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
embedding_dense_backward_ttllb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> CBool -> IO (Ptr Tensor)
embedding_dense_backward_ttllb Ptr Tensor
_grad_output Ptr Tensor
_indices Int64
_num_weights Int64
_padding_idx CBool
_scale_grad_by_freq =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding_dense_backward(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _indices)
  , $(int64_t _num_weights)
  , $(int64_t _padding_idx)
  , $(bool _scale_grad_by_freq)));
  }|]

embedding_renorm__ttdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
embedding_renorm__ttdd :: Ptr Tensor -> Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
embedding_renorm__ttdd Ptr Tensor
_self Ptr Tensor
_indices CDouble
_max_norm CDouble
_norm_type =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding_renorm_(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _indices)
  , $(double _max_norm)
  , $(double _norm_type)));
  }|]

embedding_sparse_backward_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
embedding_sparse_backward_ttllb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> CBool -> IO (Ptr Tensor)
embedding_sparse_backward_ttllb Ptr Tensor
_grad Ptr Tensor
_indices Int64
_num_weights Int64
_padding_idx CBool
_scale_grad_by_freq =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::embedding_sparse_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , $(int64_t _num_weights)
  , $(int64_t _padding_idx)
  , $(bool _scale_grad_by_freq)));
  }|]

_embedding_bag_forward_only_tttblbtbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_tttblbtbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_tttblbtbl Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights CBool
_include_last_offset Int64
_padding_idx =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(bool _include_last_offset)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_forward_only_tttblbtb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_tttblbtb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_tttblbtb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights CBool
_include_last_offset =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(bool _include_last_offset)));
  }|]

_embedding_bag_forward_only_tttblbt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_tttblbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_tttblbt Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)));
  }|]

_embedding_bag_forward_only_tttblb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_tttblb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_tttblb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)));
  }|]

_embedding_bag_forward_only_tttbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_tttbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_tttbl Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)));
  }|]

_embedding_bag_forward_only_tttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_tttb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)));
  }|]

_embedding_bag_forward_only_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_forward_only_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_forward_only_ttt Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag_forward_only(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)));
  }|]

_rowwise_prune_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> ScalarType
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_rowwise_prune_tts :: Ptr Tensor
-> Ptr Tensor
-> ScalarType
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_rowwise_prune_tts Ptr Tensor
_weight Ptr Tensor
_mask ScalarType
_compressed_indices_dtype =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_rowwise_prune(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _mask)
  , $(at::ScalarType _compressed_indices_dtype)));
  }|]

row_stack_l
  :: Ptr TensorList
  -> IO (Ptr Tensor)
row_stack_l :: Ptr TensorList -> IO (Ptr Tensor)
row_stack_l Ptr TensorList
_tensors =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::row_stack(
    *$(std::vector<at::Tensor>* _tensors)));
  }|]

row_stack_out_tl
  :: Ptr Tensor
  -> Ptr TensorList
  -> IO (Ptr Tensor)
row_stack_out_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor)
row_stack_out_tl Ptr Tensor
_out Ptr TensorList
_tensors =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::row_stack_out(
    *$(at::Tensor* _out)
  , *$(std::vector<at::Tensor>* _tensors)));
  }|]

embedding_bag_tttblbtb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_tttblbtb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_tttblbtb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights CBool
_include_last_offset =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(bool _include_last_offset)));
  }|]

embedding_bag_tttblbt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_tttblbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_tttblbt Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)));
  }|]

embedding_bag_tttblb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_tttblb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_tttblb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)));
  }|]

embedding_bag_tttbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_tttbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_tttbl Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)));
  }|]

embedding_bag_tttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_tttb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)));
  }|]

embedding_bag_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_ttt Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)));
  }|]

embedding_bag_tttblbtbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
embedding_bag_tttblbtbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
embedding_bag_tttblbtbl Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights CBool
_include_last_offset Int64
_padding_idx =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(bool _include_last_offset)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_tttblbtbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_tttblbtbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_tttblbtbl Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights CBool
_include_last_offset Int64
_padding_idx =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(bool _include_last_offset)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_tttblbtb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_tttblbtb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_tttblbtb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights CBool
_include_last_offset =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(bool _include_last_offset)));
  }|]

_embedding_bag_tttblbt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_tttblbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_tttblbt Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)));
  }|]

_embedding_bag_tttblb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_tttblb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_tttblb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)));
  }|]

_embedding_bag_tttbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_tttbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_tttbl Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq Int64
_mode =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)));
  }|]

_embedding_bag_tttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_tttb Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets CBool
_scale_grad_by_freq =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(bool _scale_grad_by_freq)));
  }|]

_embedding_bag_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
_embedding_bag_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
_embedding_bag_ttt Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_embedding_bag(
    *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)));
  }|]

_embedding_bag_backward_ttttttlblbtl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_embedding_bag_backward_ttttttlblbtl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_embedding_bag_backward_ttttttlblbtl Ptr Tensor
_grad Ptr Tensor
_indices Ptr Tensor
_offsets Ptr Tensor
_offset2bag Ptr Tensor
_bag_size Ptr Tensor
_maximum_indices Int64
_num_weights CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights Int64
_padding_idx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , *$(at::Tensor* _offset2bag)
  , *$(at::Tensor* _bag_size)
  , *$(at::Tensor* _maximum_indices)
  , $(int64_t _num_weights)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_backward_ttttttlblbt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Int64
  -> CBool
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_embedding_bag_backward_ttttttlblbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Int64
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
_embedding_bag_backward_ttttttlblbt Ptr Tensor
_grad Ptr Tensor
_indices Ptr Tensor
_offsets Ptr Tensor
_offset2bag Ptr Tensor
_bag_size Ptr Tensor
_maximum_indices Int64
_num_weights CBool
_scale_grad_by_freq Int64
_mode CBool
_sparse Ptr Tensor
_per_sample_weights =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , *$(at::Tensor* _offset2bag)
  , *$(at::Tensor* _bag_size)
  , *$(at::Tensor* _maximum_indices)
  , $(int64_t _num_weights)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , $(bool _sparse)
  , *$(at::Tensor* _per_sample_weights)));
  }|]

_embedding_bag_sparse_backward_tttttlbltl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Int64
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_embedding_bag_sparse_backward_tttttlbltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Int64
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_embedding_bag_sparse_backward_tttttlbltl Ptr Tensor
_grad Ptr Tensor
_indices Ptr Tensor
_offsets Ptr Tensor
_offset2bag Ptr Tensor
_bag_size Int64
_num_weights CBool
_scale_grad_by_freq Int64
_mode Ptr Tensor
_per_sample_weights Int64
_padding_idx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_sparse_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , *$(at::Tensor* _offset2bag)
  , *$(at::Tensor* _bag_size)
  , $(int64_t _num_weights)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , *$(at::Tensor* _per_sample_weights)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_sparse_backward_tttttlblt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_embedding_bag_sparse_backward_tttttlblt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
_embedding_bag_sparse_backward_tttttlblt Ptr Tensor
_grad Ptr Tensor
_indices Ptr Tensor
_offsets Ptr Tensor
_offset2bag Ptr Tensor
_bag_size Int64
_num_weights CBool
_scale_grad_by_freq Int64
_mode Ptr Tensor
_per_sample_weights =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_sparse_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , *$(at::Tensor* _offset2bag)
  , *$(at::Tensor* _bag_size)
  , $(int64_t _num_weights)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , *$(at::Tensor* _per_sample_weights)));
  }|]

_embedding_bag_dense_backward_tttttlbltl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Int64
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_embedding_bag_dense_backward_tttttlbltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Int64
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_embedding_bag_dense_backward_tttttlbltl Ptr Tensor
_grad Ptr Tensor
_indices Ptr Tensor
_offset2bag Ptr Tensor
_bag_size Ptr Tensor
_maximum_indices Int64
_num_weights CBool
_scale_grad_by_freq Int64
_mode Ptr Tensor
_per_sample_weights Int64
_padding_idx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_dense_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offset2bag)
  , *$(at::Tensor* _bag_size)
  , *$(at::Tensor* _maximum_indices)
  , $(int64_t _num_weights)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , *$(at::Tensor* _per_sample_weights)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_dense_backward_tttttlblt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_embedding_bag_dense_backward_tttttlblt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
_embedding_bag_dense_backward_tttttlblt Ptr Tensor
_grad Ptr Tensor
_indices Ptr Tensor
_offset2bag Ptr Tensor
_bag_size Ptr Tensor
_maximum_indices Int64
_num_weights CBool
_scale_grad_by_freq Int64
_mode Ptr Tensor
_per_sample_weights =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_dense_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offset2bag)
  , *$(at::Tensor* _bag_size)
  , *$(at::Tensor* _maximum_indices)
  , $(int64_t _num_weights)
  , $(bool _scale_grad_by_freq)
  , $(int64_t _mode)
  , *$(at::Tensor* _per_sample_weights)));
  }|]

_embedding_bag_per_sample_weights_backward_tttttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
_embedding_bag_per_sample_weights_backward_tttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
_embedding_bag_per_sample_weights_backward_tttttll Ptr Tensor
_grad Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets Ptr Tensor
_offset2bag Int64
_mode Int64
_padding_idx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_per_sample_weights_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , *$(at::Tensor* _offset2bag)
  , $(int64_t _mode)
  , $(int64_t _padding_idx)));
  }|]

_embedding_bag_per_sample_weights_backward_tttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_embedding_bag_per_sample_weights_backward_tttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_embedding_bag_per_sample_weights_backward_tttttl Ptr Tensor
_grad Ptr Tensor
_weight Ptr Tensor
_indices Ptr Tensor
_offsets Ptr Tensor
_offset2bag Int64
_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_embedding_bag_per_sample_weights_backward(
    *$(at::Tensor* _grad)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , *$(at::Tensor* _offset2bag)
  , $(int64_t _mode)));
  }|]

empty_lNoM
  :: Ptr IntArray
  -> Ptr DimnameList
  -> Ptr TensorOptions
  -> MemoryFormat
  -> IO (Ptr Tensor)
empty_lNoM :: Ptr IntArray
-> Ptr DimnameList
-> Ptr TensorOptions
-> ScalarType
-> IO (Ptr Tensor)
empty_lNoM Ptr IntArray
_size Ptr DimnameList
_names Ptr TensorOptions
_options ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty(
    *$(std::vector<int64_t>* _size)
  , *$(std::vector<at::Dimname>* _names)
  , *$(at::TensorOptions* _options)
  , $(at::MemoryFormat _memory_format)));
  }|]

empty_lNo
  :: Ptr IntArray
  -> Ptr DimnameList
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
empty_lNo :: Ptr IntArray
-> Ptr DimnameList -> Ptr TensorOptions -> IO (Ptr Tensor)
empty_lNo Ptr IntArray
_size Ptr DimnameList
_names Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty(
    *$(std::vector<int64_t>* _size)
  , *$(std::vector<at::Dimname>* _names)
  , *$(at::TensorOptions* _options)));
  }|]

empty_lN
  :: Ptr IntArray
  -> Ptr DimnameList
  -> IO (Ptr Tensor)
empty_lN :: Ptr IntArray -> Ptr DimnameList -> IO (Ptr Tensor)
empty_lN Ptr IntArray
_size Ptr DimnameList
_names =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty(
    *$(std::vector<int64_t>* _size)
  , *$(std::vector<at::Dimname>* _names)));
  }|]

empty_loM
  :: Ptr IntArray
  -> Ptr TensorOptions
  -> MemoryFormat
  -> IO (Ptr Tensor)
empty_loM :: Ptr IntArray -> Ptr TensorOptions -> ScalarType -> IO (Ptr Tensor)
empty_loM Ptr IntArray
_size Ptr TensorOptions
_options ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty(
    *$(std::vector<int64_t>* _size)
  , *$(at::TensorOptions* _options)
  , $(at::MemoryFormat _memory_format)));
  }|]

empty_lo
  :: Ptr IntArray
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
empty_lo :: Ptr IntArray -> Ptr TensorOptions -> IO (Ptr Tensor)
empty_lo Ptr IntArray
_size Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty(
    *$(std::vector<int64_t>* _size)
  , *$(at::TensorOptions* _options)));
  }|]

empty_l
  :: Ptr IntArray
  -> IO (Ptr Tensor)
empty_l :: Ptr IntArray -> IO (Ptr Tensor)
empty_l Ptr IntArray
_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty(
    *$(std::vector<int64_t>* _size)));
  }|]

_empty_affine_quantized_lodlM
  :: Ptr IntArray
  -> Ptr TensorOptions
  -> CDouble
  -> Int64
  -> MemoryFormat
  -> IO (Ptr Tensor)
_empty_affine_quantized_lodlM :: Ptr IntArray
-> Ptr TensorOptions
-> CDouble
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
_empty_affine_quantized_lodlM Ptr IntArray
_size Ptr TensorOptions
_options CDouble
_scale Int64
_zero_point ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::TensorOptions* _options)
  , $(double _scale)
  , $(int64_t _zero_point)
  , $(at::MemoryFormat _memory_format)));
  }|]

_empty_affine_quantized_lodl
  :: Ptr IntArray
  -> Ptr TensorOptions
  -> CDouble
  -> Int64
  -> IO (Ptr Tensor)
_empty_affine_quantized_lodl :: Ptr IntArray
-> Ptr TensorOptions -> CDouble -> Int64 -> IO (Ptr Tensor)
_empty_affine_quantized_lodl Ptr IntArray
_size Ptr TensorOptions
_options CDouble
_scale Int64
_zero_point =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::TensorOptions* _options)
  , $(double _scale)
  , $(int64_t _zero_point)));
  }|]

_empty_affine_quantized_lod
  :: Ptr IntArray
  -> Ptr TensorOptions
  -> CDouble
  -> IO (Ptr Tensor)
_empty_affine_quantized_lod :: Ptr IntArray -> Ptr TensorOptions -> CDouble -> IO (Ptr Tensor)
_empty_affine_quantized_lod Ptr IntArray
_size Ptr TensorOptions
_options CDouble
_scale =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::TensorOptions* _options)
  , $(double _scale)));
  }|]

_empty_affine_quantized_lo
  :: Ptr IntArray
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
_empty_affine_quantized_lo :: Ptr IntArray -> Ptr TensorOptions -> IO (Ptr Tensor)
_empty_affine_quantized_lo Ptr IntArray
_size Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::TensorOptions* _options)));
  }|]

_empty_affine_quantized_l
  :: Ptr IntArray
  -> IO (Ptr Tensor)
_empty_affine_quantized_l :: Ptr IntArray -> IO (Ptr Tensor)
_empty_affine_quantized_l Ptr IntArray
_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_affine_quantized(
    *$(std::vector<int64_t>* _size)));
  }|]

_empty_per_channel_affine_quantized_lttloM
  :: Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Ptr TensorOptions
  -> MemoryFormat
  -> IO (Ptr Tensor)
_empty_per_channel_affine_quantized_lttloM :: Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr TensorOptions
-> ScalarType
-> IO (Ptr Tensor)
_empty_per_channel_affine_quantized_lttloM Ptr IntArray
_size Ptr Tensor
_scales Ptr Tensor
_zero_points Int64
_axis Ptr TensorOptions
_options ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_per_channel_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::Tensor* _scales)
  , *$(at::Tensor* _zero_points)
  , $(int64_t _axis)
  , *$(at::TensorOptions* _options)
  , $(at::MemoryFormat _memory_format)));
  }|]

_empty_per_channel_affine_quantized_lttlo
  :: Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
_empty_per_channel_affine_quantized_lttlo :: Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr TensorOptions
-> IO (Ptr Tensor)
_empty_per_channel_affine_quantized_lttlo Ptr IntArray
_size Ptr Tensor
_scales Ptr Tensor
_zero_points Int64
_axis Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_per_channel_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::Tensor* _scales)
  , *$(at::Tensor* _zero_points)
  , $(int64_t _axis)
  , *$(at::TensorOptions* _options)));
  }|]

_empty_per_channel_affine_quantized_lttl
  :: Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_empty_per_channel_affine_quantized_lttl :: Ptr IntArray
-> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
_empty_per_channel_affine_quantized_lttl Ptr IntArray
_size Ptr Tensor
_scales Ptr Tensor
_zero_points Int64
_axis =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_empty_per_channel_affine_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::Tensor* _scales)
  , *$(at::Tensor* _zero_points)
  , $(int64_t _axis)));
  }|]

empty_quantized_ltoM
  :: Ptr IntArray
  -> Ptr Tensor
  -> Ptr TensorOptions
  -> MemoryFormat
  -> IO (Ptr Tensor)
empty_quantized_ltoM :: Ptr IntArray
-> Ptr Tensor -> Ptr TensorOptions -> ScalarType -> IO (Ptr Tensor)
empty_quantized_ltoM Ptr IntArray
_size Ptr Tensor
_qtensor Ptr TensorOptions
_options ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::Tensor* _qtensor)
  , *$(at::TensorOptions* _options)
  , $(at::MemoryFormat _memory_format)));
  }|]

empty_quantized_lto
  :: Ptr IntArray
  -> Ptr Tensor
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
empty_quantized_lto :: Ptr IntArray -> Ptr Tensor -> Ptr TensorOptions -> IO (Ptr Tensor)
empty_quantized_lto Ptr IntArray
_size Ptr Tensor
_qtensor Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::Tensor* _qtensor)
  , *$(at::TensorOptions* _options)));
  }|]

empty_quantized_lt
  :: Ptr IntArray
  -> Ptr Tensor
  -> IO (Ptr Tensor)
empty_quantized_lt :: Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
empty_quantized_lt Ptr IntArray
_size Ptr Tensor
_qtensor =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_quantized(
    *$(std::vector<int64_t>* _size)
  , *$(at::Tensor* _qtensor)));
  }|]

empty_out_tlM
  :: Ptr Tensor
  -> Ptr IntArray
  -> MemoryFormat
  -> IO (Ptr Tensor)
empty_out_tlM :: Ptr Tensor -> Ptr IntArray -> ScalarType -> IO (Ptr Tensor)
empty_out_tlM Ptr Tensor
_out Ptr IntArray
_size ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_out(
    *$(at::Tensor* _out)
  , *$(std::vector<int64_t>* _size)
  , $(at::MemoryFormat _memory_format)));
  }|]

empty_out_tl
  :: Ptr Tensor
  -> Ptr IntArray
  -> IO (Ptr Tensor)
empty_out_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
empty_out_tl Ptr Tensor
_out Ptr IntArray
_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_out(
    *$(at::Tensor* _out)
  , *$(std::vector<int64_t>* _size)));
  }|]

empty_like_toM
  :: Ptr Tensor
  -> Ptr TensorOptions
  -> MemoryFormat
  -> IO (Ptr Tensor)
empty_like_toM :: Ptr Tensor -> Ptr TensorOptions -> ScalarType -> IO (Ptr Tensor)
empty_like_toM Ptr Tensor
_self Ptr TensorOptions
_options ScalarType
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_like(
    *$(at::Tensor* _self)
  , *$(at::TensorOptions* _options)
  , $(at::MemoryFormat _memory_format)));
  }|]

empty_like_to
  :: Ptr Tensor
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
empty_like_to :: Ptr Tensor -> Ptr TensorOptions -> IO (Ptr Tensor)
empty_like_to Ptr Tensor
_self Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_like(
    *$(at::Tensor* _self)
  , *$(at::TensorOptions* _options)));
  }|]

empty_like_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
empty_like_t :: Ptr Tensor -> IO (Ptr Tensor)
empty_like_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_like(
    *$(at::Tensor* _self)));
  }|]

empty_strided_llo
  :: Ptr IntArray
  -> Ptr IntArray
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
empty_strided_llo :: Ptr IntArray
-> Ptr IntArray -> Ptr TensorOptions -> IO (Ptr Tensor)
empty_strided_llo Ptr IntArray
_size Ptr IntArray
_stride Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_strided(
    *$(std::vector<int64_t>* _size)
  , *$(std::vector<int64_t>* _stride)
  , *$(at::TensorOptions* _options)));
  }|]

empty_strided_ll
  :: Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
empty_strided_ll :: Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
empty_strided_ll Ptr IntArray
_size Ptr IntArray
_stride =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::empty_strided(
    *$(std::vector<int64_t>* _size)
  , *$(std::vector<int64_t>* _stride)));
  }|]

erf_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
erf_t :: Ptr Tensor -> IO (Ptr Tensor)
erf_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::erf(
    *$(at::Tensor* _self)));
  }|]

erf__t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
erf__t :: Ptr Tensor -> IO (Ptr Tensor)
erf__t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::erf_(
    *$(at::Tensor* _self)));
  }|]

erf_out_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
erf_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
erf_out_tt Ptr Tensor
_out Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::erf_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)));
  }|]

erfc_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
erfc_t :: Ptr Tensor -> IO (Ptr Tensor)
erfc_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::erfc(
    *$(at::Tensor* _self)));
  }|]

erfc__t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
erfc__t :: Ptr Tensor -> IO (Ptr Tensor)
erfc__t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::erfc_(
    *$(at::Tensor* _self)));
  }|]

erfc_out_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
erfc_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
erfc_out_tt Ptr Tensor
_out Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::erfc_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)));
  }|]

exp_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
exp_t :: Ptr Tensor -> IO (Ptr Tensor)
exp_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::exp(
    *$(at::Tensor* _self)));
  }|]

exp__t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
exp__t :: Ptr Tensor -> IO (Ptr Tensor)
exp__t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::exp_(
    *$(at::Tensor* _self)));
  }|]

exp_out_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
exp_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
exp_out_tt Ptr Tensor
_out Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::exp_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)));
  }|]

exp2_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
exp2_t :: Ptr Tensor -> IO (Ptr Tensor)
exp2_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::exp2(
    *$(at::Tensor* _self)));
  }|]

exp2__t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
exp2__t :: Ptr Tensor -> IO (Ptr Tensor)
exp2__t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::exp2_(
    *$(at::Tensor* _self)));
  }|]

exp2_out_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
exp2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
exp2_out_tt Ptr Tensor
_out Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::exp2_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)));
  }|]

expm1_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
expm1_t :: Ptr Tensor -> IO (Ptr Tensor)
expm1_t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::expm1(
    *$(at::Tensor* _self)));
  }|]

expm1__t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
expm1__t :: Ptr Tensor -> IO (Ptr Tensor)
expm1__t Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::expm1_(
    *$(at::Tensor* _self)));
  }|]

expm1_out_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
expm1_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
expm1_out_tt Ptr Tensor
_out Ptr Tensor
_self =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::expm1_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)));
  }|]

eye_lo
  :: Int64
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
eye_lo :: Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
eye_lo Int64
_n Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::eye(
    $(int64_t _n)
  , *$(at::TensorOptions* _options)));
  }|]

eye_l
  :: Int64
  -> IO (Ptr Tensor)
eye_l :: Int64 -> IO (Ptr Tensor)
eye_l Int64
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::eye(
    $(int64_t _n)));
  }|]

eye_llo
  :: Int64
  -> Int64
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
eye_llo :: Int64 -> Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
eye_llo Int64
_n Int64
_m Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::eye(
    $(int64_t _n)
  , $(int64_t _m)
  , *$(at::TensorOptions* _options)));
  }|]