-- generated by using spec/Declarations.yaml

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

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


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

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

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

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

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

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

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

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

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

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

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

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

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

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

clamp_tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
clamp_tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clamp_tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _min)
  , *$(at::Scalar* _max)));
  }|]

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

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

clamp_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
clamp_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _min)
  , *$(at::Tensor* _max)));
  }|]

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

clamp__tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
clamp__tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clamp__tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _min)
  , *$(at::Scalar* _max)));
  }|]

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

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

clamp__ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
clamp__ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp__ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _min)
  , *$(at::Tensor* _max)));
  }|]

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

clamp_out_ttss
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
clamp_out_ttss :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clamp_out_ttss Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Scalar* _min)
  , *$(at::Scalar* _max)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

clip_tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
clip_tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clip_tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _min)
  , *$(at::Scalar* _max)));
  }|]

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

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

clip_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
clip_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip_ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _min)
  , *$(at::Tensor* _max)));
  }|]

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

clip__tss
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
clip__tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clip__tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
    *$(at::Tensor* _self)
  , *$(at::Scalar* _min)
  , *$(at::Scalar* _max)));
  }|]

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

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

clip__ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
clip__ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip__ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _min)
  , *$(at::Tensor* _max)));
  }|]

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

clip_out_ttss
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> IO (Ptr Tensor)
clip_out_ttss :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clip_out_ttss Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Scalar* _min)
  , *$(at::Scalar* _max)));
  }|]

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

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

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

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

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

complex_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
complex_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
complex_tt Ptr Tensor
_real Ptr Tensor
_imag =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::complex(
    *$(at::Tensor* _real)
  , *$(at::Tensor* _imag)));
  }|]

complex_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
complex_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
complex_out_ttt Ptr Tensor
_out Ptr Tensor
_real Ptr Tensor
_imag =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::complex_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _real)
  , *$(at::Tensor* _imag)));
  }|]

polar_tt
  :: Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
polar_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
polar_tt Ptr Tensor
_abs Ptr Tensor
_angle =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::polar(
    *$(at::Tensor* _abs)
  , *$(at::Tensor* _angle)));
  }|]

polar_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
polar_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
polar_out_ttt Ptr Tensor
_out Ptr Tensor
_abs Ptr Tensor
_angle =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::polar_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _abs)
  , *$(at::Tensor* _angle)));
  }|]

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

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

convolution_tttlllbll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
convolution_tttlllbll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_tttlllbll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::convolution(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _transposed)
  , *$(std::vector<int64_t>* _output_padding)
  , $(int64_t _groups)));
  }|]

convolution_backward_tttllllblla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
convolution_backward_tttllllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
convolution_backward_tttllllblla Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_weight Ptr IntArray
_bias_sizes Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups 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::convolution_backward(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(std::vector<int64_t>* _bias_sizes)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _transposed)
  , *$(std::vector<int64_t>* _output_padding)
  , $(int64_t _groups)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

convolution_overrideable_tttlllbll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
convolution_overrideable_tttlllbll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_overrideable_tttlllbll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::convolution_overrideable(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _transposed)
  , *$(std::vector<int64_t>* _output_padding)
  , $(int64_t _groups)));
  }|]

convolution_backward_overrideable_tttlllblla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
convolution_backward_overrideable_tttlllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
convolution_backward_overrideable_tttlllblla Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_weight Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups 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::convolution_backward_overrideable(
    *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _transposed)
  , *$(std::vector<int64_t>* _output_padding)
  , $(int64_t _groups)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

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

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

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

_convolution_double_backward_ttttttlllblla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_convolution_double_backward_ttttttlllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_convolution_double_backward_ttttttlllblla Ptr Tensor
_ggI Ptr Tensor
_ggW Ptr Tensor
_ggb Ptr Tensor
_gO Ptr Tensor
_weight Ptr Tensor
_self Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups 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::_convolution_double_backward(
    *$(at::Tensor* _ggI)
  , *$(at::Tensor* _ggW)
  , *$(at::Tensor* _ggb)
  , *$(at::Tensor* _gO)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _transposed)
  , *$(std::vector<int64_t>* _output_padding)
  , $(int64_t _groups)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

conv1d_tttlsl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr StdString
  -> Ptr IntArray
  -> IO (Ptr Tensor)
conv1d_tttlsl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttlsl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::string* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

conv1d_tttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr StdString
  -> IO (Ptr Tensor)
conv1d_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv1d_tttls Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::string* _padding)));
  }|]

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

conv2d_tttlsl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr StdString
  -> Ptr IntArray
  -> IO (Ptr Tensor)
conv2d_tttlsl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttlsl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::string* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

conv2d_tttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr StdString
  -> IO (Ptr Tensor)
conv2d_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv2d_tttls Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::string* _padding)));
  }|]

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

conv3d_tttlsl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr StdString
  -> Ptr IntArray
  -> IO (Ptr Tensor)
conv3d_tttlsl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttlsl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::string* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

conv3d_tttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr StdString
  -> IO (Ptr Tensor)
conv3d_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv3d_tttls Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
    *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::string* _padding)));
  }|]

conv_tbc_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
conv_tbc_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
conv_tbc_tttl Ptr Tensor
_self Ptr Tensor
_weight Ptr Tensor
_bias Int64
_pad =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_tbc(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(int64_t _pad)));
  }|]

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

conv_tbc_backward_ttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
conv_tbc_backward_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
conv_tbc_backward_ttttl Ptr Tensor
_self Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Int64
_pad =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::conv_tbc_backward(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , $(int64_t _pad)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

copy_ttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
copy_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
copy_ttb Ptr Tensor
_self Ptr Tensor
_src CBool
_non_blocking =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::copy(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _src)
  , $(bool _non_blocking)));
  }|]

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

_copy_from_ttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
_copy_from_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
_copy_from_ttb Ptr Tensor
_self Ptr Tensor
_dst CBool
_non_blocking =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_copy_from(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _dst)
  , $(bool _non_blocking)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

mps_convolution_transpose_backward_tttllllla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> Ptr (StdArray '(CBool,2))
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
mps_convolution_transpose_backward_tttllllla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 2))
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
mps_convolution_transpose_backward_tttllllla Ptr Tensor
_self Ptr Tensor
_grad_output Ptr Tensor
_weight Ptr IntArray
_padding Ptr IntArray
_output_padding Ptr IntArray
_stride Ptr IntArray
_dilation Int64
_groups Ptr (StdArray '(CBool, 2))
_output_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::mps_convolution_transpose_backward(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _weight)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _output_padding)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _dilation)
  , $(int64_t _groups)
  , *$(std::array<bool,2>* _output_mask)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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