-- generated by using spec/Declarations.yaml

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

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


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

special_hermite_polynomial_h_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_hermite_polynomial_h_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_hermite_polynomial_h_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_h(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_hermite_polynomial_h_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_hermite_polynomial_h_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_hermite_polynomial_h_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_h(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_hermite_polynomial_h_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_hermite_polynomial_h_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_hermite_polynomial_h_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_h_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_hermite_polynomial_h_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_hermite_polynomial_h_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_hermite_polynomial_h_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_h_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_hermite_polynomial_h_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_hermite_polynomial_h_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_hermite_polynomial_h_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_h_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

special_hermite_polynomial_he_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_hermite_polynomial_he_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_hermite_polynomial_he_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_he(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_hermite_polynomial_he_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_hermite_polynomial_he_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_hermite_polynomial_he_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_he(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_hermite_polynomial_he_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_hermite_polynomial_he_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_hermite_polynomial_he_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_he_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_hermite_polynomial_he_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_hermite_polynomial_he_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_hermite_polynomial_he_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_he_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_hermite_polynomial_he_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_hermite_polynomial_he_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_hermite_polynomial_he_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_hermite_polynomial_he_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

special_laguerre_polynomial_l_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_laguerre_polynomial_l_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_laguerre_polynomial_l_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_laguerre_polynomial_l(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_laguerre_polynomial_l_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_laguerre_polynomial_l_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_laguerre_polynomial_l_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_laguerre_polynomial_l(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_laguerre_polynomial_l_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_laguerre_polynomial_l_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_laguerre_polynomial_l_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_laguerre_polynomial_l_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_laguerre_polynomial_l_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_laguerre_polynomial_l_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_laguerre_polynomial_l_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_laguerre_polynomial_l_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_laguerre_polynomial_l_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_laguerre_polynomial_l_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_laguerre_polynomial_l_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_laguerre_polynomial_l_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

special_legendre_polynomial_p_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_legendre_polynomial_p_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_legendre_polynomial_p_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_legendre_polynomial_p(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_legendre_polynomial_p_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_legendre_polynomial_p_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_legendre_polynomial_p_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_legendre_polynomial_p(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_legendre_polynomial_p_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_legendre_polynomial_p_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_legendre_polynomial_p_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_legendre_polynomial_p_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_legendre_polynomial_p_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_legendre_polynomial_p_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_legendre_polynomial_p_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_legendre_polynomial_p_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_legendre_polynomial_p_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_legendre_polynomial_p_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_legendre_polynomial_p_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_legendre_polynomial_p_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

special_shifted_chebyshev_polynomial_t_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_t(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_t_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_t(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_shifted_chebyshev_polynomial_t_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_t_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_t_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_t_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_t_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_t_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_t_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

special_shifted_chebyshev_polynomial_u_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_u(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_u_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_u(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_shifted_chebyshev_polynomial_u_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_u_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_u_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_u_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_u_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_u_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_u_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

special_shifted_chebyshev_polynomial_v_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_v(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_v_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_v(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_shifted_chebyshev_polynomial_v_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_v_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_v_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_v_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_v_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_v_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_v_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

special_shifted_chebyshev_polynomial_w_st
  :: Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_st Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_w(
    *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_w_ts
  :: Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_ts Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_w(
    *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

special_shifted_chebyshev_polynomial_w_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_out_ttt Ptr Tensor
_out Ptr Tensor
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_w_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_w_out_tst
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_out_tst Ptr Tensor
_out Ptr Scalar
_x Ptr Tensor
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_w_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _x)
  , *$(at::Tensor* _n)));
  }|]

special_shifted_chebyshev_polynomial_w_out_tts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_shifted_chebyshev_polynomial_w_out_tts Ptr Tensor
_out Ptr Tensor
_x Ptr Scalar
_n =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::special_shifted_chebyshev_polynomial_w_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _x)
  , *$(at::Scalar* _n)));
  }|]

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

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

_foobar_tbbb
  :: Ptr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
_foobar_tbbb :: Ptr Tensor -> CBool -> CBool -> CBool -> IO (Ptr Tensor)
_foobar_tbbb Ptr Tensor
_self CBool
_arg1 CBool
_arg2 CBool
_arg3 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_foobar(
    *$(at::Tensor* _self)
  , $(bool _arg1)
  , $(bool _arg2)
  , $(bool _arg3)));
  }|]

_foobar_tbb
  :: Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
_foobar_tbb :: Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
_foobar_tbb Ptr Tensor
_self CBool
_arg1 CBool
_arg2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_foobar(
    *$(at::Tensor* _self)
  , $(bool _arg1)
  , $(bool _arg2)));
  }|]

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

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

_fused_adam__lllllldddddbbtt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (())
_fused_adam__lllllldddddbbtt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> Ptr Tensor
-> IO ()
_fused_adam__lllllldddddbbtt Ptr TensorList
_self Ptr TensorList
_grads Ptr TensorList
_exp_avgs Ptr TensorList
_exp_avg_sqs Ptr TensorList
_max_exp_avg_sqs Ptr TensorList
_state_steps CDouble
_lr CDouble
_beta1 CDouble
_beta2 CDouble
_weight_decay CDouble
_eps CBool
_amsgrad CBool
_maximize Ptr Tensor
_grad_scale Ptr Tensor
_found_inf =
  [C.throwBlock| void {  (at::_fused_adam_(
    *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _grads)
  , *$(std::vector<at::Tensor>* _exp_avgs)
  , *$(std::vector<at::Tensor>* _exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _max_exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _state_steps)
  , $(double _lr)
  , $(double _beta1)
  , $(double _beta2)
  , $(double _weight_decay)
  , $(double _eps)
  , $(bool _amsgrad)
  , $(bool _maximize)
  , *$(at::Tensor* _grad_scale)
  , *$(at::Tensor* _found_inf)));
  }|]

_fused_adam__lllllldddddbbt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr Tensor
  -> IO (())
_fused_adam__lllllldddddbbt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> IO ()
_fused_adam__lllllldddddbbt Ptr TensorList
_self Ptr TensorList
_grads Ptr TensorList
_exp_avgs Ptr TensorList
_exp_avg_sqs Ptr TensorList
_max_exp_avg_sqs Ptr TensorList
_state_steps CDouble
_lr CDouble
_beta1 CDouble
_beta2 CDouble
_weight_decay CDouble
_eps CBool
_amsgrad CBool
_maximize Ptr Tensor
_grad_scale =
  [C.throwBlock| void {  (at::_fused_adam_(
    *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _grads)
  , *$(std::vector<at::Tensor>* _exp_avgs)
  , *$(std::vector<at::Tensor>* _exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _max_exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _state_steps)
  , $(double _lr)
  , $(double _beta1)
  , $(double _beta2)
  , $(double _weight_decay)
  , $(double _eps)
  , $(bool _amsgrad)
  , $(bool _maximize)
  , *$(at::Tensor* _grad_scale)));
  }|]

_fused_adam__lllllldddddbb
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> IO (())
_fused_adam__lllllldddddbb :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO ()
_fused_adam__lllllldddddbb Ptr TensorList
_self Ptr TensorList
_grads Ptr TensorList
_exp_avgs Ptr TensorList
_exp_avg_sqs Ptr TensorList
_max_exp_avg_sqs Ptr TensorList
_state_steps CDouble
_lr CDouble
_beta1 CDouble
_beta2 CDouble
_weight_decay CDouble
_eps CBool
_amsgrad CBool
_maximize =
  [C.throwBlock| void {  (at::_fused_adam_(
    *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _grads)
  , *$(std::vector<at::Tensor>* _exp_avgs)
  , *$(std::vector<at::Tensor>* _exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _max_exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _state_steps)
  , $(double _lr)
  , $(double _beta1)
  , $(double _beta2)
  , $(double _weight_decay)
  , $(double _eps)
  , $(bool _amsgrad)
  , $(bool _maximize)));
  }|]

_fused_adamw__lllllldddddbbtt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (())
_fused_adamw__lllllldddddbbtt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> Ptr Tensor
-> IO ()
_fused_adamw__lllllldddddbbtt Ptr TensorList
_self Ptr TensorList
_grads Ptr TensorList
_exp_avgs Ptr TensorList
_exp_avg_sqs Ptr TensorList
_max_exp_avg_sqs Ptr TensorList
_state_steps CDouble
_lr CDouble
_beta1 CDouble
_beta2 CDouble
_weight_decay CDouble
_eps CBool
_amsgrad CBool
_maximize Ptr Tensor
_grad_scale Ptr Tensor
_found_inf =
  [C.throwBlock| void {  (at::_fused_adamw_(
    *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _grads)
  , *$(std::vector<at::Tensor>* _exp_avgs)
  , *$(std::vector<at::Tensor>* _exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _max_exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _state_steps)
  , $(double _lr)
  , $(double _beta1)
  , $(double _beta2)
  , $(double _weight_decay)
  , $(double _eps)
  , $(bool _amsgrad)
  , $(bool _maximize)
  , *$(at::Tensor* _grad_scale)
  , *$(at::Tensor* _found_inf)));
  }|]

_fused_adamw__lllllldddddbbt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr Tensor
  -> IO (())
_fused_adamw__lllllldddddbbt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> IO ()
_fused_adamw__lllllldddddbbt Ptr TensorList
_self Ptr TensorList
_grads Ptr TensorList
_exp_avgs Ptr TensorList
_exp_avg_sqs Ptr TensorList
_max_exp_avg_sqs Ptr TensorList
_state_steps CDouble
_lr CDouble
_beta1 CDouble
_beta2 CDouble
_weight_decay CDouble
_eps CBool
_amsgrad CBool
_maximize Ptr Tensor
_grad_scale =
  [C.throwBlock| void {  (at::_fused_adamw_(
    *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _grads)
  , *$(std::vector<at::Tensor>* _exp_avgs)
  , *$(std::vector<at::Tensor>* _exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _max_exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _state_steps)
  , $(double _lr)
  , $(double _beta1)
  , $(double _beta2)
  , $(double _weight_decay)
  , $(double _eps)
  , $(bool _amsgrad)
  , $(bool _maximize)
  , *$(at::Tensor* _grad_scale)));
  }|]

_fused_adamw__lllllldddddbb
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> IO (())
_fused_adamw__lllllldddddbb :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO ()
_fused_adamw__lllllldddddbb Ptr TensorList
_self Ptr TensorList
_grads Ptr TensorList
_exp_avgs Ptr TensorList
_exp_avg_sqs Ptr TensorList
_max_exp_avg_sqs Ptr TensorList
_state_steps CDouble
_lr CDouble
_beta1 CDouble
_beta2 CDouble
_weight_decay CDouble
_eps CBool
_amsgrad CBool
_maximize =
  [C.throwBlock| void {  (at::_fused_adamw_(
    *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _grads)
  , *$(std::vector<at::Tensor>* _exp_avgs)
  , *$(std::vector<at::Tensor>* _exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _max_exp_avg_sqs)
  , *$(std::vector<at::Tensor>* _state_steps)
  , $(double _lr)
  , $(double _beta1)
  , $(double _beta2)
  , $(double _weight_decay)
  , $(double _eps)
  , $(bool _amsgrad)
  , $(bool _maximize)));
  }|]

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

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

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

_cudnn_rnn_flatten_weight_out_tlllllllbb
  :: Ptr Tensor
  -> Ptr TensorList
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
_cudnn_rnn_flatten_weight_out_tlllllllbb :: Ptr Tensor
-> Ptr TensorList
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
_cudnn_rnn_flatten_weight_out_tlllllllbb Ptr Tensor
_out Ptr TensorList
_weight_arr Int64
_weight_stride0 Int64
_input_size Int64
_mode Int64
_hidden_size Int64
_proj_size Int64
_num_layers CBool
_batch_first CBool
_bidirectional =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_cudnn_rnn_flatten_weight_out(
    *$(at::Tensor* _out)
  , *$(std::vector<at::Tensor>* _weight_arr)
  , $(int64_t _weight_stride0)
  , $(int64_t _input_size)
  , $(int64_t _mode)
  , $(int64_t _hidden_size)
  , $(int64_t _proj_size)
  , $(int64_t _num_layers)
  , $(bool _batch_first)
  , $(bool _bidirectional)));
  }|]

_cudnn_rnn_out_ttttttlltttllllbdbblt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr TensorList
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr IntArray
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)))
_cudnn_rnn_out_ttttttlltttllllbdbblt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
_cudnn_rnn_out_ttttttlltttllllbdbblt Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 Ptr Tensor
_out3 Ptr Tensor
_out4 Ptr Tensor
_input Ptr TensorList
_weight Int64
_weight_stride0 Ptr Tensor
_weight_buf Ptr Tensor
_hx Ptr Tensor
_cx Int64
_mode Int64
_hidden_size Int64
_proj_size Int64
_num_layers CBool
_batch_first CDouble
_dropout CBool
_train CBool
_bidirectional Ptr IntArray
_batch_sizes Ptr Tensor
_dropout_state =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::_cudnn_rnn_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(at::Tensor* _out3)
  , *$(at::Tensor* _out4)
  , *$(at::Tensor* _input)
  , *$(std::vector<at::Tensor>* _weight)
  , $(int64_t _weight_stride0)
  , *$(at::Tensor* _weight_buf)
  , *$(at::Tensor* _hx)
  , *$(at::Tensor* _cx)
  , $(int64_t _mode)
  , $(int64_t _hidden_size)
  , $(int64_t _proj_size)
  , $(int64_t _num_layers)
  , $(bool _batch_first)
  , $(double _dropout)
  , $(bool _train)
  , $(bool _bidirectional)
  , *$(std::vector<int64_t>* _batch_sizes)
  , *$(at::Tensor* _dropout_state)));
  }|]

_cudnn_rnn_backward_out_tttltlltttttttllllbdbbltta
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr TensorList
  -> Ptr Tensor
  -> Ptr TensorList
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr (StdArray '(CBool,4))
  -> IO (())
_cudnn_rnn_backward_out_tttltlltttttttllllbdbbltta :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> Ptr TensorList
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 4))
-> IO ()
_cudnn_rnn_backward_out_tttltlltttttttllllbdbbltta Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 Ptr TensorList
_out3 Ptr Tensor
_input Ptr TensorList
_weight Int64
_weight_stride0 Ptr Tensor
_weight_buf Ptr Tensor
_hx Ptr Tensor
_cx Ptr Tensor
_output Ptr Tensor
_grad_output Ptr Tensor
_grad_hy Ptr Tensor
_grad_cy Int64
_mode Int64
_hidden_size Int64
_proj_size Int64
_num_layers CBool
_batch_first CDouble
_dropout CBool
_train CBool
_bidirectional Ptr IntArray
_batch_sizes Ptr Tensor
_dropout_state Ptr Tensor
_reserve Ptr (StdArray '(CBool, 4))
_output_mask =
  [C.throwBlock| void {  (at::_cudnn_rnn_backward_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(std::vector<at::Tensor>* _out3)
  , *$(at::Tensor* _input)
  , *$(std::vector<at::Tensor>* _weight)
  , $(int64_t _weight_stride0)
  , *$(at::Tensor* _weight_buf)
  , *$(at::Tensor* _hx)
  , *$(at::Tensor* _cx)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _grad_hy)
  , *$(at::Tensor* _grad_cy)
  , $(int64_t _mode)
  , $(int64_t _hidden_size)
  , $(int64_t _proj_size)
  , $(int64_t _num_layers)
  , $(bool _batch_first)
  , $(double _dropout)
  , $(bool _train)
  , $(bool _bidirectional)
  , *$(std::vector<int64_t>* _batch_sizes)
  , *$(at::Tensor* _dropout_state)
  , *$(at::Tensor* _reserve)
  , *$(std::array<bool,4>* _output_mask)));
  }|]

_cudnn_init_dropout_state_out_tdbl
  :: Ptr Tensor
  -> CDouble
  -> CBool
  -> Int64
  -> IO (Ptr Tensor)
_cudnn_init_dropout_state_out_tdbl :: Ptr Tensor -> CDouble -> CBool -> Int64 -> IO (Ptr Tensor)
_cudnn_init_dropout_state_out_tdbl Ptr Tensor
_out CDouble
_dropout CBool
_train Int64
_dropout_seed =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_cudnn_init_dropout_state_out(
    *$(at::Tensor* _out)
  , $(double _dropout)
  , $(bool _train)
  , $(int64_t _dropout_seed)));
  }|]

_fused_dropout_out_tttdG
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> Ptr Generator
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_fused_dropout_out_tttdG :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Ptr Generator
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_fused_dropout_out_tttdG Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_self CDouble
_p Ptr Generator
_generator =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_fused_dropout_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _self)
  , $(double _p)
  , *$(at::Generator* _generator)));
  }|]

_fused_dropout_out_tttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_fused_dropout_out_tttd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_fused_dropout_out_tttd Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_self CDouble
_p =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_fused_dropout_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _self)
  , $(double _p)));
  }|]

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

native_dropout_out_tttdb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
native_dropout_out_tttdb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
native_dropout_out_tttdb Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_input CDouble
_p CBool
_train =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::native_dropout_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _input)
  , $(double _p)
  , $(bool _train)));
  }|]

native_dropout_backward_out_tttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
native_dropout_backward_out_tttd :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
native_dropout_backward_out_tttd Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_mask CDouble
_scale =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::native_dropout_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _mask)
  , $(double _scale)));
  }|]

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

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

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

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

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

affine_grid_generator_out_ttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
affine_grid_generator_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
affine_grid_generator_out_ttlb Ptr Tensor
_out Ptr Tensor
_theta Ptr IntArray
_size CBool
_align_corners =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::affine_grid_generator_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _theta)
  , *$(std::vector<int64_t>* _size)
  , $(bool _align_corners)));
  }|]

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

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

quantized_batch_norm_out_ttttttddl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> Int64
  -> IO (Ptr Tensor)
quantized_batch_norm_out_ttttttddl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (Ptr Tensor)
quantized_batch_norm_out_ttttttddl Ptr Tensor
_out Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr Tensor
_mean Ptr Tensor
_var CDouble
_eps CDouble
_output_scale Int64
_output_zero_point =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_batch_norm_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _bias)
  , *$(at::Tensor* _mean)
  , *$(at::Tensor* _var)
  , $(double _eps)
  , $(double _output_scale)
  , $(int64_t _output_zero_point)));
  }|]

bernoulli_out_tttG
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Generator
  -> IO (Ptr Tensor)
bernoulli_out_tttG :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Generator -> IO (Ptr Tensor)
bernoulli_out_tttG Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_p Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _p)
  , *$(at::Generator* _generator)));
  }|]

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

bernoulli_ttG
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Generator
  -> IO (Ptr Tensor)
bernoulli_ttG :: Ptr Tensor -> Ptr Tensor -> Ptr Generator -> IO (Ptr Tensor)
bernoulli_ttG Ptr Tensor
_self Ptr Tensor
_p Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _p)
  , *$(at::Generator* _generator)));
  }|]

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

bernoulli_out_ttdG
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> Ptr Generator
  -> IO (Ptr Tensor)
bernoulli_out_ttdG :: Ptr Tensor
-> Ptr Tensor -> CDouble -> Ptr Generator -> IO (Ptr Tensor)
bernoulli_out_ttdG Ptr Tensor
_out Ptr Tensor
_self CDouble
_p Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(double _p)
  , *$(at::Generator* _generator)));
  }|]

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

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

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

binary_cross_entropy_with_logits_out_ttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
binary_cross_entropy_with_logits_out_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_out_ttttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Ptr Tensor
_pos_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _target)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _pos_weight)));
  }|]

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

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

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

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

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

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

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

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

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

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

convolution_out_ttttlllbll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
convolution_out_ttttlllbll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_out_ttttlllbll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_ttttttllllblla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> 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_out_ttttttllllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> 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_out_ttttttllllblla Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(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_out_ttttlllbll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
convolution_overrideable_out_ttttlllbll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_overrideable_out_ttttlllbll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_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_backward_overrideable_out_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_backward_overrideable_out_ttttttlllblla Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(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_out_ttttlllbllbbbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
_convolution_out_ttttlllbllbbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
_convolution_out_ttttlllbllbbbb Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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)));
  }|]

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

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

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

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

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

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

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

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

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

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

cudnn_affine_grid_generator_backward_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
cudnn_affine_grid_generator_backward_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
cudnn_affine_grid_generator_backward_out_ttllll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , $(int64_t _N)
  , $(int64_t _C)
  , $(int64_t _H)
  , $(int64_t _W)));
  }|]

cudnn_batch_norm_out_tttttttttbdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
cudnn_batch_norm_out_tttttttttbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
cudnn_batch_norm_out_tttttttttbdd Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 Ptr Tensor
_out3 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(at::Tensor* _out3)
  , *$(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_out_ttttttttttdt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> 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_out_ttttttttttdt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> 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_out_ttttttttttdt Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(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_out_tttllllbbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
cudnn_convolution_out_tttllllbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
cudnn_convolution_out_tttllllbbb Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_tttlllllbbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
cudnn_convolution_transpose_out_tttlllllbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
cudnn_convolution_transpose_out_tttlllllbbb Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_tttlllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
_mps_convolution_transpose_out_tttlllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
_mps_convolution_transpose_out_tttlllll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_tttttllllla
  :: Ptr Tensor
  -> Ptr Tensor
  -> 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_out_tttttllllla :: Ptr Tensor
-> Ptr Tensor
-> 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_out_tttttllllla Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(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_out_ttttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
cudnn_convolution_relu_out_ttttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
cudnn_convolution_relu_out_ttttllll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_ttttstllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr Tensor)
cudnn_convolution_add_relu_out_ttttstllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
cudnn_convolution_add_relu_out_ttttstllll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_ttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
cudnn_grid_sampler_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cudnn_grid_sampler_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_grid =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cudnn_grid_sampler_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _grid)));
  }|]

cudnn_grid_sampler_backward_out_ttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
cudnn_grid_sampler_backward_out_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
cudnn_grid_sampler_backward_out_ttttt Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _grid)
  , *$(at::Tensor* _grad_output)));
  }|]

_ctc_loss_out_ttttlllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_out_ttttlllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_out_ttttlllb Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(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_out_ttttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_out_ttttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_out_ttttlll Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , $(int64_t _blank)));
  }|]

_ctc_loss_out_ttttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_out_ttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_out_ttttll Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)));
  }|]

_ctc_loss_out_ttttttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_out_ttttttlb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_out_ttttttlb Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)
  , $(int64_t _blank)
  , $(bool _zero_infinity)));
  }|]

_ctc_loss_out_ttttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_out_ttttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_out_ttttttl Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)
  , $(int64_t _blank)));
  }|]

_ctc_loss_out_tttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_ctc_loss_out_tttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_ctc_loss_out_tttttt Ptr Tensor
_out0 Ptr Tensor
_out1 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_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(at::Tensor* _input_lengths)
  , *$(at::Tensor* _target_lengths)));
  }|]

_ctc_loss_backward_out_ttttllttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
_ctc_loss_backward_out_ttttllttlb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr Tensor)
_ctc_loss_backward_out_ttttllttlb Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(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_out_ttttllttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_ctc_loss_backward_out_ttttllttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_ctc_loss_backward_out_ttttllttl Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _log_probs)
  , *$(at::Tensor* _targets)
  , *$(std::vector<int64_t>* _input_lengths)
  , *$(std::vector<int64_t>* _target_lengths)
  , *$(at::Tensor* _neg_log_likelihood)
  , *$(at::Tensor* _log_alpha)
  , $(int64_t _blank)));
  }|]

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

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

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

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

diagonal_backward_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
diagonal_backward_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
diagonal_backward_out_ttllll Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(std::vector<int64_t>* _input_sizes)
  , $(int64_t _offset)
  , $(int64_t _dim1)
  , $(int64_t _dim2)));
  }|]

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

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

embedding_out_tttlbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
embedding_out_tttlbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
embedding_out_tttlbb Ptr Tensor
_out 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_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _weight)
  , *$(at::Tensor* _indices)
  , $(int64_t _padding_idx)
  , $(bool _scale_grad_by_freq)
  , $(bool _sparse)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

full_like_out_ttsM
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> MemoryFormat
  -> IO (Ptr Tensor)
full_like_out_ttsM :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> MemoryFormat -> IO (Ptr Tensor)
full_like_out_ttsM Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_fill_value MemoryFormat
_memory_format =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::full_like_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Scalar* _fill_value)
  , $(at::MemoryFormat _memory_format)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

matmul_backward_out_ttttta
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr (StdArray '(CBool,2))
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
matmul_backward_out_ttttta :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 2))
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
matmul_backward_out_ttttta Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_grad Ptr Tensor
_self Ptr Tensor
_other Ptr (StdArray '(CBool, 2))
_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::matmul_backward_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _other)
  , *$(std::array<bool,2>* _mask)));
  }|]

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

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

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

max_pool2d_backward_out_tttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
max_pool2d_backward_out_tttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
max_pool2d_backward_out_tttllllb Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

max_pool2d_backward_out_tttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
max_pool2d_backward_out_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_pool2d_backward_out_tttllll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

max_pool2d_backward_out_tttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
max_pool2d_backward_out_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_pool2d_backward_out_tttlll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

max_pool2d_backward_out_tttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
max_pool2d_backward_out_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_pool2d_backward_out_tttll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)));
  }|]

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

mkldnn_max_pool2d_out_ttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_out_ttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
mkldnn_max_pool2d_out_ttllllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

mkldnn_max_pool2d_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool2d_out_ttllll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

mkldnn_max_pool2d_out_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_out_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool2d_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

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

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

mkldnn_max_pool2d_backward_out_ttttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttllllb Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

mkldnn_max_pool2d_backward_out_ttttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttllll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

mkldnn_max_pool2d_backward_out_ttttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttlll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

mkldnn_max_pool2d_backward_out_ttttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)));
  }|]

mkldnn_max_pool2d_backward_out_ttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool2d_backward_out_ttttl Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool2d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)));
  }|]

mkldnn_max_pool3d_out_ttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_out_ttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
mkldnn_max_pool3d_out_ttllllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

mkldnn_max_pool3d_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool3d_out_ttllll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

mkldnn_max_pool3d_out_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_out_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool3d_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

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

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

mkldnn_max_pool3d_backward_out_ttttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttllllb Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

mkldnn_max_pool3d_backward_out_ttttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttllll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

mkldnn_max_pool3d_backward_out_ttttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttlll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

mkldnn_max_pool3d_backward_out_ttttll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttll Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size Ptr IntArray
_stride =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)));
  }|]

mkldnn_max_pool3d_backward_out_ttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_max_pool3d_backward_out_ttttl Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_output Ptr Tensor
_input Ptr IntArray
_kernel_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_max_pool3d_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _input)
  , *$(std::vector<int64_t>* _kernel_size)));
  }|]

quantized_max_pool1d_out_ttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
quantized_max_pool1d_out_ttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
quantized_max_pool1d_out_ttllllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_max_pool1d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

quantized_max_pool1d_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
quantized_max_pool1d_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
quantized_max_pool1d_out_ttllll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_max_pool1d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

quantized_max_pool1d_out_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
quantized_max_pool1d_out_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
quantized_max_pool1d_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_max_pool1d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

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

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

quantized_max_pool2d_out_ttllllb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> CBool
  -> IO (Ptr Tensor)
quantized_max_pool2d_out_ttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
quantized_max_pool2d_out_ttllllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_max_pool2d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)
  , $(bool _ceil_mode)));
  }|]

quantized_max_pool2d_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
quantized_max_pool2d_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
quantized_max_pool2d_out_ttllll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_max_pool2d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _dilation)));
  }|]

quantized_max_pool2d_out_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> IO (Ptr Tensor)
quantized_max_pool2d_out_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
quantized_max_pool2d_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantized_max_pool2d_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _kernel_size)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _padding)));
  }|]

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

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

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

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

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

mps_convolution_backward_out_ttttttlllla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr IntArray
  -> Ptr IntArray
  -> Int64
  -> Ptr (StdArray '(CBool,3))
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
mps_convolution_backward_out_ttttttlllla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
mps_convolution_backward_out_ttttttlllla Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 Ptr Tensor
_self Ptr Tensor
_grad_output Ptr Tensor
_weight Ptr IntArray
_padding Ptr IntArray
_stride Ptr IntArray
_dilation 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::mps_convolution_backward_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _weight)
  , *$(std::vector<int64_t>* _padding)
  , *$(std::vector<int64_t>* _stride)
  , *$(std::vector<int64_t>* _dilation)
  , $(int64_t _groups)
  , *$(std::array<bool,3>* _output_mask)));
  }|]

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

mkldnn_rnn_layer_out_tttttttttttbllllbbbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
mkldnn_rnn_layer_out_tttttttttttbllllbbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Ptr IntArray
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
mkldnn_rnn_layer_out_tttttttttttbllllbbbb Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 Ptr Tensor
_out3 Ptr Tensor
_input Ptr Tensor
_weight0 Ptr Tensor
_weight1 Ptr Tensor
_weight2 Ptr Tensor
_weight3 Ptr Tensor
_hx_ Ptr Tensor
_cx_ CBool
_reverse Ptr IntArray
_batch_sizes Int64
_mode Int64
_hidden_size Int64
_num_layers CBool
_has_biases CBool
_bidirectional CBool
_batch_first CBool
_train =
  [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::mkldnn_rnn_layer_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(at::Tensor* _out3)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight0)
  , *$(at::Tensor* _weight1)
  , *$(at::Tensor* _weight2)
  , *$(at::Tensor* _weight3)
  , *$(at::Tensor* _hx_)
  , *$(at::Tensor* _cx_)
  , $(bool _reverse)
  , *$(std::vector<int64_t>* _batch_sizes)
  , $(int64_t _mode)
  , $(int64_t _hidden_size)
  , $(int64_t _num_layers)
  , $(bool _has_biases)
  , $(bool _bidirectional)
  , $(bool _batch_first)
  , $(bool _train)));
  }|]

mkldnn_rnn_layer_backward_out_ttttttttttttttttttttblllbbblbt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> Ptr IntArray
  -> CBool
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor,Tensor,Tensor)))
mkldnn_rnn_layer_backward_out_ttttttttttttttttttttblllbbblbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO
     (Ptr
        (StdTuple
           '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
mkldnn_rnn_layer_backward_out_ttttttttttttttttttttblllbbblbt Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 Ptr Tensor
_out3 Ptr Tensor
_out4 Ptr Tensor
_out5 Ptr Tensor
_out6 Ptr Tensor
_input Ptr Tensor
_weight1 Ptr Tensor
_weight2 Ptr Tensor
_weight3 Ptr Tensor
_weight4 Ptr Tensor
_hx_ Ptr Tensor
_cx_tmp Ptr Tensor
_output Ptr Tensor
_hy_ Ptr Tensor
_cy_ Ptr Tensor
_grad_output Ptr Tensor
_grad_hy Ptr Tensor
_grad_cy CBool
_reverse Int64
_mode Int64
_hidden_size Int64
_num_layers CBool
_has_biases CBool
_train CBool
_bidirectional Ptr IntArray
_batch_sizes CBool
_batch_first Ptr Tensor
_workspace =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor,at::Tensor>(at::mkldnn_rnn_layer_backward_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(at::Tensor* _out3)
  , *$(at::Tensor* _out4)
  , *$(at::Tensor* _out5)
  , *$(at::Tensor* _out6)
  , *$(at::Tensor* _input)
  , *$(at::Tensor* _weight1)
  , *$(at::Tensor* _weight2)
  , *$(at::Tensor* _weight3)
  , *$(at::Tensor* _weight4)
  , *$(at::Tensor* _hx_)
  , *$(at::Tensor* _cx_tmp)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _hy_)
  , *$(at::Tensor* _cy_)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _grad_hy)
  , *$(at::Tensor* _grad_cy)
  , $(bool _reverse)
  , $(int64_t _mode)
  , $(int64_t _hidden_size)
  , $(int64_t _num_layers)
  , $(bool _has_biases)
  , $(bool _train)
  , $(bool _bidirectional)
  , *$(std::vector<int64_t>* _batch_sizes)
  , $(bool _batch_first)
  , *$(at::Tensor* _workspace)));
  }|]

miopen_batch_norm_out_ttttttttbdd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
miopen_batch_norm_out_ttttttttbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
miopen_batch_norm_out_ttttttttbdd Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 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>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::miopen_batch_norm_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(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)));
  }|]

miopen_batch_norm_backward_out_ttttttttttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
miopen_batch_norm_backward_out_ttttttttttd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
miopen_batch_norm_backward_out_ttttttttttd Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_out2 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 =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::miopen_batch_norm_backward_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _out2)
  , *$(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)));
  }|]