-- 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>"


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)));
  }|]

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

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)));
  }|]

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

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

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

flatten_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
flatten_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
flatten_tll Ptr Tensor
_self Int64
_start_dim Int64
_end_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::flatten(
    *$(at::Tensor* _self)
  , $(int64_t _start_dim)
  , $(int64_t _end_dim)));
  }|]

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

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

flatten_tlln
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Dimname
  -> IO (Ptr Tensor)
flatten_tlln :: Ptr Tensor -> Int64 -> Int64 -> Ptr Dimname -> IO (Ptr Tensor)
flatten_tlln Ptr Tensor
_self Int64
_start_dim Int64
_end_dim Ptr Dimname
_out_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::flatten(
    *$(at::Tensor* _self)
  , $(int64_t _start_dim)
  , $(int64_t _end_dim)
  , *$(at::Dimname* _out_dim)));
  }|]

flatten_tnnn
  :: Ptr Tensor
  -> Ptr Dimname
  -> Ptr Dimname
  -> Ptr Dimname
  -> IO (Ptr Tensor)
flatten_tnnn :: Ptr Tensor
-> Ptr Dimname -> Ptr Dimname -> Ptr Dimname -> IO (Ptr Tensor)
flatten_tnnn Ptr Tensor
_self Ptr Dimname
_start_dim Ptr Dimname
_end_dim Ptr Dimname
_out_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::flatten(
    *$(at::Tensor* _self)
  , *$(at::Dimname* _start_dim)
  , *$(at::Dimname* _end_dim)
  , *$(at::Dimname* _out_dim)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

from_file_sblo
  :: Ptr StdString
  -> CBool
  -> Int64
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
from_file_sblo :: Ptr StdString
-> CBool -> Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
from_file_sblo Ptr StdString
_filename CBool
_shared Int64
_size Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::from_file(
    *$(std::string* _filename)
  , $(bool _shared)
  , $(int64_t _size)
  , *$(at::TensorOptions* _options)));
  }|]

from_file_sbl
  :: Ptr StdString
  -> CBool
  -> Int64
  -> IO (Ptr Tensor)
from_file_sbl :: Ptr StdString -> CBool -> Int64 -> IO (Ptr Tensor)
from_file_sbl Ptr StdString
_filename CBool
_shared Int64
_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::from_file(
    *$(std::string* _filename)
  , $(bool _shared)
  , $(int64_t _size)));
  }|]

from_file_sb
  :: Ptr StdString
  -> CBool
  -> IO (Ptr Tensor)
from_file_sb :: Ptr StdString -> CBool -> IO (Ptr Tensor)
from_file_sb Ptr StdString
_filename CBool
_shared =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::from_file(
    *$(std::string* _filename)
  , $(bool _shared)));
  }|]

from_file_s
  :: Ptr StdString
  -> IO (Ptr Tensor)
from_file_s :: Ptr StdString -> IO (Ptr Tensor)
from_file_s Ptr StdString
_filename =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::from_file(
    *$(std::string* _filename)));
  }|]

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

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

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

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

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

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

grid_sampler_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
grid_sampler_ttllb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> CBool -> IO (Ptr Tensor)
grid_sampler_ttllb Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::grid_sampler(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)));
  }|]

grid_sampler_2d_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
grid_sampler_2d_ttllb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> CBool -> IO (Ptr Tensor)
grid_sampler_2d_ttllb Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::grid_sampler_2d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)));
  }|]

grid_sampler_2d_backward_tttllba
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> Ptr (StdArray '(CBool,2))
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
grid_sampler_2d_backward_tttllba :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CBool
-> Ptr (StdArray '(CBool, 2))
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
grid_sampler_2d_backward_tttllba Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners Ptr (StdArray '(CBool, 2))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::grid_sampler_2d_backward(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)
  , *$(std::array<bool,2>* _output_mask)));
  }|]

_grid_sampler_2d_cpu_fallback_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
_grid_sampler_2d_cpu_fallback_ttllb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> CBool -> IO (Ptr Tensor)
_grid_sampler_2d_cpu_fallback_ttllb Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_grid_sampler_2d_cpu_fallback(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)));
  }|]

_grid_sampler_2d_cpu_fallback_backward_tttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_grid_sampler_2d_cpu_fallback_backward_tttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_grid_sampler_2d_cpu_fallback_backward_tttllb Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_grid_sampler_2d_cpu_fallback_backward(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)));
  }|]

grid_sampler_3d_ttllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
grid_sampler_3d_ttllb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> CBool -> IO (Ptr Tensor)
grid_sampler_3d_ttllb Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::grid_sampler_3d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)));
  }|]

grid_sampler_3d_backward_tttllba
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> CBool
  -> Ptr (StdArray '(CBool,2))
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
grid_sampler_3d_backward_tttllba :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CBool
-> Ptr (StdArray '(CBool, 2))
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
grid_sampler_3d_backward_tttllba Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_grid Int64
_interpolation_mode Int64
_padding_mode CBool
_align_corners Ptr (StdArray '(CBool, 2))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::grid_sampler_3d_backward(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _grid)
  , $(int64_t _interpolation_mode)
  , $(int64_t _padding_mode)
  , $(bool _align_corners)
  , *$(std::array<bool,2>* _output_mask)));
  }|]

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

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

hann_window_lbo
  :: Int64
  -> CBool
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
hann_window_lbo :: Int64 -> CBool -> Ptr TensorOptions -> IO (Ptr Tensor)
hann_window_lbo Int64
_window_length CBool
_periodic Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hann_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , *$(at::TensorOptions* _options)));
  }|]

hann_window_lb
  :: Int64
  -> CBool
  -> IO (Ptr Tensor)
hann_window_lb :: Int64 -> CBool -> IO (Ptr Tensor)
hann_window_lb Int64
_window_length CBool
_periodic =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hann_window(
    $(int64_t _window_length)
  , $(bool _periodic)));
  }|]

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

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

hamming_window_lbo
  :: Int64
  -> CBool
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
hamming_window_lbo :: Int64 -> CBool -> Ptr TensorOptions -> IO (Ptr Tensor)
hamming_window_lbo Int64
_window_length CBool
_periodic Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hamming_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , *$(at::TensorOptions* _options)));
  }|]

hamming_window_lb
  :: Int64
  -> CBool
  -> IO (Ptr Tensor)
hamming_window_lb :: Int64 -> CBool -> IO (Ptr Tensor)
hamming_window_lb Int64
_window_length CBool
_periodic =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hamming_window(
    $(int64_t _window_length)
  , $(bool _periodic)));
  }|]

hamming_window_lbdo
  :: Int64
  -> CBool
  -> CDouble
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
hamming_window_lbdo :: Int64 -> CBool -> CDouble -> Ptr TensorOptions -> IO (Ptr Tensor)
hamming_window_lbdo Int64
_window_length CBool
_periodic CDouble
_alpha Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hamming_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , $(double _alpha)
  , *$(at::TensorOptions* _options)));
  }|]

hamming_window_lbd
  :: Int64
  -> CBool
  -> CDouble
  -> IO (Ptr Tensor)
hamming_window_lbd :: Int64 -> CBool -> CDouble -> IO (Ptr Tensor)
hamming_window_lbd Int64
_window_length CBool
_periodic CDouble
_alpha =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hamming_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , $(double _alpha)));
  }|]

hamming_window_lbddo
  :: Int64
  -> CBool
  -> CDouble
  -> CDouble
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
hamming_window_lbddo :: Int64
-> CBool
-> CDouble
-> CDouble
-> Ptr TensorOptions
-> IO (Ptr Tensor)
hamming_window_lbddo Int64
_window_length CBool
_periodic CDouble
_alpha CDouble
_beta Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hamming_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , $(double _alpha)
  , $(double _beta)
  , *$(at::TensorOptions* _options)));
  }|]

hamming_window_lbdd
  :: Int64
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
hamming_window_lbdd :: Int64 -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
hamming_window_lbdd Int64
_window_length CBool
_periodic CDouble
_alpha CDouble
_beta =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::hamming_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , $(double _alpha)
  , $(double _beta)));
  }|]

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

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

kaiser_window_lbo
  :: Int64
  -> CBool
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
kaiser_window_lbo :: Int64 -> CBool -> Ptr TensorOptions -> IO (Ptr Tensor)
kaiser_window_lbo Int64
_window_length CBool
_periodic Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::kaiser_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , *$(at::TensorOptions* _options)));
  }|]

kaiser_window_lb
  :: Int64
  -> CBool
  -> IO (Ptr Tensor)
kaiser_window_lb :: Int64 -> CBool -> IO (Ptr Tensor)
kaiser_window_lb Int64
_window_length CBool
_periodic =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::kaiser_window(
    $(int64_t _window_length)
  , $(bool _periodic)));
  }|]

kaiser_window_lbdo
  :: Int64
  -> CBool
  -> CDouble
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
kaiser_window_lbdo :: Int64 -> CBool -> CDouble -> Ptr TensorOptions -> IO (Ptr Tensor)
kaiser_window_lbdo Int64
_window_length CBool
_periodic CDouble
_beta Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::kaiser_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , $(double _beta)
  , *$(at::TensorOptions* _options)));
  }|]

kaiser_window_lbd
  :: Int64
  -> CBool
  -> CDouble
  -> IO (Ptr Tensor)
kaiser_window_lbd :: Int64 -> CBool -> CDouble -> IO (Ptr Tensor)
kaiser_window_lbd Int64
_window_length CBool
_periodic CDouble
_beta =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::kaiser_window(
    $(int64_t _window_length)
  , $(bool _periodic)
  , $(double _beta)));
  }|]

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

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

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

group_norm_tlttdb
  :: Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CBool
  -> IO (Ptr Tensor)
group_norm_tlttdb :: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CBool
-> IO (Ptr Tensor)
group_norm_tlttdb Ptr Tensor
_input Int64
_num_groups Ptr Tensor
_weight Ptr Tensor
_bias CDouble
_eps CBool
_cudnn_enabled =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::group_norm(
    *$(at::Tensor* _input)
  , $(int64_t _num_groups)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(double _eps)
  , $(bool _cudnn_enabled)));
  }|]

group_norm_tlttd
  :: Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
group_norm_tlttd :: Ptr Tensor
-> Int64 -> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
group_norm_tlttd Ptr Tensor
_input Int64
_num_groups Ptr Tensor
_weight Ptr Tensor
_bias CDouble
_eps =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::group_norm(
    *$(at::Tensor* _input)
  , $(int64_t _num_groups)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(double _eps)));
  }|]

group_norm_tltt
  :: Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
group_norm_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
group_norm_tltt Ptr Tensor
_input Int64
_num_groups Ptr Tensor
_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::group_norm(
    *$(at::Tensor* _input)
  , $(int64_t _num_groups)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)));
  }|]

group_norm_tlt
  :: Ptr Tensor
  -> Int64
  -> Ptr Tensor
  -> IO (Ptr Tensor)
group_norm_tlt :: Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
group_norm_tlt Ptr Tensor
_input Int64
_num_groups Ptr Tensor
_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::group_norm(
    *$(at::Tensor* _input)
  , $(int64_t _num_groups)
  , *$(at::Tensor* _weight)));
  }|]

group_norm_tl
  :: Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
group_norm_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
group_norm_tl Ptr Tensor
_input Int64
_num_groups =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::group_norm(
    *$(at::Tensor* _input)
  , $(int64_t _num_groups)));
  }|]

native_group_norm_tttlllld
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
native_group_norm_tttlllld :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
native_group_norm_tttlllld Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Int64
_N Int64
_C Int64
_HxW Int64
_group CDouble
_eps =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::native_group_norm(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(int64_t _N)
  , $(int64_t _C)
  , $(int64_t _HxW)
  , $(int64_t _group)
  , $(double _eps)));
  }|]

native_group_norm_backward_tttttlllla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
native_group_norm_backward_tttttlllla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
native_group_norm_backward_tttttlllla Ptr Tensor
_grad_out Ptr Tensor
_input Ptr Tensor
_mean Ptr Tensor
_rstd Ptr Tensor
_weight Int64
_N Int64
_C Int64
_HxW Int64
_group Ptr (StdArray '(CBool, 3))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::native_group_norm_backward(
    *$(at::Tensor* _grad_out)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _mean)
  , *$(at::Tensor* _rstd)
  , *$(at::Tensor* _weight)
  , $(int64_t _N)
  , $(int64_t _C)
  , $(int64_t _HxW)
  , $(int64_t _group)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

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

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

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

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

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

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

_validate_compressed_sparse_indices_bttlll
  :: CBool
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (())
_validate_compressed_sparse_indices_bttlll :: CBool
-> Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO ()
_validate_compressed_sparse_indices_bttlll CBool
_is_crow Ptr Tensor
_compressed_idx Ptr Tensor
_plain_idx Int64
_cdim Int64
_dim Int64
_nnz =
  [C.throwBlock| void {  (at::_validate_compressed_sparse_indices(
    $(bool _is_crow)
  , *$(at::Tensor* _compressed_idx)
  , *$(at::Tensor* _plain_idx)
  , $(int64_t _cdim)
  , $(int64_t _dim)
  , $(int64_t _nnz)));
  }|]

_cufft_get_plan_cache_size_l
  :: Int64
  -> IO (Int64)
_cufft_get_plan_cache_size_l :: Int64 -> IO Int64
_cufft_get_plan_cache_size_l Int64
_device_index =
  [C.throwBlock| int64_t { return (at::_cufft_get_plan_cache_size(
    $(int64_t _device_index)));
  }|]

_cufft_get_plan_cache_max_size_l
  :: Int64
  -> IO (Int64)
_cufft_get_plan_cache_max_size_l :: Int64 -> IO Int64
_cufft_get_plan_cache_max_size_l Int64
_device_index =
  [C.throwBlock| int64_t { return (at::_cufft_get_plan_cache_max_size(
    $(int64_t _device_index)));
  }|]

_cufft_set_plan_cache_max_size_ll
  :: Int64
  -> Int64
  -> IO (())
_cufft_set_plan_cache_max_size_ll :: Int64 -> Int64 -> IO ()
_cufft_set_plan_cache_max_size_ll Int64
_device_index Int64
_max_size =
  [C.throwBlock| void {  (at::_cufft_set_plan_cache_max_size(
    $(int64_t _device_index)
  , $(int64_t _max_size)));
  }|]

_cufft_clear_plan_cache_l
  :: Int64
  -> IO (())
_cufft_clear_plan_cache_l :: Int64 -> IO ()
_cufft_clear_plan_cache_l Int64
_device_index =
  [C.throwBlock| void {  (at::_cufft_clear_plan_cache(
    $(int64_t _device_index)));
  }|]

index_tl
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> IO (Ptr Tensor)
index_tl :: Ptr Tensor -> Ptr (C10List (C10Optional Tensor)) -> IO (Ptr Tensor)
index_tl Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::index(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)));
  }|]

index_out_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> IO (Ptr Tensor)
index_out_ttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> IO (Ptr Tensor)
index_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::index_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)));
  }|]

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

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

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

index_put__tltb
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
index_put__tltb :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
index_put__tltb Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values CBool
_accumulate =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::index_put_(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)
  , $(bool _accumulate)));
  }|]

index_put__tlt
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> IO (Ptr Tensor)
index_put__tlt :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> IO (Ptr Tensor)
index_put__tlt Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::index_put_(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)));
  }|]

index_put_tltb
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
index_put_tltb :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
index_put_tltb Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values CBool
_accumulate =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::index_put(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)
  , $(bool _accumulate)));
  }|]

index_put_tlt
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> IO (Ptr Tensor)
index_put_tlt :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> IO (Ptr Tensor)
index_put_tlt Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::index_put(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)));
  }|]

_index_put_impl__tltbb
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
_index_put_impl__tltbb :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
_index_put_impl__tltbb Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values CBool
_accumulate CBool
_unsafe =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_index_put_impl_(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)
  , $(bool _accumulate)
  , $(bool _unsafe)));
  }|]

_index_put_impl__tltb
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
_index_put_impl__tltb :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_index_put_impl__tltb Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values CBool
_accumulate =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_index_put_impl_(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)
  , $(bool _accumulate)));
  }|]

_index_put_impl__tlt
  :: Ptr Tensor
  -> Ptr (C10List (C10Optional Tensor))
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_index_put_impl__tlt :: Ptr Tensor
-> Ptr (C10List (C10Optional Tensor))
-> Ptr Tensor
-> IO (Ptr Tensor)
_index_put_impl__tlt Ptr Tensor
_self Ptr (C10List (C10Optional Tensor))
_indices Ptr Tensor
_values =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_index_put_impl_(
    *$(at::Tensor* _self)
  , *$(c10::List<c10::optional<at::Tensor>>* _indices)
  , *$(at::Tensor* _values)));
  }|]

instance_norm_tttttbddb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> CBool
  -> IO (Ptr Tensor)
instance_norm_tttttbddb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> CBool
-> IO (Ptr Tensor)
instance_norm_tttttbddb Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr Tensor
_running_mean Ptr Tensor
_running_var CBool
_use_input_stats CDouble
_momentum CDouble
_eps CBool
_cudnn_enabled =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::instance_norm(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(at::Tensor* _running_mean)
  , *$(at::Tensor* _running_var)
  , $(bool _use_input_stats)
  , $(double _momentum)
  , $(double _eps)
  , $(bool _cudnn_enabled)));
  }|]

isclose_ttddb
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> CBool
  -> IO (Ptr Tensor)
isclose_ttddb :: Ptr Tensor
-> Ptr Tensor -> CDouble -> CDouble -> CBool -> IO (Ptr Tensor)
isclose_ttddb Ptr Tensor
_self Ptr Tensor
_other CDouble
_rtol CDouble
_atol CBool
_equal_nan =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isclose(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , $(double _rtol)
  , $(double _atol)
  , $(bool _equal_nan)));
  }|]

isclose_ttdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
isclose_ttdd :: Ptr Tensor -> Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
isclose_ttdd Ptr Tensor
_self Ptr Tensor
_other CDouble
_rtol CDouble
_atol =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isclose(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , $(double _rtol)
  , $(double _atol)));
  }|]

isclose_ttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
isclose_ttd :: Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
isclose_ttd Ptr Tensor
_self Ptr Tensor
_other CDouble
_rtol =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isclose(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , $(double _rtol)));
  }|]

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

isin_out_tttbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
isin_out_tttbb :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
isin_out_tttbb Ptr Tensor
_out Ptr Tensor
_elements Ptr Tensor
_test_elements CBool
_assume_unique CBool
_invert =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _elements)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)
  , $(bool _invert)));
  }|]

isin_out_tttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
isin_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
isin_out_tttb Ptr Tensor
_out Ptr Tensor
_elements Ptr Tensor
_test_elements CBool
_assume_unique =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _elements)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)));
  }|]

isin_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
isin_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
isin_out_ttt Ptr Tensor
_out Ptr Tensor
_elements Ptr Tensor
_test_elements =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _elements)
  , *$(at::Tensor* _test_elements)));
  }|]

isin_ttbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
isin_ttbb :: Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
isin_ttbb Ptr Tensor
_elements Ptr Tensor
_test_elements CBool
_assume_unique CBool
_invert =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Tensor* _elements)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)
  , $(bool _invert)));
  }|]

isin_ttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
isin_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
isin_ttb Ptr Tensor
_elements Ptr Tensor
_test_elements CBool
_assume_unique =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Tensor* _elements)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)));
  }|]

isin_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
isin_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
isin_tt Ptr Tensor
_elements Ptr Tensor
_test_elements =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Tensor* _elements)
  , *$(at::Tensor* _test_elements)));
  }|]

isin_out_ttsbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
isin_out_ttsbb :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> CBool -> CBool -> IO (Ptr Tensor)
isin_out_ttsbb Ptr Tensor
_out Ptr Tensor
_elements Ptr Scalar
_test_element CBool
_assume_unique CBool
_invert =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _elements)
  , *$(at::Scalar* _test_element)
  , $(bool _assume_unique)
  , $(bool _invert)));
  }|]

isin_out_ttsb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> IO (Ptr Tensor)
isin_out_ttsb :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> CBool -> IO (Ptr Tensor)
isin_out_ttsb Ptr Tensor
_out Ptr Tensor
_elements Ptr Scalar
_test_element CBool
_assume_unique =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _elements)
  , *$(at::Scalar* _test_element)
  , $(bool _assume_unique)));
  }|]

isin_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
isin_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
isin_out_tts Ptr Tensor
_out Ptr Tensor
_elements Ptr Scalar
_test_element =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _elements)
  , *$(at::Scalar* _test_element)));
  }|]

isin_tsbb
  :: Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
isin_tsbb :: Ptr Tensor -> Ptr Scalar -> CBool -> CBool -> IO (Ptr Tensor)
isin_tsbb Ptr Tensor
_elements Ptr Scalar
_test_element CBool
_assume_unique CBool
_invert =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Tensor* _elements)
  , *$(at::Scalar* _test_element)
  , $(bool _assume_unique)
  , $(bool _invert)));
  }|]

isin_tsb
  :: Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> IO (Ptr Tensor)
isin_tsb :: Ptr Tensor -> Ptr Scalar -> CBool -> IO (Ptr Tensor)
isin_tsb Ptr Tensor
_elements Ptr Scalar
_test_element CBool
_assume_unique =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Tensor* _elements)
  , *$(at::Scalar* _test_element)
  , $(bool _assume_unique)));
  }|]

isin_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
isin_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
isin_ts Ptr Tensor
_elements Ptr Scalar
_test_element =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Tensor* _elements)
  , *$(at::Scalar* _test_element)));
  }|]

isin_out_tstbb
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
isin_out_tstbb :: Ptr Tensor
-> Ptr Scalar -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
isin_out_tstbb Ptr Tensor
_out Ptr Scalar
_element Ptr Tensor
_test_elements CBool
_assume_unique CBool
_invert =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _element)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)
  , $(bool _invert)));
  }|]

isin_out_tstb
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
isin_out_tstb :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
isin_out_tstb Ptr Tensor
_out Ptr Scalar
_element Ptr Tensor
_test_elements CBool
_assume_unique =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _element)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)));
  }|]

isin_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
isin_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
isin_out_tst Ptr Tensor
_out Ptr Scalar
_element Ptr Tensor
_test_elements =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _element)
  , *$(at::Tensor* _test_elements)));
  }|]

isin_stbb
  :: Ptr Scalar
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
isin_stbb :: Ptr Scalar -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
isin_stbb Ptr Scalar
_element Ptr Tensor
_test_elements CBool
_assume_unique CBool
_invert =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Scalar* _element)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)
  , $(bool _invert)));
  }|]

isin_stb
  :: Ptr Scalar
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
isin_stb :: Ptr Scalar -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
isin_stb Ptr Scalar
_element Ptr Tensor
_test_elements CBool
_assume_unique =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Scalar* _element)
  , *$(at::Tensor* _test_elements)
  , $(bool _assume_unique)));
  }|]

isin_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
isin_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
isin_st Ptr Scalar
_element Ptr Tensor
_test_elements =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::isin(
    *$(at::Scalar* _element)
  , *$(at::Tensor* _test_elements)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

kl_div_ttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
kl_div_ttlb :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor)
kl_div_ttlb Ptr Tensor
_self Ptr Tensor
_target Int64
_reduction CBool
_log_target =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::kl_div(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _target)
  , $(int64_t _reduction)
  , $(bool _log_target)));
  }|]

kl_div_ttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
kl_div_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
kl_div_ttl Ptr Tensor
_self Ptr Tensor
_target Int64
_reduction =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::kl_div(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _target)
  , $(int64_t _reduction)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

kthvalue_out_tttlnb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Ptr Dimname
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
kthvalue_out_tttlnb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Dimname
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
kthvalue_out_tttlnb Ptr Tensor
_values Ptr Tensor
_indices Ptr Tensor
_self Int64
_k Ptr Dimname
_dim CBool
_keepdim =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::kthvalue_out(
    *$(at::Tensor* _values)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _self)
  , $(int64_t _k)
  , *$(at::Dimname* _dim)
  , $(bool _keepdim)));
  }|]

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

layer_norm_tlttdb
  :: Ptr Tensor
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CBool
  -> IO (Ptr Tensor)
layer_norm_tlttdb :: Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CBool
-> IO (Ptr Tensor)
layer_norm_tlttdb Ptr Tensor
_input Ptr IntArray
_normalized_shape Ptr Tensor
_weight Ptr Tensor
_bias CDouble
_eps CBool
_cudnn_enable =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::layer_norm(
    *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _normalized_shape)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(double _eps)
  , $(bool _cudnn_enable)));
  }|]

layer_norm_tlttd
  :: Ptr Tensor
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
layer_norm_tlttd :: Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
layer_norm_tlttd Ptr Tensor
_input Ptr IntArray
_normalized_shape Ptr Tensor
_weight Ptr Tensor
_bias CDouble
_eps =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::layer_norm(
    *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _normalized_shape)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(double _eps)));
  }|]

layer_norm_tltt
  :: Ptr Tensor
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
layer_norm_tltt :: Ptr Tensor
-> Ptr IntArray -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
layer_norm_tltt Ptr Tensor
_input Ptr IntArray
_normalized_shape Ptr Tensor
_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::layer_norm(
    *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _normalized_shape)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)));
  }|]

layer_norm_tlt
  :: Ptr Tensor
  -> Ptr IntArray
  -> Ptr Tensor
  -> IO (Ptr Tensor)
layer_norm_tlt :: Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
layer_norm_tlt Ptr Tensor
_input Ptr IntArray
_normalized_shape Ptr Tensor
_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::layer_norm(
    *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _normalized_shape)
  , *$(at::Tensor* _weight)));
  }|]

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

native_layer_norm_tlttd
  :: Ptr Tensor
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
native_layer_norm_tlttd :: Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
native_layer_norm_tlttd Ptr Tensor
_input Ptr IntArray
_normalized_shape Ptr Tensor
_weight Ptr Tensor
_bias CDouble
_eps =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::native_layer_norm(
    *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _normalized_shape)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(double _eps)));
  }|]

native_layer_norm_backward_ttltttta
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
native_layer_norm_backward_ttltttta :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
native_layer_norm_backward_ttltttta Ptr Tensor
_grad_out Ptr Tensor
_input Ptr IntArray
_normalized_shape Ptr Tensor
_mean Ptr Tensor
_rstd Ptr Tensor
_weight Ptr Tensor
_bias Ptr (StdArray '(CBool, 3))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::native_layer_norm_backward(
    *$(at::Tensor* _grad_out)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _normalized_shape)
  , *$(at::Tensor* _mean)
  , *$(at::Tensor* _rstd)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

nan_to_num_tddd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num_tddd :: Ptr Tensor -> CDouble -> CDouble -> CDouble -> IO (Ptr Tensor)
nan_to_num_tddd Ptr Tensor
_self CDouble
_nan CDouble
_posinf CDouble
_neginf =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num(
    *$(at::Tensor* _self)
  , $(double _nan)
  , $(double _posinf)
  , $(double _neginf)));
  }|]

nan_to_num_tdd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num_tdd :: Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
nan_to_num_tdd Ptr Tensor
_self CDouble
_nan CDouble
_posinf =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num(
    *$(at::Tensor* _self)
  , $(double _nan)
  , $(double _posinf)));
  }|]

nan_to_num_td
  :: Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num_td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor)
nan_to_num_td Ptr Tensor
_self CDouble
_nan =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num(
    *$(at::Tensor* _self)
  , $(double _nan)));
  }|]

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

nan_to_num__tddd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num__tddd :: Ptr Tensor -> CDouble -> CDouble -> CDouble -> IO (Ptr Tensor)
nan_to_num__tddd Ptr Tensor
_self CDouble
_nan CDouble
_posinf CDouble
_neginf =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num_(
    *$(at::Tensor* _self)
  , $(double _nan)
  , $(double _posinf)
  , $(double _neginf)));
  }|]

nan_to_num__tdd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num__tdd :: Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
nan_to_num__tdd Ptr Tensor
_self CDouble
_nan CDouble
_posinf =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num_(
    *$(at::Tensor* _self)
  , $(double _nan)
  , $(double _posinf)));
  }|]

nan_to_num__td
  :: Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num__td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor)
nan_to_num__td Ptr Tensor
_self CDouble
_nan =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num_(
    *$(at::Tensor* _self)
  , $(double _nan)));
  }|]

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

nan_to_num_out_ttddd
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num_out_ttddd :: Ptr Tensor
-> Ptr Tensor -> CDouble -> CDouble -> CDouble -> IO (Ptr Tensor)
nan_to_num_out_ttddd Ptr Tensor
_out Ptr Tensor
_self CDouble
_nan CDouble
_posinf CDouble
_neginf =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(double _nan)
  , $(double _posinf)
  , $(double _neginf)));
  }|]

nan_to_num_out_ttdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num_out_ttdd :: Ptr Tensor -> Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
nan_to_num_out_ttdd Ptr Tensor
_out Ptr Tensor
_self CDouble
_nan CDouble
_posinf =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(double _nan)
  , $(double _posinf)));
  }|]

nan_to_num_out_ttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
nan_to_num_out_ttd :: Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
nan_to_num_out_ttd Ptr Tensor
_out Ptr Tensor
_self CDouble
_nan =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::nan_to_num_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(double _nan)));
  }|]

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

linear_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
linear_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
linear_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linear(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)));
  }|]

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

linear_backward_ttta
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
linear_backward_ttta :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
linear_backward_ttta Ptr Tensor
_self Ptr Tensor
_grad_output Ptr Tensor
_weight Ptr (StdArray '(CBool, 3))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::linear_backward(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _weight)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

linear_out_tttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
linear_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
linear_out_tttt Ptr Tensor
_out Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linear_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)));
  }|]

linear_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
linear_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
linear_out_ttt Ptr Tensor
_out Ptr Tensor
_input Ptr Tensor
_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linear_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)));
  }|]

mkldnn_linear_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
mkldnn_linear_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
mkldnn_linear_ttt Ptr Tensor
_self Ptr Tensor
_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_linear(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)));
  }|]

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

mkldnn_linear_backward_input_ltt
  :: Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
mkldnn_linear_backward_input_ltt :: Ptr IntArray -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
mkldnn_linear_backward_input_ltt Ptr IntArray
_input_size Ptr Tensor
_grad_output Ptr Tensor
_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_linear_backward_input(
    *$(std::vector<int64_t>* _input_size)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _weight)));
  }|]

mkldnn_linear_backward_weights_tttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
mkldnn_linear_backward_weights_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
mkldnn_linear_backward_weights_tttb Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_weight CBool
_bias_defined =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::mkldnn_linear_backward_weights(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , $(bool _bias_defined)));
  }|]

mkldnn_linear_backward_ttta
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
mkldnn_linear_backward_ttta :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
mkldnn_linear_backward_ttta Ptr Tensor
_self Ptr Tensor
_grad_output Ptr Tensor
_weight Ptr (StdArray '(CBool, 3))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::mkldnn_linear_backward(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _weight)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

fbgemm_linear_int8_weight_fp32_activation_ttttsst
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
fbgemm_linear_int8_weight_fp32_activation_ttttsst :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
fbgemm_linear_int8_weight_fp32_activation_ttttsst Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_packed Ptr Tensor
_col_offsets Ptr Scalar
_weight_scale Ptr Scalar
_weight_zero_point Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_linear_int8_weight_fp32_activation(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _packed)
  , *$(at::Tensor* _col_offsets)
  , *$(at::Scalar* _weight_scale)
  , *$(at::Scalar* _weight_zero_point)
  , *$(at::Tensor* _bias)));
  }|]

fbgemm_linear_int8_weight_ttttsst
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
fbgemm_linear_int8_weight_ttttsst :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
fbgemm_linear_int8_weight_ttttsst Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_packed Ptr Tensor
_col_offsets Ptr Scalar
_weight_scale Ptr Scalar
_weight_zero_point Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_linear_int8_weight(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _packed)
  , *$(at::Tensor* _col_offsets)
  , *$(at::Scalar* _weight_scale)
  , *$(at::Scalar* _weight_zero_point)
  , *$(at::Tensor* _bias)));
  }|]

fbgemm_linear_quantize_weight_t
  :: Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,CDouble,Int64)))
fbgemm_linear_quantize_weight_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor, CDouble, Int64)))
fbgemm_linear_quantize_weight_t Ptr Tensor
_input =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,double,int64_t>* { return new std::tuple<at::Tensor,at::Tensor,double,int64_t>(at::fbgemm_linear_quantize_weight(
    *$(at::Tensor* _input)));
  }|]

fbgemm_pack_gemm_matrix_fp16_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
fbgemm_pack_gemm_matrix_fp16_t :: Ptr Tensor -> IO (Ptr Tensor)
fbgemm_pack_gemm_matrix_fp16_t Ptr Tensor
_input =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_pack_gemm_matrix_fp16(
    *$(at::Tensor* _input)));
  }|]

fbgemm_linear_fp16_weight_fp32_activation_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
fbgemm_linear_fp16_weight_fp32_activation_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fbgemm_linear_fp16_weight_fp32_activation_ttt Ptr Tensor
_input Ptr Tensor
_packed_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_linear_fp16_weight_fp32_activation(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _packed_weight)
  , *$(at::Tensor* _bias)));
  }|]

fbgemm_linear_fp16_weight_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
fbgemm_linear_fp16_weight_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fbgemm_linear_fp16_weight_ttt Ptr Tensor
_input Ptr Tensor
_packed_weight Ptr Tensor
_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_linear_fp16_weight(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _packed_weight)
  , *$(at::Tensor* _bias)));
  }|]

fbgemm_pack_quantized_matrix_t
  :: Ptr Tensor
  -> IO (Ptr Tensor)
fbgemm_pack_quantized_matrix_t :: Ptr Tensor -> IO (Ptr Tensor)
fbgemm_pack_quantized_matrix_t Ptr Tensor
_input =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_pack_quantized_matrix(
    *$(at::Tensor* _input)));
  }|]

fbgemm_pack_quantized_matrix_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
fbgemm_pack_quantized_matrix_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fbgemm_pack_quantized_matrix_tll Ptr Tensor
_input Int64
_K Int64
_N =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::fbgemm_pack_quantized_matrix(
    *$(at::Tensor* _input)
  , $(int64_t _K)
  , $(int64_t _N)));
  }|]

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

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

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

linspace_sslo
  :: Ptr Scalar
  -> Ptr Scalar
  -> Int64
  -> Ptr TensorOptions
  -> IO (Ptr Tensor)
linspace_sslo :: Ptr Scalar
-> Ptr Scalar -> Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
linspace_sslo Ptr Scalar
_start Ptr Scalar
_end Int64
_steps Ptr TensorOptions
_options =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linspace(
    *$(at::Scalar* _start)
  , *$(at::Scalar* _end)
  , $(int64_t _steps)
  , *$(at::TensorOptions* _options)));
  }|]

linspace_ssl
  :: Ptr Scalar
  -> Ptr Scalar
  -> Int64
  -> IO (Ptr Tensor)
linspace_ssl :: Ptr Scalar -> Ptr Scalar -> Int64 -> IO (Ptr Tensor)
linspace_ssl Ptr Scalar
_start Ptr Scalar
_end Int64
_steps =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linspace(
    *$(at::Scalar* _start)
  , *$(at::Scalar* _end)
  , $(int64_t _steps)));
  }|]

linspace_out_tssl
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> Int64
  -> IO (Ptr Tensor)
linspace_out_tssl :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> Int64 -> IO (Ptr Tensor)
linspace_out_tssl Ptr Tensor
_out Ptr Scalar
_start Ptr Scalar
_end Int64
_steps =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::linspace_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _start)
  , *$(at::Scalar* _end)
  , $(int64_t _steps)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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