-- generated by using spec/Declarations.yaml

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

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


random_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
random_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
random_tll Ptr Tensor
_self Int64
_from Int64
_to =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::random(
    *$(at::Tensor* _self)
  , $(int64_t _from)
  , $(int64_t _to)));
  }|]

random_out_ttlG
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Ptr Generator
  -> IO (Ptr Tensor)
random_out_ttlG :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Ptr Generator -> IO (Ptr Tensor)
random_out_ttlG Ptr Tensor
_out Ptr Tensor
_self Int64
_to Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::random_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _to)
  , *$(at::Generator* _generator)));
  }|]

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

random_tlG
  :: Ptr Tensor
  -> Int64
  -> Ptr Generator
  -> IO (Ptr Tensor)
random_tlG :: Ptr Tensor -> Int64 -> Ptr Generator -> IO (Ptr Tensor)
random_tlG Ptr Tensor
_self Int64
_to Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::random(
    *$(at::Tensor* _self)
  , $(int64_t _to)
  , *$(at::Generator* _generator)));
  }|]

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

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

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

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

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

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

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

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

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

uniform_tddG
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> Ptr Generator
  -> IO (Ptr Tensor)
uniform_tddG :: Ptr Tensor
-> CDouble -> CDouble -> Ptr Generator -> IO (Ptr Tensor)
uniform_tddG Ptr Tensor
_self CDouble
_from CDouble
_to Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::uniform(
    *$(at::Tensor* _self)
  , $(double _from)
  , $(double _to)
  , *$(at::Generator* _generator)));
  }|]

uniform_tdd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
uniform_tdd :: Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
uniform_tdd Ptr Tensor
_self CDouble
_from CDouble
_to =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::uniform(
    *$(at::Tensor* _self)
  , $(double _from)
  , $(double _to)));
  }|]

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

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

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

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

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

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

cauchy_tddG
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> Ptr Generator
  -> IO (Ptr Tensor)
cauchy_tddG :: Ptr Tensor
-> CDouble -> CDouble -> Ptr Generator -> IO (Ptr Tensor)
cauchy_tddG Ptr Tensor
_self CDouble
_median CDouble
_sigma Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cauchy(
    *$(at::Tensor* _self)
  , $(double _median)
  , $(double _sigma)
  , *$(at::Generator* _generator)));
  }|]

cauchy_tdd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
cauchy_tdd :: Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
cauchy_tdd Ptr Tensor
_self CDouble
_median CDouble
_sigma =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::cauchy(
    *$(at::Tensor* _self)
  , $(double _median)
  , $(double _sigma)));
  }|]

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

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

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

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

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

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

log_normal_tddG
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> Ptr Generator
  -> IO (Ptr Tensor)
log_normal_tddG :: Ptr Tensor
-> CDouble -> CDouble -> Ptr Generator -> IO (Ptr Tensor)
log_normal_tddG Ptr Tensor
_self CDouble
_mean CDouble
_std Ptr Generator
_generator =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::log_normal(
    *$(at::Tensor* _self)
  , $(double _mean)
  , $(double _std)
  , *$(at::Generator* _generator)));
  }|]

log_normal_tdd
  :: Ptr Tensor
  -> CDouble
  -> CDouble
  -> IO (Ptr Tensor)
log_normal_tdd :: Ptr Tensor -> CDouble -> CDouble -> IO (Ptr Tensor)
log_normal_tdd Ptr Tensor
_self CDouble
_mean CDouble
_std =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::log_normal(
    *$(at::Tensor* _self)
  , $(double _mean)
  , $(double _std)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

tril_indices_out_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
tril_indices_out_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
tril_indices_out_tll Ptr Tensor
_out Int64
_row Int64
_col =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::tril_indices_out(
    *$(at::Tensor* _out)
  , $(int64_t _row)
  , $(int64_t _col)));
  }|]

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

triu_indices_out_tll
  :: Ptr Tensor
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
triu_indices_out_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
triu_indices_out_tll Ptr Tensor
_out Int64
_row Int64
_col =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices_out(
    *$(at::Tensor* _out)
  , $(int64_t _row)
  , $(int64_t _col)));
  }|]

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

_cholesky_solve_helper_out_tttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
_cholesky_solve_helper_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
_cholesky_solve_helper_out_tttb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_A CBool
_upper =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_cholesky_solve_helper_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _A)
  , $(bool _upper)));
  }|]

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

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

_histogramdd_bin_edges_out_ltlatb
  :: Ptr TensorList
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr (StdVector CDouble)
  -> Ptr Tensor
  -> CBool
  -> IO (())
_histogramdd_bin_edges_out_ltlatb :: Ptr TensorList
-> Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO ()
_histogramdd_bin_edges_out_ltlatb Ptr TensorList
_out Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight CBool
_density =
  [C.throwBlock| void {  (at::_histogramdd_bin_edges_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)
  , *$(std::vector<double>* _range)
  , *$(at::Tensor* _weight)
  , $(bool _density)));
  }|]

_histogramdd_bin_edges_out_ltlat
  :: Ptr TensorList
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr (StdVector CDouble)
  -> Ptr Tensor
  -> IO (())
_histogramdd_bin_edges_out_ltlat :: Ptr TensorList
-> Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO ()
_histogramdd_bin_edges_out_ltlat Ptr TensorList
_out Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight =
  [C.throwBlock| void {  (at::_histogramdd_bin_edges_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)
  , *$(std::vector<double>* _range)
  , *$(at::Tensor* _weight)));
  }|]

_histogramdd_bin_edges_out_ltla
  :: Ptr TensorList
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr (StdVector CDouble)
  -> IO (())
_histogramdd_bin_edges_out_ltla :: Ptr TensorList
-> Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> IO ()
_histogramdd_bin_edges_out_ltla Ptr TensorList
_out Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range =
  [C.throwBlock| void {  (at::_histogramdd_bin_edges_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)
  , *$(std::vector<double>* _range)));
  }|]

_histogramdd_bin_edges_out_ltl
  :: Ptr TensorList
  -> Ptr Tensor
  -> Ptr IntArray
  -> IO (())
_histogramdd_bin_edges_out_ltl :: Ptr TensorList -> Ptr Tensor -> Ptr IntArray -> IO ()
_histogramdd_bin_edges_out_ltl Ptr TensorList
_out Ptr Tensor
_self Ptr IntArray
_bins =
  [C.throwBlock| void {  (at::_histogramdd_bin_edges_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)));
  }|]

_histogramdd_from_bin_cts_out_ttlatb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr (StdVector CDouble)
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
_histogramdd_from_bin_cts_out_ttlatb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_out_ttlatb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight CBool
_density =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)
  , *$(std::vector<double>* _range)
  , *$(at::Tensor* _weight)
  , $(bool _density)));
  }|]

_histogramdd_from_bin_cts_out_ttlat
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr (StdVector CDouble)
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_histogramdd_from_bin_cts_out_ttlat :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_out_ttlat Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)
  , *$(std::vector<double>* _range)
  , *$(at::Tensor* _weight)));
  }|]

_histogramdd_from_bin_cts_out_ttla
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Ptr (StdVector CDouble)
  -> IO (Ptr Tensor)
_histogramdd_from_bin_cts_out_ttla :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_out_ttla Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<int64_t>* _bins)
  , *$(std::vector<double>* _range)));
  }|]

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

_histogramdd_from_bin_tensors_out_ttltb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr TensorList
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_out_ttltb :: Ptr Tensor
-> Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_out_ttltb Ptr Tensor
_out Ptr Tensor
_self Ptr TensorList
_bins Ptr Tensor
_weight CBool
_density =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Tensor>* _bins)
  , *$(at::Tensor* _weight)
  , $(bool _density)));
  }|]

_histogramdd_from_bin_tensors_out_ttlt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr TensorList
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_out_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr TensorList -> Ptr Tensor -> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_out_ttlt Ptr Tensor
_out Ptr Tensor
_self Ptr TensorList
_bins Ptr Tensor
_weight =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(std::vector<at::Tensor>* _bins)
  , *$(at::Tensor* _weight)));
  }|]

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

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

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

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

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

unfold_backward_out_ttllll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr IntArray
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
unfold_backward_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
unfold_backward_out_ttllll Ptr Tensor
_out Ptr Tensor
_grad_in Ptr IntArray
_input_sizes Int64
_dim Int64
_size Int64
_step =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::unfold_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_in)
  , *$(std::vector<int64_t>* _input_sizes)
  , $(int64_t _dim)
  , $(int64_t _size)
  , $(int64_t _step)));
  }|]

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

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

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

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

_amp_foreach_non_finite_check_and_unscale_out_lltt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (())
_amp_foreach_non_finite_check_and_unscale_out_lltt :: Ptr TensorList
-> Ptr TensorList -> Ptr Tensor -> Ptr Tensor -> IO ()
_amp_foreach_non_finite_check_and_unscale_out_lltt Ptr TensorList
_out Ptr TensorList
_self Ptr Tensor
_found_inf Ptr Tensor
_inv_scale =
  [C.throwBlock| void {  (at::_amp_foreach_non_finite_check_and_unscale_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Tensor* _found_inf)
  , *$(at::Tensor* _inv_scale)));
  }|]

_amp_foreach_non_finite_check_and_unscale_ltt
  :: Ptr TensorList
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(TensorList,Tensor)))
_amp_foreach_non_finite_check_and_unscale_ltt :: Ptr TensorList
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(TensorList, Tensor)))
_amp_foreach_non_finite_check_and_unscale_ltt Ptr TensorList
_self Ptr Tensor
_found_inf Ptr Tensor
_inv_scale =
  [C.throwBlock| std::tuple<std::vector<at::Tensor>,at::Tensor>* { return new std::tuple<std::vector<at::Tensor>,at::Tensor>(at::_amp_foreach_non_finite_check_and_unscale(
    *$(std::vector<at::Tensor>* _self)
  , *$(at::Tensor* _found_inf)
  , *$(at::Tensor* _inv_scale)));
  }|]

_amp_update_scale_out_ttttddl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> Int64
  -> IO (Ptr Tensor)
_amp_update_scale_out_ttttddl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (Ptr Tensor)
_amp_update_scale_out_ttttddl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_growth_tracker Ptr Tensor
_found_inf CDouble
_scale_growth_factor CDouble
_scale_backoff_factor Int64
_growth_interval =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_amp_update_scale_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _growth_tracker)
  , *$(at::Tensor* _found_inf)
  , $(double _scale_growth_factor)
  , $(double _scale_backoff_factor)
  , $(int64_t _growth_interval)));
  }|]

_amp_update_scale_tttddl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> CDouble
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_amp_update_scale_tttddl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_amp_update_scale_tttddl Ptr Tensor
_self Ptr Tensor
_growth_tracker Ptr Tensor
_found_inf CDouble
_scale_growth_factor CDouble
_scale_backoff_factor Int64
_growth_interval =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_amp_update_scale(
    *$(at::Tensor* _self)
  , *$(at::Tensor* _growth_tracker)
  , *$(at::Tensor* _found_inf)
  , $(double _scale_growth_factor)
  , $(double _scale_backoff_factor)
  , $(int64_t _growth_interval)));
  }|]

_foreach_add_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_add_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_add_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_add_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_sub_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_sub_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_sub_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_sub_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_mul_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_mul_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_mul_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_mul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_div_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_div_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_div_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_div_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_clamp_min_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_clamp_min_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_clamp_min_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_clamp_min_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_clamp_max_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_clamp_max_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_clamp_max_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_clamp_max_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_maximum_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_maximum_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_maximum_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_maximum_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_minimum_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_minimum_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_minimum_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_scalar =
  [C.throwBlock| void {  (at::_foreach_minimum_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _scalar)));
  }|]

_foreach_add_out_llls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_add_out_llls :: Ptr TensorList
-> Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_add_out_llls Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other Ptr Scalar
_alpha =
  [C.throwBlock| void {  (at::_foreach_add_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)
  , *$(at::Scalar* _alpha)));
  }|]

_foreach_add_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_add_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_add_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_add_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_sub_out_llls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_sub_out_llls :: Ptr TensorList
-> Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_sub_out_llls Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other Ptr Scalar
_alpha =
  [C.throwBlock| void {  (at::_foreach_sub_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)
  , *$(at::Scalar* _alpha)));
  }|]

_foreach_sub_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_sub_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_sub_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_sub_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_mul_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_mul_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_mul_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_mul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_div_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_div_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_div_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_div_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_clamp_min_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_clamp_min_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_clamp_min_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_clamp_min_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_clamp_max_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_clamp_max_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_clamp_max_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_clamp_max_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_maximum_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_maximum_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_maximum_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_maximum_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_minimum_out_lll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_minimum_out_lll :: Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_minimum_out_lll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_other =
  [C.throwBlock| void {  (at::_foreach_minimum_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _other)));
  }|]

_foreach_add_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_add_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_add_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_add_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_sub_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_sub_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_sub_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_sub_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_div_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_div_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_div_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_div_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_mul_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_mul_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_mul_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_mul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_clamp_min_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_clamp_min_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_clamp_min_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_clamp_min_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_clamp_max_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_clamp_max_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_clamp_max_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_clamp_max_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_maximum_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_maximum_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_maximum_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_maximum_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_minimum_out_llA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_minimum_out_llA :: Ptr TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
_foreach_minimum_out_llA Ptr TensorList
_out Ptr TensorList
_self Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_minimum_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_exp_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_exp_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_exp_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_exp_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_zero_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_zero_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_zero_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_zero_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

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

_foreach_sqrt_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_sqrt_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_sqrt_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_sqrt_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_abs_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_abs_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_abs_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_abs_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_acos_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_acos_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_acos_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_acos_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_asin_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_asin_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_asin_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_asin_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_atan_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_atan_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_atan_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_atan_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_ceil_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_ceil_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_ceil_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_ceil_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_cos_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_cos_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_cos_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_cos_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_cosh_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_cosh_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_cosh_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_cosh_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_erf_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_erf_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_erf_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_erf_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_erfc_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_erfc_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_erfc_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_erfc_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_expm1_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_expm1_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_expm1_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_expm1_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_floor_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_floor_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_floor_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_floor_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_log_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_log_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_log_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_log_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_log10_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_log10_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_log10_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_log10_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_log1p_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_log1p_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_log1p_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_log1p_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_log2_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_log2_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_log2_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_log2_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_neg_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_neg_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_neg_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_neg_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_tan_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_tan_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_tan_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_tan_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_tanh_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_tanh_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_tanh_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_tanh_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_sin_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_sin_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_sin_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_sin_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_sinh_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_sinh_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_sinh_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_sinh_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_round_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_round_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_round_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_round_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_lgamma_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_lgamma_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_lgamma_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_lgamma_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_frac_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_frac_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_frac_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_frac_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_reciprocal_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_reciprocal_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_reciprocal_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_reciprocal_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_sigmoid_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_sigmoid_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_sigmoid_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_sigmoid_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_trunc_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_trunc_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_trunc_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_trunc_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_addcdiv_out_lllls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_addcdiv_out_lllls :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr Scalar
-> IO ()
_foreach_addcdiv_out_lllls Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 Ptr Scalar
_value =
  [C.throwBlock| void {  (at::_foreach_addcdiv_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)
  , *$(at::Scalar* _value)));
  }|]

_foreach_addcdiv_out_llll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_addcdiv_out_llll :: Ptr TensorList
-> Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_addcdiv_out_llll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 =
  [C.throwBlock| void {  (at::_foreach_addcdiv_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)));
  }|]

_foreach_addcmul_out_lllls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_addcmul_out_lllls :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr Scalar
-> IO ()
_foreach_addcmul_out_lllls Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 Ptr Scalar
_value =
  [C.throwBlock| void {  (at::_foreach_addcmul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)
  , *$(at::Scalar* _value)));
  }|]

_foreach_addcmul_out_llll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_addcmul_out_llll :: Ptr TensorList
-> Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_addcmul_out_llll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 =
  [C.throwBlock| void {  (at::_foreach_addcmul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)));
  }|]

_foreach_addcdiv_out_llllA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_addcdiv_out_llllA :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr (StdVector Scalar)
-> IO ()
_foreach_addcdiv_out_llllA Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_addcdiv_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_addcdiv_out_llllt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Tensor
  -> IO (())
_foreach_addcdiv_out_llllt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr Tensor
-> IO ()
_foreach_addcdiv_out_llllt Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 Ptr Tensor
_scalars =
  [C.throwBlock| void {  (at::_foreach_addcdiv_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)
  , *$(at::Tensor* _scalars)));
  }|]

_foreach_addcmul_out_llllA
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr (StdVector Scalar)
  -> IO (())
_foreach_addcmul_out_llllA :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr (StdVector Scalar)
-> IO ()
_foreach_addcmul_out_llllA Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 Ptr (StdVector Scalar)
_scalars =
  [C.throwBlock| void {  (at::_foreach_addcmul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)
  , *$(std::vector<at::Scalar>* _scalars)));
  }|]

_foreach_addcmul_out_llllt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Tensor
  -> IO (())
_foreach_addcmul_out_llllt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr Tensor
-> IO ()
_foreach_addcmul_out_llllt Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensor1 Ptr TensorList
_tensor2 Ptr Tensor
_scalars =
  [C.throwBlock| void {  (at::_foreach_addcmul_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensor1)
  , *$(std::vector<at::Tensor>* _tensor2)
  , *$(at::Tensor* _scalars)));
  }|]

_foreach_norm_out_lls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_norm_out_lls :: Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_norm_out_lls Ptr TensorList
_out Ptr TensorList
_self Ptr Scalar
_ord =
  [C.throwBlock| void {  (at::_foreach_norm_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(at::Scalar* _ord)));
  }|]

_foreach_norm_out_ll
  :: Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_norm_out_ll :: Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_norm_out_ll Ptr TensorList
_out Ptr TensorList
_self =
  [C.throwBlock| void {  (at::_foreach_norm_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)));
  }|]

_foreach_lerp_out_llll
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> IO (())
_foreach_lerp_out_llll :: Ptr TensorList
-> Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
_foreach_lerp_out_llll Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensors1 Ptr TensorList
_weights =
  [C.throwBlock| void {  (at::_foreach_lerp_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensors1)
  , *$(std::vector<at::Tensor>* _weights)));
  }|]

_foreach_lerp_out_llls
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr Scalar
  -> IO (())
_foreach_lerp_out_llls :: Ptr TensorList
-> Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
_foreach_lerp_out_llls Ptr TensorList
_out Ptr TensorList
_self Ptr TensorList
_tensors1 Ptr Scalar
_weight =
  [C.throwBlock| void {  (at::_foreach_lerp_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(std::vector<at::Tensor>* _self)
  , *$(std::vector<at::Tensor>* _tensors1)
  , *$(at::Scalar* _weight)));
  }|]

bucketize_out_tstbb
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
bucketize_out_tstbb :: Ptr Tensor
-> Ptr Scalar -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
bucketize_out_tstbb Ptr Tensor
_out Ptr Scalar
_self Ptr Tensor
_boundaries CBool
_out_int32 CBool
_right =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::bucketize_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _self)
  , *$(at::Tensor* _boundaries)
  , $(bool _out_int32)
  , $(bool _right)));
  }|]

bucketize_out_tstb
  :: Ptr Tensor
  -> Ptr Scalar
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr Tensor)
bucketize_out_tstb :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
bucketize_out_tstb Ptr Tensor
_out Ptr Scalar
_self Ptr Tensor
_boundaries CBool
_out_int32 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::bucketize_out(
    *$(at::Tensor* _out)
  , *$(at::Scalar* _self)
  , *$(at::Tensor* _boundaries)
  , $(bool _out_int32)));
  }|]

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

searchsorted_out_ttsbbst
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> CBool
  -> Ptr StdString
  -> Ptr Tensor
  -> IO (Ptr Tensor)
searchsorted_out_ttsbbst :: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> CBool
-> CBool
-> Ptr StdString
-> Ptr Tensor
-> IO (Ptr Tensor)
searchsorted_out_ttsbbst Ptr Tensor
_out Ptr Tensor
_sorted_sequence Ptr Scalar
_self CBool
_out_int32 CBool
_right Ptr StdString
_side Ptr Tensor
_sorter =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::searchsorted_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _sorted_sequence)
  , *$(at::Scalar* _self)
  , $(bool _out_int32)
  , $(bool _right)
  , *$(std::string* _side)
  , *$(at::Tensor* _sorter)));
  }|]

searchsorted_out_ttsbbs
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> CBool
  -> Ptr StdString
  -> IO (Ptr Tensor)
searchsorted_out_ttsbbs :: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> CBool
-> CBool
-> Ptr StdString
-> IO (Ptr Tensor)
searchsorted_out_ttsbbs Ptr Tensor
_out Ptr Tensor
_sorted_sequence Ptr Scalar
_self CBool
_out_int32 CBool
_right Ptr StdString
_side =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::searchsorted_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _sorted_sequence)
  , *$(at::Scalar* _self)
  , $(bool _out_int32)
  , $(bool _right)
  , *$(std::string* _side)));
  }|]

searchsorted_out_ttsbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
searchsorted_out_ttsbb :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> CBool -> CBool -> IO (Ptr Tensor)
searchsorted_out_ttsbb Ptr Tensor
_out Ptr Tensor
_sorted_sequence Ptr Scalar
_self CBool
_out_int32 CBool
_right =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::searchsorted_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _sorted_sequence)
  , *$(at::Scalar* _self)
  , $(bool _out_int32)
  , $(bool _right)));
  }|]

searchsorted_out_ttsb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> CBool
  -> IO (Ptr Tensor)
searchsorted_out_ttsb :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> CBool -> IO (Ptr Tensor)
searchsorted_out_ttsb Ptr Tensor
_out Ptr Tensor
_sorted_sequence Ptr Scalar
_self CBool
_out_int32 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::searchsorted_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _sorted_sequence)
  , *$(at::Scalar* _self)
  , $(bool _out_int32)));
  }|]

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

glu_jvp_out_ttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
glu_jvp_out_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
glu_jvp_out_ttttl Ptr Tensor
_out Ptr Tensor
_glu Ptr Tensor
_x Ptr Tensor
_dx Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::glu_jvp_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _glu)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _dx)
  , $(int64_t _dim)));
  }|]

glu_backward_jvp_out_ttttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
glu_backward_jvp_out_ttttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
glu_backward_jvp_out_ttttttl Ptr Tensor
_out Ptr Tensor
_grad_x Ptr Tensor
_grad_glu Ptr Tensor
_x Ptr Tensor
_dgrad_glu Ptr Tensor
_dx Int64
_dim =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::glu_backward_jvp_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_x)
  , *$(at::Tensor* _grad_glu)
  , *$(at::Tensor* _x)
  , *$(at::Tensor* _dgrad_glu)
  , *$(at::Tensor* _dx)
  , $(int64_t _dim)));
  }|]

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

rrelu_with_noise_backward_out_ttttssbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Scalar
  -> Ptr Scalar
  -> CBool
  -> CBool
  -> IO (Ptr Tensor)
rrelu_with_noise_backward_out_ttttssbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> CBool
-> CBool
-> IO (Ptr Tensor)
rrelu_with_noise_backward_out_ttttssbb Ptr Tensor
_out Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_noise Ptr Scalar
_lower Ptr Scalar
_upper CBool
_training CBool
_self_is_result =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::rrelu_with_noise_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad_output)
  , *$(at::Tensor* _self)
  , *$(at::Tensor* _noise)
  , *$(at::Scalar* _lower)
  , *$(at::Scalar* _upper)
  , $(bool _training)
  , $(bool _self_is_result)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_test_optional_floatlist_out_tta
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr (StdVector CDouble)
  -> IO (Ptr Tensor)
_test_optional_floatlist_out_tta :: Ptr Tensor
-> Ptr Tensor -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
_test_optional_floatlist_out_tta Ptr Tensor
_out Ptr Tensor
_values Ptr (StdVector CDouble)
_addends =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_test_optional_floatlist_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _values)
  , *$(std::vector<double>* _addends)));
  }|]

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

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

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

segment_reduce_out_ttstttlbs
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> Ptr Scalar
  -> IO (Ptr Tensor)
segment_reduce_out_ttstttlbs :: Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Ptr Scalar
-> IO (Ptr Tensor)
segment_reduce_out_ttstttlbs Ptr Tensor
_out Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_indices Ptr Tensor
_offsets Int64
_axis CBool
_unsafe Ptr Scalar
_initial =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::segment_reduce_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(int64_t _axis)
  , $(bool _unsafe)
  , *$(at::Scalar* _initial)));
  }|]

segment_reduce_out_ttstttlb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> CBool
  -> IO (Ptr Tensor)
segment_reduce_out_ttstttlb :: Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr Tensor)
segment_reduce_out_ttstttlb Ptr Tensor
_out Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_indices Ptr Tensor
_offsets Int64
_axis CBool
_unsafe =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::segment_reduce_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(int64_t _axis)
  , $(bool _unsafe)));
  }|]

segment_reduce_out_ttstttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
segment_reduce_out_ttstttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
segment_reduce_out_ttstttl Ptr Tensor
_out Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_indices Ptr Tensor
_offsets Int64
_axis =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::segment_reduce_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)
  , $(int64_t _axis)));
  }|]

segment_reduce_out_ttsttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
segment_reduce_out_ttsttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
segment_reduce_out_ttsttt Ptr Tensor
_out Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_indices Ptr Tensor
_offsets =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::segment_reduce_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _indices)
  , *$(at::Tensor* _offsets)));
  }|]

segment_reduce_out_ttstt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
segment_reduce_out_ttstt :: Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
segment_reduce_out_ttstt Ptr Tensor
_out Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_indices =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::segment_reduce_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _indices)));
  }|]

segment_reduce_out_ttst
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> IO (Ptr Tensor)
segment_reduce_out_ttst :: Ptr Tensor
-> Ptr Tensor -> Ptr StdString -> Ptr Tensor -> IO (Ptr Tensor)
segment_reduce_out_ttst Ptr Tensor
_out Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::segment_reduce_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)));
  }|]

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

_segment_reduce_backward_out_ttttsttls
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Ptr Scalar
  -> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttsttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Scalar
-> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttsttls Ptr Tensor
_out Ptr Tensor
_grad Ptr Tensor
_output Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_offsets Int64
_axis Ptr Scalar
_initial =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_segment_reduce_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _offsets)
  , $(int64_t _axis)
  , *$(at::Scalar* _initial)));
  }|]

_segment_reduce_backward_out_ttttsttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttsttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttsttl Ptr Tensor
_out Ptr Tensor
_grad Ptr Tensor
_output Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_offsets Int64
_axis =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_segment_reduce_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _offsets)
  , $(int64_t _axis)));
  }|]

_segment_reduce_backward_out_ttttstt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttstt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttstt Ptr Tensor
_out Ptr Tensor
_grad Ptr Tensor
_output Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths Ptr Tensor
_offsets =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_segment_reduce_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)
  , *$(at::Tensor* _offsets)));
  }|]

_segment_reduce_backward_out_ttttst
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttst :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> Ptr Tensor
-> IO (Ptr Tensor)
_segment_reduce_backward_out_ttttst Ptr Tensor
_out Ptr Tensor
_grad Ptr Tensor
_output Ptr Tensor
_data Ptr StdString
_reduce Ptr Tensor
_lengths =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_segment_reduce_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)
  , *$(at::Tensor* _lengths)));
  }|]

_segment_reduce_backward_out_tttts
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr StdString
  -> IO (Ptr Tensor)
_segment_reduce_backward_out_tttts :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
_segment_reduce_backward_out_tttts Ptr Tensor
_out Ptr Tensor
_grad Ptr Tensor
_output Ptr Tensor
_data Ptr StdString
_reduce =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_segment_reduce_backward_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _grad)
  , *$(at::Tensor* _output)
  , *$(at::Tensor* _data)
  , *$(std::string* _reduce)));
  }|]

_nested_tensor_from_tensor_list_out_tlsLDb
  :: Ptr Tensor
  -> Ptr TensorList
  -> ScalarType
  -> Layout
  -> DeviceType
  -> CBool
  -> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tlsLDb :: Ptr Tensor
-> Ptr TensorList
-> ScalarType
-> ScalarType
-> DeviceType
-> CBool
-> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tlsLDb Ptr Tensor
_out Ptr TensorList
_list ScalarType
_dtype ScalarType
_layout DeviceType
_device CBool
_pin_memory =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_nested_tensor_from_tensor_list_out(
    *$(at::Tensor* _out)
  , *$(std::vector<at::Tensor>* _list)
  , $(at::ScalarType _dtype)
  , $(at::Layout _layout)
  , $(at::DeviceType _device)
  , $(bool _pin_memory)));
  }|]

_nested_tensor_from_tensor_list_out_tlsLD
  :: Ptr Tensor
  -> Ptr TensorList
  -> ScalarType
  -> Layout
  -> DeviceType
  -> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tlsLD :: Ptr Tensor
-> Ptr TensorList
-> ScalarType
-> ScalarType
-> DeviceType
-> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tlsLD Ptr Tensor
_out Ptr TensorList
_list ScalarType
_dtype ScalarType
_layout DeviceType
_device =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_nested_tensor_from_tensor_list_out(
    *$(at::Tensor* _out)
  , *$(std::vector<at::Tensor>* _list)
  , $(at::ScalarType _dtype)
  , $(at::Layout _layout)
  , $(at::DeviceType _device)));
  }|]

_nested_tensor_from_tensor_list_out_tlsL
  :: Ptr Tensor
  -> Ptr TensorList
  -> ScalarType
  -> Layout
  -> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tlsL :: Ptr Tensor
-> Ptr TensorList -> ScalarType -> ScalarType -> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tlsL Ptr Tensor
_out Ptr TensorList
_list ScalarType
_dtype ScalarType
_layout =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_nested_tensor_from_tensor_list_out(
    *$(at::Tensor* _out)
  , *$(std::vector<at::Tensor>* _list)
  , $(at::ScalarType _dtype)
  , $(at::Layout _layout)));
  }|]

_nested_tensor_from_tensor_list_out_tls
  :: Ptr Tensor
  -> Ptr TensorList
  -> ScalarType
  -> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tls :: Ptr Tensor -> Ptr TensorList -> ScalarType -> IO (Ptr Tensor)
_nested_tensor_from_tensor_list_out_tls Ptr Tensor
_out Ptr TensorList
_list ScalarType
_dtype =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_nested_tensor_from_tensor_list_out(
    *$(at::Tensor* _out)
  , *$(std::vector<at::Tensor>* _list)
  , $(at::ScalarType _dtype)));
  }|]

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

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

_make_dual_copy_out_tttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_make_dual_copy_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
_make_dual_copy_out_tttl Ptr Tensor
_out Ptr Tensor
_primal Ptr Tensor
_tangent Int64
_level =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_make_dual_copy_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _primal)
  , *$(at::Tensor* _tangent)
  , $(int64_t _level)));
  }|]

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

unfold_copy_out_ttlll
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (Ptr Tensor)
unfold_copy_out_ttlll :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
unfold_copy_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Int64
_dimension Int64
_size Int64
_step =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::unfold_copy_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(int64_t _dimension)
  , $(int64_t _size)
  , $(int64_t _step)));
  }|]

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

to_padded_tensor_out_ttdl
  :: Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> Ptr IntArray
  -> IO (Ptr Tensor)
to_padded_tensor_out_ttdl :: Ptr Tensor
-> Ptr Tensor -> CDouble -> Ptr IntArray -> IO (Ptr Tensor)
to_padded_tensor_out_ttdl Ptr Tensor
_out Ptr Tensor
_self CDouble
_padding Ptr IntArray
_output_size =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::to_padded_tensor_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _self)
  , $(double _padding)
  , *$(std::vector<int64_t>* _output_size)));
  }|]

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

_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttttl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CDouble
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> IO (Ptr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttttl :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CDouble
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttttl Ptr Tensor
_out Ptr Tensor
_src Int64
_embed_dim Int64
_num_heads Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias CBool
_use_gelu CBool
_norm_first CDouble
_eps Ptr Tensor
_norm_weight_1 Ptr Tensor
_norm_bias_1 Ptr Tensor
_norm_weight_2 Ptr Tensor
_norm_bias_2 Ptr Tensor
_ffn_weight_1 Ptr Tensor
_ffn_bias_1 Ptr Tensor
_ffn_weight_2 Ptr Tensor
_ffn_bias_2 Ptr Tensor
_mask Int64
_mask_type =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_transformer_encoder_layer_fwd_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _src)
  , $(int64_t _embed_dim)
  , $(int64_t _num_heads)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , $(bool _use_gelu)
  , $(bool _norm_first)
  , $(double _eps)
  , *$(at::Tensor* _norm_weight_1)
  , *$(at::Tensor* _norm_bias_1)
  , *$(at::Tensor* _norm_weight_2)
  , *$(at::Tensor* _norm_bias_2)
  , *$(at::Tensor* _ffn_weight_1)
  , *$(at::Tensor* _ffn_bias_1)
  , *$(at::Tensor* _ffn_weight_2)
  , *$(at::Tensor* _ffn_bias_2)
  , *$(at::Tensor* _mask)
  , $(int64_t _mask_type)));
  }|]

_transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CDouble
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CDouble
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt Ptr Tensor
_out Ptr Tensor
_src Int64
_embed_dim Int64
_num_heads Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias CBool
_use_gelu CBool
_norm_first CDouble
_eps Ptr Tensor
_norm_weight_1 Ptr Tensor
_norm_bias_1 Ptr Tensor
_norm_weight_2 Ptr Tensor
_norm_bias_2 Ptr Tensor
_ffn_weight_1 Ptr Tensor
_ffn_bias_1 Ptr Tensor
_ffn_weight_2 Ptr Tensor
_ffn_bias_2 Ptr Tensor
_mask =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_transformer_encoder_layer_fwd_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _src)
  , $(int64_t _embed_dim)
  , $(int64_t _num_heads)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , $(bool _use_gelu)
  , $(bool _norm_first)
  , $(double _eps)
  , *$(at::Tensor* _norm_weight_1)
  , *$(at::Tensor* _norm_bias_1)
  , *$(at::Tensor* _norm_weight_2)
  , *$(at::Tensor* _norm_bias_2)
  , *$(at::Tensor* _ffn_weight_1)
  , *$(at::Tensor* _ffn_bias_1)
  , *$(at::Tensor* _ffn_weight_2)
  , *$(at::Tensor* _ffn_bias_2)
  , *$(at::Tensor* _mask)));
  }|]

_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> CDouble
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CDouble
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt Ptr Tensor
_out Ptr Tensor
_src Int64
_embed_dim Int64
_num_heads Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias CBool
_use_gelu CBool
_norm_first CDouble
_eps Ptr Tensor
_norm_weight_1 Ptr Tensor
_norm_bias_1 Ptr Tensor
_norm_weight_2 Ptr Tensor
_norm_bias_2 Ptr Tensor
_ffn_weight_1 Ptr Tensor
_ffn_bias_1 Ptr Tensor
_ffn_weight_2 Ptr Tensor
_ffn_bias_2 =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_transformer_encoder_layer_fwd_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _src)
  , $(int64_t _embed_dim)
  , $(int64_t _num_heads)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , $(bool _use_gelu)
  , $(bool _norm_first)
  , $(double _eps)
  , *$(at::Tensor* _norm_weight_1)
  , *$(at::Tensor* _norm_bias_1)
  , *$(at::Tensor* _norm_weight_2)
  , *$(at::Tensor* _norm_bias_2)
  , *$(at::Tensor* _ffn_weight_1)
  , *$(at::Tensor* _ffn_bias_1)
  , *$(at::Tensor* _ffn_weight_2)
  , *$(at::Tensor* _ffn_bias_2)));
  }|]

_native_multi_head_attention_out_tttttlltttttbbl
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> Int64
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttlltttttbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttlltttttbbl Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias Ptr Tensor
_mask CBool
_need_weights CBool
_average_attn_weights Int64
_mask_type =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_native_multi_head_attention_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , *$(at::Tensor* _mask)
  , $(bool _need_weights)
  , $(bool _average_attn_weights)
  , $(int64_t _mask_type)));
  }|]

_native_multi_head_attention_out_tttttlltttttbb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttlltttttbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttlltttttbb Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias Ptr Tensor
_mask CBool
_need_weights CBool
_average_attn_weights =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_native_multi_head_attention_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , *$(at::Tensor* _mask)
  , $(bool _need_weights)
  , $(bool _average_attn_weights)));
  }|]

_native_multi_head_attention_out_tttttlltttttb
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CBool
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttlltttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttlltttttb Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias Ptr Tensor
_mask CBool
_need_weights =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_native_multi_head_attention_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , *$(at::Tensor* _mask)
  , $(bool _need_weights)));
  }|]

_native_multi_head_attention_out_tttttllttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttllttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttllttttt Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias Ptr Tensor
_mask =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_native_multi_head_attention_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , *$(at::Tensor* _mask)));
  }|]

_native_multi_head_attention_out_tttttlltttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttlltttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttlltttt Ptr Tensor
_out0 Ptr Tensor
_out1 Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias =
  [C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_native_multi_head_attention_out(
    *$(at::Tensor* _out0)
  , *$(at::Tensor* _out1)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)));
  }|]

_triton_scaled_dot_attention_out_ttttd
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> CDouble
  -> IO (Ptr Tensor)
_triton_scaled_dot_attention_out_ttttd :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
_triton_scaled_dot_attention_out_ttttd Ptr Tensor
_out Ptr Tensor
_q Ptr Tensor
_k Ptr Tensor
_v CDouble
_dropout_p =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_triton_scaled_dot_attention_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _q)
  , *$(at::Tensor* _k)
  , *$(at::Tensor* _v)
  , $(double _dropout_p)));
  }|]

_triton_scaled_dot_attention_out_tttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_triton_scaled_dot_attention_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_triton_scaled_dot_attention_out_tttt Ptr Tensor
_out Ptr Tensor
_q Ptr Tensor
_k Ptr Tensor
_v =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_triton_scaled_dot_attention_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _q)
  , *$(at::Tensor* _k)
  , *$(at::Tensor* _v)));
  }|]

_triton_multi_head_attention_out_ttttllttttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_triton_multi_head_attention_out_ttttllttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_triton_multi_head_attention_out_ttttllttttt Ptr Tensor
_out Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias Ptr Tensor
_mask =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_triton_multi_head_attention_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)
  , *$(at::Tensor* _mask)));
  }|]

_triton_multi_head_attention_out_ttttlltttt
  :: Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Int64
  -> Int64
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> Ptr Tensor
  -> IO (Ptr Tensor)
_triton_multi_head_attention_out_ttttlltttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_triton_multi_head_attention_out_ttttlltttt Ptr Tensor
_out Ptr Tensor
_query Ptr Tensor
_key Ptr Tensor
_value Int64
_embed_dim Int64
_num_head Ptr Tensor
_qkv_weight Ptr Tensor
_qkv_bias Ptr Tensor
_proj_weight Ptr Tensor
_proj_bias =
  [C.throwBlock| at::Tensor* { return new at::Tensor(at::_triton_multi_head_attention_out(
    *$(at::Tensor* _out)
  , *$(at::Tensor* _query)
  , *$(at::Tensor* _key)
  , *$(at::Tensor* _value)
  , $(int64_t _embed_dim)
  , $(int64_t _num_head)
  , *$(at::Tensor* _qkv_weight)
  , *$(at::Tensor* _qkv_bias)
  , *$(at::Tensor* _proj_weight)
  , *$(at::Tensor* _proj_bias)));
  }|]

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

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

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

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

_fused_adam_out_llllllldddddbbtt
  :: Ptr TensorList
  -> 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_out_llllllldddddbbtt :: Ptr TensorList
-> 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_out_llllllldddddbbtt Ptr TensorList
_out 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_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(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_out_llllllldddddbbt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr Tensor
  -> IO (())
_fused_adam_out_llllllldddddbbt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> IO ()
_fused_adam_out_llllllldddddbbt Ptr TensorList
_out 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_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(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_out_llllllldddddbb
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> IO (())
_fused_adam_out_llllllldddddbb :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO ()
_fused_adam_out_llllllldddddbb Ptr TensorList
_out 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_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(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_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 (Ptr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_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
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_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| std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>* { return new std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>(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 (Ptr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_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
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_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| std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>* { return new std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>(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 (Ptr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_fused_adam_lllllldddddbb :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_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| std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>* { return new std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>(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_out_llllllldddddbbtt
  :: Ptr TensorList
  -> 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_out_llllllldddddbbtt :: Ptr TensorList
-> 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_out_llllllldddddbbtt Ptr TensorList
_out 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_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(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_out_llllllldddddbbt
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> Ptr Tensor
  -> IO (())
_fused_adamw_out_llllllldddddbbt :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> IO ()
_fused_adamw_out_llllllldddddbbt Ptr TensorList
_out 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_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(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_out_llllllldddddbb
  :: Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> Ptr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> IO (())
_fused_adamw_out_llllllldddddbb :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO ()
_fused_adamw_out_llllllldddddbb Ptr TensorList
_out 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_out(
    *$(std::vector<at::Tensor>* _out)
  , *$(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 (Ptr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_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
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_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| std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>* { return new std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>(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 (Ptr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_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
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_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| std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>* { return new std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>(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 (Ptr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_fused_adamw_lllllldddddbb :: Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_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| std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>* { return new std::tuple<std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>,std::vector<at::Tensor>>(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)));
  }|]