-- generated by using spec/Declarations.yaml

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

module Torch.Internal.Unmanaged.Native.Native6 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>"


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

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

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

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

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

slice_backward_tlllll
  :: Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
slice_backward_tlllll :: Ptr Tensor
-> Ptr IntArray
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
slice_backward_tlllll Ptr Tensor
_grad_output Ptr IntArray
_input_sizes Int64
_dim Int64
_start Int64
_end Int64
_step =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::slice_backward(
    *$(at::Tensor* _grad_output)
  , *$(std::vector<int64_t>* _input_sizes)
  , $(int64_t _dim)
  , $(int64_t _start)
  , $(int64_t _end)
  , $(int64_t _step)));
  }|]

slice_scatter_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
slice_scatter_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
slice_scatter_ttllll Ptr Tensor
_self Ptr Tensor
_src Int64
_dim Int64
_start Int64
_end Int64
_step =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::slice_scatter(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _src)
  , $(int64_t _dim)
  , $(int64_t _start)
  , $(int64_t _end)
  , $(int64_t _step)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_softmax_backward_data_ttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> ScalarType
  -> IO (Ptr Tensor)
_softmax_backward_data_ttls :: Ptr Tensor -> Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
_softmax_backward_data_ttls Ptr Tensor
_grad_output Ptr Tensor
_output Int64
_dim ScalarType
_input_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_softmax_backward_data(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , $(int64_t _dim)
  , $(at::ScalarType _input_dtype)));
  }|]

_softmax_backward_data_out_tttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> ScalarType
  -> IO (Ptr Tensor)
_softmax_backward_data_out_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
_softmax_backward_data_out_tttls Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_output Int64
_dim ScalarType
_input_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_softmax_backward_data_out(
    *$(at::Tensor* _grad_input)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , $(int64_t _dim)
  , $(at::ScalarType _input_dtype)));
  }|]

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

unsafe_split_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr TensorList)
unsafe_split_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
unsafe_split_tl Ptr Tensor
_self Int64
_split_size =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::unsafe_split(
    *$(at::Tensor* _self)
  , $(int64_t _split_size)));
  }|]

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

split_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr TensorList)
split_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
split_tl Ptr Tensor
_self Int64
_split_size =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::split(
    *$(at::Tensor* _self)
  , $(int64_t _split_size)));
  }|]

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

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

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

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

hsplit_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr TensorList)
hsplit_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
hsplit_tl Ptr Tensor
_self Int64
_sections =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::hsplit(
    *$(at::Tensor* _self)
  , $(int64_t _sections)));
  }|]

vsplit_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr TensorList)
vsplit_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
vsplit_tl Ptr Tensor
_self Int64
_sections =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::vsplit(
    *$(at::Tensor* _self)
  , $(int64_t _sections)));
  }|]

dsplit_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr TensorList)
dsplit_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
dsplit_tl Ptr Tensor
_self Int64
_sections =
  [C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::dsplit(
    *$(at::Tensor* _self)
  , $(int64_t _sections)));
  }|]

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

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

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

sspaddmm_tttss
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
sspaddmm_tttss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
sspaddmm_tttss Ptr Tensor
_self Ptr Tensor
_mat1 Ptr Tensor
_mat2 Ptr Scalar
_beta Ptr Scalar
_alpha =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sspaddmm(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _mat1)
  , *$(at::Tensor* _mat2)
  , *$(at::Scalar* _beta)
  , *$(at::Scalar* _alpha)));
  }|]

sspaddmm_ttts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
sspaddmm_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
sspaddmm_ttts Ptr Tensor
_self Ptr Tensor
_mat1 Ptr Tensor
_mat2 Ptr Scalar
_beta =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sspaddmm(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _mat1)
  , *$(at::Tensor* _mat2)
  , *$(at::Scalar* _beta)));
  }|]

sspaddmm_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
sspaddmm_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
sspaddmm_ttt Ptr Tensor
_self Ptr Tensor
_mat1 Ptr Tensor
_mat2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sspaddmm(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _mat1)
  , *$(at::Tensor* _mat2)));
  }|]

sspaddmm_out_ttttss
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
sspaddmm_out_ttttss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
sspaddmm_out_ttttss Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_mat1 Ptr Tensor
_mat2 Ptr Scalar
_beta Ptr Scalar
_alpha =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sspaddmm_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _mat1)
  , *$(at::Tensor* _mat2)
  , *$(at::Scalar* _beta)
  , *$(at::Scalar* _alpha)));
  }|]

sspaddmm_out_tttts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
sspaddmm_out_tttts :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
sspaddmm_out_tttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_mat1 Ptr Tensor
_mat2 Ptr Scalar
_beta =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sspaddmm_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _mat1)
  , *$(at::Tensor* _mat2)
  , *$(at::Scalar* _beta)));
  }|]

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

stack_ll
  :: Ptr TensorList
  -> Int64
  -> IO (Ptr Tensor)
stack_ll :: Ptr TensorList -> Int64 -> IO (Ptr Tensor)
stack_ll Ptr TensorList
_tensors Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stack(
    *$(std::vector<at::Tensor>* _tensors)
  , $(int64_t _dim)));
  }|]

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

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

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

_stack_ll
  :: Ptr TensorList
  -> Int64
  -> IO (Ptr Tensor)
_stack_ll :: Ptr TensorList -> Int64 -> IO (Ptr Tensor)
_stack_ll Ptr TensorList
_tensors Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_stack(
    *$(std::vector<at::Tensor>* _tensors)
  , $(int64_t _dim)));
  }|]

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

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

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

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

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

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

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

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

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

stft_tllltbbb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
stft_tllltbbb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
stft_tllltbbb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_normalized CBool
_onesided CBool
_return_complex =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _normalized)
  , $(bool _onesided)
  , $(bool _return_complex)));
  }|]

stft_tllltbb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
stft_tllltbb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
stft_tllltbb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_normalized CBool
_onesided =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _normalized)
  , $(bool _onesided)));
  }|]

stft_tllltb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
stft_tllltb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
stft_tllltb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_normalized =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _normalized)));
  }|]

stft_tlllt
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
stft_tlllt :: Ptr Tensor
-> Int64 -> Int64 -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
stft_tlllt Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)));
  }|]

stft_tlll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
stft_tlll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
stft_tlll Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)));
  }|]

stft_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
stft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
stft_tll Ptr Tensor
_self Int64
_n_fft Int64
_hop_length =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::stft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)));
  }|]

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

istft_tllltbbblb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
istft_tllltbbblb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> CBool
-> IO (Ptr Tensor)
istft_tllltbbblb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_center CBool
_normalized CBool
_onesided Int64
_length CBool
_return_complex =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _center)
  , $(bool _normalized)
  , $(bool _onesided)
  , $(int64_t _length)
  , $(bool _return_complex)));
  }|]

istft_tllltbbbl
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> Int64
  -> IO (Ptr Tensor)
istft_tllltbbbl :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
istft_tllltbbbl Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_center CBool
_normalized CBool
_onesided Int64
_length =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _center)
  , $(bool _normalized)
  , $(bool _onesided)
  , $(int64_t _length)));
  }|]

istft_tllltbbb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
istft_tllltbbb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
istft_tllltbbb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_center CBool
_normalized CBool
_onesided =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _center)
  , $(bool _normalized)
  , $(bool _onesided)));
  }|]

istft_tllltbb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
istft_tllltbb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
istft_tllltbb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_center CBool
_normalized =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _center)
  , $(bool _normalized)));
  }|]

istft_tllltb
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
istft_tllltb :: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
istft_tllltb Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window CBool
_center =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)
  , $(bool _center)));
  }|]

istft_tlllt
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
istft_tlllt :: Ptr Tensor
-> Int64 -> Int64 -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
istft_tlllt Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length Ptr Tensor
_window =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)
  , *$(at::Tensor* _window)));
  }|]

istft_tlll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
istft_tlll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
istft_tlll Ptr Tensor
_self Int64
_n_fft Int64
_hop_length Int64
_win_length =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)
  , $(int64_t _win_length)));
  }|]

istft_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
istft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
istft_tll Ptr Tensor
_self Int64
_n_fft Int64
_hop_length =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::istft(
    *$(at::Tensor* _self)
  , $(int64_t _n_fft)
  , $(int64_t _hop_length)));
  }|]

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

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

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

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

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

sum_tlbs
  :: Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> ScalarType
  -> IO (Ptr Tensor)
sum_tlbs :: Ptr Tensor
-> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor)
sum_tlbs Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _keepdim)
  , $(at::ScalarType _dtype)));
  }|]

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

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

sum_tNbs
  :: Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> ScalarType
  -> IO (Ptr Tensor)
sum_tNbs :: Ptr Tensor
-> Ptr DimnameList -> CBool -> ScalarType -> IO (Ptr Tensor)
sum_tNbs Ptr Tensor
_self Ptr DimnameList
_dim CBool
_keepdim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _keepdim)
  , $(at::ScalarType _dtype)));
  }|]

sum_tNb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> IO (Ptr Tensor)
sum_tNb :: Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
sum_tNb Ptr Tensor
_self Ptr DimnameList
_dim CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _keepdim)));
  }|]

sum_tN
  :: Ptr Tensor
  -> Ptr DimnameList
  -> IO (Ptr Tensor)
sum_tN :: Ptr Tensor -> Ptr DimnameList -> IO (Ptr Tensor)
sum_tN Ptr Tensor
_self Ptr DimnameList
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)));
  }|]

sum_out_ttlbs
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> ScalarType
  -> IO (Ptr Tensor)
sum_out_ttlbs :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
sum_out_ttlbs Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _keepdim)
  , $(at::ScalarType _dtype)));
  }|]

sum_out_ttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
sum_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
sum_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _keepdim)));
  }|]

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

sum_out_ttNbs
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> ScalarType
  -> IO (Ptr Tensor)
sum_out_ttNbs :: Ptr Tensor
-> Ptr Tensor
-> Ptr DimnameList
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
sum_out_ttNbs Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim CBool
_keepdim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _keepdim)
  , $(at::ScalarType _dtype)));
  }|]

sum_out_ttNb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> IO (Ptr Tensor)
sum_out_ttNb :: Ptr Tensor
-> Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
sum_out_ttNb Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _keepdim)));
  }|]

sum_out_ttN
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> IO (Ptr Tensor)
sum_out_ttN :: Ptr Tensor -> Ptr Tensor -> Ptr DimnameList -> IO (Ptr Tensor)
sum_out_ttN Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::sum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)));
  }|]

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

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

nansum_tlbs
  :: Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> ScalarType
  -> IO (Ptr Tensor)
nansum_tlbs :: Ptr Tensor
-> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor)
nansum_tlbs Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nansum(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _keepdim)
  , $(at::ScalarType _dtype)));
  }|]

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

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

nansum_out_ttlbs
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> ScalarType
  -> IO (Ptr Tensor)
nansum_out_ttlbs :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
nansum_out_ttlbs Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nansum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _keepdim)
  , $(at::ScalarType _dtype)));
  }|]

nansum_out_ttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
nansum_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
nansum_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nansum_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _keepdim)));
  }|]

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

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

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

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

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

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

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

std_tb
  :: Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
std_tb :: Ptr Tensor -> CBool -> IO (Ptr Tensor)
std_tb Ptr Tensor
_self CBool
_unbiased =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std(
    *$(at::Tensor* _self)
  , $(bool _unbiased)));
  }|]

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

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

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

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

std_tllb
  :: Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
std_tllb :: Ptr Tensor -> Ptr IntArray -> Int64 -> CBool -> IO (Ptr Tensor)
std_tllb Ptr Tensor
_self Ptr IntArray
_dim Int64
_correction CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(int64_t _correction)
  , $(bool _keepdim)));
  }|]

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

std_mean_tb
  :: Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tb Ptr Tensor
_self CBool
_unbiased =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , $(bool _unbiased)));
  }|]

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

std_mean_tlbb
  :: Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tlbb :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tlbb Ptr Tensor
_self Ptr IntArray
_dim CBool
_unbiased CBool
_keepdim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _unbiased)
  , $(bool _keepdim)));
  }|]

std_mean_tlb
  :: Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tlb :: Ptr Tensor
-> Ptr IntArray -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tlb Ptr Tensor
_self Ptr IntArray
_dim CBool
_unbiased =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _unbiased)));
  }|]

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

std_mean_tllb
  :: Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tllb :: Ptr Tensor
-> Ptr IntArray
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tllb Ptr Tensor
_self Ptr IntArray
_dim Int64
_correction CBool
_keepdim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(int64_t _correction)
  , $(bool _keepdim)));
  }|]

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

std_mean_tNbb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tNbb :: Ptr Tensor
-> Ptr DimnameList
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tNbb Ptr Tensor
_self Ptr DimnameList
_dim CBool
_unbiased CBool
_keepdim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _unbiased)
  , $(bool _keepdim)));
  }|]

std_mean_tNb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tNb :: Ptr Tensor
-> Ptr DimnameList
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tNb Ptr Tensor
_self Ptr DimnameList
_dim CBool
_unbiased =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _unbiased)));
  }|]

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

std_mean_tNlb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
std_mean_tNlb :: Ptr Tensor
-> Ptr DimnameList
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
std_mean_tNlb Ptr Tensor
_self Ptr DimnameList
_dim Int64
_correction CBool
_keepdim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::std_mean(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(int64_t _correction)
  , $(bool _keepdim)));
  }|]

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

std_out_ttlbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
std_out_ttlbb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> CBool -> IO (Ptr Tensor)
std_out_ttlbb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_unbiased CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _unbiased)
  , $(bool _keepdim)));
  }|]

std_out_ttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
std_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
std_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_unbiased =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(bool _unbiased)));
  }|]

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

std_out_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
std_out_ttllb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Int64 -> CBool -> IO (Ptr Tensor)
std_out_ttllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim Int64
_correction CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _dim)
  , $(int64_t _correction)
  , $(bool _keepdim)));
  }|]

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

std_tNbb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
std_tNbb :: Ptr Tensor -> Ptr DimnameList -> CBool -> CBool -> IO (Ptr Tensor)
std_tNbb Ptr Tensor
_self Ptr DimnameList
_dim CBool
_unbiased CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _unbiased)
  , $(bool _keepdim)));
  }|]

std_tNb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> IO (Ptr Tensor)
std_tNb :: Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
std_tNb Ptr Tensor
_self Ptr DimnameList
_dim CBool
_unbiased =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _unbiased)));
  }|]

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

std_out_ttNbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
std_out_ttNbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr DimnameList
-> CBool
-> CBool
-> IO (Ptr Tensor)
std_out_ttNbb Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim CBool
_unbiased CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _unbiased)
  , $(bool _keepdim)));
  }|]

std_out_ttNb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> CBool
  -> IO (Ptr Tensor)
std_out_ttNb :: Ptr Tensor
-> Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
std_out_ttNb Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim CBool
_unbiased =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(bool _unbiased)));
  }|]

std_out_ttN
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> IO (Ptr Tensor)
std_out_ttN :: Ptr Tensor -> Ptr Tensor -> Ptr DimnameList -> IO (Ptr Tensor)
std_out_ttN Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)));
  }|]

std_tNlb
  :: Ptr Tensor
  -> Ptr DimnameList
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
std_tNlb :: Ptr Tensor -> Ptr DimnameList -> Int64 -> CBool -> IO (Ptr Tensor)
std_tNlb Ptr Tensor
_self Ptr DimnameList
_dim Int64
_correction CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(int64_t _correction)
  , $(bool _keepdim)));
  }|]

std_tNl
  :: Ptr Tensor
  -> Ptr DimnameList
  -> Int64
  -> IO (Ptr Tensor)
std_tNl :: Ptr Tensor -> Ptr DimnameList -> Int64 -> IO (Ptr Tensor)
std_tNl Ptr Tensor
_self Ptr DimnameList
_dim Int64
_correction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std(
    *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(int64_t _correction)));
  }|]

std_out_ttNlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
std_out_ttNlb :: Ptr Tensor
-> Ptr Tensor
-> Ptr DimnameList
-> Int64
-> CBool
-> IO (Ptr Tensor)
std_out_ttNlb Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim Int64
_correction CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(int64_t _correction)
  , $(bool _keepdim)));
  }|]

std_out_ttNl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr DimnameList
  -> Int64
  -> IO (Ptr Tensor)
std_out_ttNl :: Ptr Tensor
-> Ptr Tensor -> Ptr DimnameList -> Int64 -> IO (Ptr Tensor)
std_out_ttNl Ptr Tensor
_out Ptr Tensor
_self Ptr DimnameList
_dim Int64
_correction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::std_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Dimname>* _dim)
  , $(int64_t _correction)));
  }|]

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

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

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

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

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

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

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

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

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

prod_tnb
  :: Ptr Tensor
  -> Ptr Dimname
  -> CBool
  -> IO (Ptr Tensor)
prod_tnb :: Ptr Tensor -> Ptr Dimname -> CBool -> IO (Ptr Tensor)
prod_tnb Ptr Tensor
_self Ptr Dimname
_dim CBool
_keepdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::prod(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim)
  , $(bool _keepdim)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

tensordot_ttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
tensordot_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
tensordot_ttll Ptr Tensor
_self Ptr Tensor
_other Ptr IntArray
_dims_self Ptr IntArray
_dims_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::tensordot(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::vector<int64_t>* _dims_self)
  , *$(std::vector<int64_t>* _dims_other)));
  }|]

tensordot_out_tttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
tensordot_out_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
tensordot_out_tttll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other Ptr IntArray
_dims_self Ptr IntArray
_dims_other =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::tensordot_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::vector<int64_t>* _dims_self)
  , *$(std::vector<int64_t>* _dims_other)));
  }|]

threshold_tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
threshold_tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
threshold_tss Ptr Tensor
_self Ptr Scalar
_threshold Ptr Scalar
_value =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::threshold(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _threshold)
  , *$(at::Scalar* _value)));
  }|]

threshold__tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
threshold__tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
threshold__tss Ptr Tensor
_self Ptr Scalar
_threshold Ptr Scalar
_value =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::threshold_(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _threshold)
  , *$(at::Scalar* _value)));
  }|]

threshold_out_ttss
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
threshold_out_ttss :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
threshold_out_ttss Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_threshold Ptr Scalar
_value =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::threshold_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Scalar* _threshold)
  , *$(at::Scalar* _value)));
  }|]

threshold_backward_out_ttts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
threshold_backward_out_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
threshold_backward_out_ttts Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Scalar
_threshold =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::threshold_backward_out(
    *$(at::Tensor* _grad_input)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(at::Scalar* _threshold)));
  }|]

threshold_backward_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
threshold_backward_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
threshold_backward_tts Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Scalar
_threshold =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::threshold_backward(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(at::Scalar* _threshold)));
  }|]

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

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

transpose_tnn
  :: Ptr Tensor
  -> Ptr Dimname
  -> Ptr Dimname
  -> IO (Ptr Tensor)
transpose_tnn :: Ptr Tensor -> Ptr Dimname -> Ptr Dimname -> IO (Ptr Tensor)
transpose_tnn Ptr Tensor
_self Ptr Dimname
_dim0 Ptr Dimname
_dim1 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::transpose(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _dim0)
  , *$(at::Dimname* _dim1)));
  }|]

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

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

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

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

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

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

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

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

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

rot90_tll
  :: Ptr Tensor
  -> Int64
  -> Ptr IntArray
  -> IO (Ptr Tensor)
rot90_tll :: Ptr Tensor -> Int64 -> Ptr IntArray -> IO (Ptr Tensor)
rot90_tll Ptr Tensor
_self Int64
_k Ptr IntArray
_dims =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::rot90(
    *$(at::Tensor* _self)
  , $(int64_t _k)
  , *$(std::vector<int64_t>* _dims)));
  }|]

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

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

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

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

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

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

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

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

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

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

trapz_td
  :: Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
trapz_td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor)
trapz_td Ptr Tensor
_y CDouble
_dx =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::trapz(
    *$(at::Tensor* _y)
  , $(double _dx)));
  }|]

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

_trilinear_tttlllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
_trilinear_tttlllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
_trilinear_tttlllll Ptr Tensor
_i1 Ptr Tensor
_i2 Ptr Tensor
_i3 Ptr IntArray
_expand1 Ptr IntArray
_expand2 Ptr IntArray
_expand3 Ptr IntArray
_sumdim Int64
_unroll_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_trilinear(
    *$(at::Tensor* _i1)
  , *$(at::Tensor* _i2)
  , *$(at::Tensor* _i3)
  , *$(std::vector<int64_t>* _expand1)
  , *$(std::vector<int64_t>* _expand2)
  , *$(std::vector<int64_t>* _expand3)
  , *$(std::vector<int64_t>* _sumdim)
  , $(int64_t _unroll_dim)));
  }|]

_trilinear_tttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
_trilinear_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_trilinear_tttllll Ptr Tensor
_i1 Ptr Tensor
_i2 Ptr Tensor
_i3 Ptr IntArray
_expand1 Ptr IntArray
_expand2 Ptr IntArray
_expand3 Ptr IntArray
_sumdim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_trilinear(
    *$(at::Tensor* _i1)
  , *$(at::Tensor* _i2)
  , *$(at::Tensor* _i3)
  , *$(std::vector<int64_t>* _expand1)
  , *$(std::vector<int64_t>* _expand2)
  , *$(std::vector<int64_t>* _expand3)
  , *$(std::vector<int64_t>* _sumdim)));
  }|]

triplet_margin_loss_tttdddbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> Int64
  -> IO (Ptr Tensor)
triplet_margin_loss_tttdddbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> Int64
-> IO (Ptr Tensor)
triplet_margin_loss_tttdddbl Ptr Tensor
_anchor Ptr Tensor
_positive Ptr Tensor
_negative CDouble
_margin CDouble
_p CDouble
_eps CBool
_swap Int64
_reduction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triplet_margin_loss(
    *$(at::Tensor* _anchor)
  , *$(at::Tensor* _positive)
  , *$(at::Tensor* _negative)
  , $(double _margin)
  , $(double _p)
  , $(double _eps)
  , $(bool _swap)
  , $(int64_t _reduction)));
  }|]

triplet_margin_loss_tttdddb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> IO (Ptr Tensor)
triplet_margin_loss_tttdddb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> IO (Ptr Tensor)
triplet_margin_loss_tttdddb Ptr Tensor
_anchor Ptr Tensor
_positive Ptr Tensor
_negative CDouble
_margin CDouble
_p CDouble
_eps CBool
_swap =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triplet_margin_loss(
    *$(at::Tensor* _anchor)
  , *$(at::Tensor* _positive)
  , *$(at::Tensor* _negative)
  , $(double _margin)
  , $(double _p)
  , $(double _eps)
  , $(bool _swap)));
  }|]

triplet_margin_loss_tttddd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
triplet_margin_loss_tttddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
triplet_margin_loss_tttddd Ptr Tensor
_anchor Ptr Tensor
_positive Ptr Tensor
_negative CDouble
_margin CDouble
_p CDouble
_eps =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triplet_margin_loss(
    *$(at::Tensor* _anchor)
  , *$(at::Tensor* _positive)
  , *$(at::Tensor* _negative)
  , $(double _margin)
  , $(double _p)
  , $(double _eps)));
  }|]

triplet_margin_loss_tttdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
triplet_margin_loss_tttdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
triplet_margin_loss_tttdd Ptr Tensor
_anchor Ptr Tensor
_positive Ptr Tensor
_negative CDouble
_margin CDouble
_p =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triplet_margin_loss(
    *$(at::Tensor* _anchor)
  , *$(at::Tensor* _positive)
  , *$(at::Tensor* _negative)
  , $(double _margin)
  , $(double _p)));
  }|]

triplet_margin_loss_tttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
triplet_margin_loss_tttd :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
triplet_margin_loss_tttd Ptr Tensor
_anchor Ptr Tensor
_positive Ptr Tensor
_negative CDouble
_margin =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triplet_margin_loss(
    *$(at::Tensor* _anchor)
  , *$(at::Tensor* _positive)
  , *$(at::Tensor* _negative)
  , $(double _margin)));
  }|]

triplet_margin_loss_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
triplet_margin_loss_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
triplet_margin_loss_ttt Ptr Tensor
_anchor Ptr Tensor
_positive Ptr Tensor
_negative =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triplet_margin_loss(
    *$(at::Tensor* _anchor)
  , *$(at::Tensor* _positive)
  , *$(at::Tensor* _negative)));
  }|]

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

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

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

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

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

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

_has_compatible_shallow_copy_type_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (CBool)
_has_compatible_shallow_copy_type_tt :: Ptr Tensor -> Ptr Tensor -> IO CBool
_has_compatible_shallow_copy_type_tt Ptr Tensor
_self Ptr Tensor
_from =
  [C.throwBlock| bool { return (at::_has_compatible_shallow_copy_type(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _from)));
  }|]

_unique_tbb
  :: Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_unique_tbb :: Ptr Tensor
-> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
_unique_tbb Ptr Tensor
_self CBool
_sorted CBool
_return_inverse =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_unique(
    *$(at::Tensor* _self)
  , $(bool _sorted)
  , $(bool _return_inverse)));
  }|]

_unique_tb
  :: Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_unique_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
_unique_tb Ptr Tensor
_self CBool
_sorted =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_unique(
    *$(at::Tensor* _self)
  , $(bool _sorted)));
  }|]

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