{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Internal.Unmanaged.Native.Native12 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>"
softplus_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
softplus_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
softplus_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_beta =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _beta)));
}|]
softplus_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
softplus_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
softplus_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
softplus_tss
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
softplus_tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
softplus_tss Ptr Tensor
_self Ptr Scalar
_beta Ptr Scalar
_threshold =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus(
*$(at::Tensor* _self)
, *$(at::Scalar* _beta)
, *$(at::Scalar* _threshold)));
}|]
softplus_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
softplus_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
softplus_ts Ptr Tensor
_self Ptr Scalar
_beta =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus(
*$(at::Tensor* _self)
, *$(at::Scalar* _beta)));
}|]
softplus_t
:: Ptr Tensor
-> IO (Ptr Tensor)
softplus_t :: Ptr Tensor -> IO (Ptr Tensor)
softplus_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus(
*$(at::Tensor* _self)));
}|]
softplus_backward_out_tttss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
softplus_backward_out_tttss :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
softplus_backward_out_tttss Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Scalar
_beta Ptr Scalar
_threshold =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Scalar* _beta)
, *$(at::Scalar* _threshold)));
}|]
softplus_backward_ttss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
softplus_backward_ttss :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
softplus_backward_ttss Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Scalar
_beta Ptr Scalar
_threshold =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softplus_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Scalar* _beta)
, *$(at::Scalar* _threshold)));
}|]
softshrink_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
softshrink_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
softshrink_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_lambd =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softshrink_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _lambd)));
}|]
softshrink_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
softshrink_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
softshrink_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softshrink_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
softshrink_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
softshrink_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
softshrink_ts Ptr Tensor
_self Ptr Scalar
_lambd =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softshrink(
*$(at::Tensor* _self)
, *$(at::Scalar* _lambd)));
}|]
softshrink_t
:: Ptr Tensor
-> IO (Ptr Tensor)
softshrink_t :: Ptr Tensor -> IO (Ptr Tensor)
softshrink_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softshrink(
*$(at::Tensor* _self)));
}|]
softshrink_backward_out_ttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
softshrink_backward_out_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
softshrink_backward_out_ttts Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Scalar
_lambd =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softshrink_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Scalar* _lambd)));
}|]
softshrink_backward_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
softshrink_backward_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
softshrink_backward_tts Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Scalar
_lambd =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::softshrink_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Scalar* _lambd)));
}|]
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_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
adaptive_avg_pool2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
adaptive_avg_pool2d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
mkldnn_adaptive_avg_pool2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
mkldnn_adaptive_avg_pool2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
mkldnn_adaptive_avg_pool2d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_adaptive_avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
mkldnn_adaptive_avg_pool2d_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
mkldnn_adaptive_avg_pool2d_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
mkldnn_adaptive_avg_pool2d_backward_tt Ptr Tensor
_grad_output Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::mkldnn_adaptive_avg_pool2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)));
}|]
_adaptive_avg_pool2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_adaptive_avg_pool2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_adaptive_avg_pool2d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_adaptive_avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_adaptive_avg_pool2d_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_adaptive_avg_pool2d_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_adaptive_avg_pool2d_backward_tt Ptr Tensor
_grad_output Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_adaptive_avg_pool2d_backward(
*$(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_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
adaptive_avg_pool3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
adaptive_avg_pool3d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_adaptive_avg_pool3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_adaptive_avg_pool3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_adaptive_avg_pool3d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_adaptive_avg_pool3d(
*$(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
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_avg_pool3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)));
}|]
_adaptive_avg_pool3d_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_adaptive_avg_pool3d_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_adaptive_avg_pool3d_backward_tt Ptr Tensor
_grad_output Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_adaptive_avg_pool3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)));
}|]
adaptive_max_pool2d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
adaptive_max_pool2d_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
adaptive_max_pool2d_out_tttl Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::adaptive_max_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
adaptive_max_pool2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
adaptive_max_pool2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr (StdTuple '(Tensor, Tensor)))
adaptive_max_pool2d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::adaptive_max_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
adaptive_max_pool2d_backward_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
adaptive_max_pool2d_backward_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
adaptive_max_pool2d_backward_out_tttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_max_pool2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)));
}|]
adaptive_max_pool2d_backward_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
adaptive_max_pool2d_backward_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
adaptive_max_pool2d_backward_ttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_max_pool2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)));
}|]
adaptive_max_pool3d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
adaptive_max_pool3d_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
adaptive_max_pool3d_out_tttl Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::adaptive_max_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
adaptive_max_pool3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
adaptive_max_pool3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr (StdTuple '(Tensor, Tensor)))
adaptive_max_pool3d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::adaptive_max_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
adaptive_max_pool3d_backward_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
adaptive_max_pool3d_backward_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
adaptive_max_pool3d_backward_out_tttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_max_pool3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)));
}|]
adaptive_max_pool3d_backward_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
adaptive_max_pool3d_backward_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
adaptive_max_pool3d_backward_ttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::adaptive_max_pool3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)));
}|]
avg_pool2d_out_ttlllbbl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_out_ttlllbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_out_ttlllbbl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool2d_out_ttlllbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_out_ttlllbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_out_ttlllbb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)));
}|]
avg_pool2d_out_ttlllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_out_ttlllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_out_ttlllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)));
}|]
avg_pool2d_out_ttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_out_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
avg_pool2d_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool2d_out_ttll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
avg_pool2d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool2d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
avg_pool2d_tlllbbl
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_tlllbbl :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_tlllbbl Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool2d_tlllbb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_tlllbb :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_tlllbb Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)));
}|]
avg_pool2d_tlllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_tlllb :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool2d_tlllb Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)));
}|]
avg_pool2d_tlll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_tlll :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool2d_tlll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
avg_pool2d_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool2d_tll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
avg_pool2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool2d_tl Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
avg_pool2d_backward_out_tttlllbbl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_backward_out_tttlllbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_backward_out_tttlllbbl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool2d_backward_ttlllbbl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_backward_ttlllbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool2d_backward_ttlllbbl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool3d_out_ttlllbbl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_out_ttlllbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_out_ttlllbbl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool3d_out_ttlllbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_out_ttlllbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_out_ttlllbb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)));
}|]
avg_pool3d_out_ttlllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_out_ttlllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_out_ttlllb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)));
}|]
avg_pool3d_out_ttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_out_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_out_ttlll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
avg_pool3d_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool3d_out_ttll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
avg_pool3d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool3d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
avg_pool3d_tlllbbl
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_tlllbbl :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_tlllbbl Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool3d_tlllbb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_tlllbb :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_tlllbb Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)));
}|]
avg_pool3d_tlllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_tlllb :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
avg_pool3d_tlllb Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)));
}|]
avg_pool3d_tlll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_tlll :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool3d_tlll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
avg_pool3d_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool3d_tll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
avg_pool3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
avg_pool3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
avg_pool3d_tl Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
avg_pool3d_backward_out_tttlllbbl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_backward_out_tttlllbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_backward_out_tttlllbbl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
avg_pool3d_backward_ttlllbbl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_backward_ttlllbbl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CBool
-> Int64
-> IO (Ptr Tensor)
avg_pool3d_backward_ttlllbbl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding CBool
_ceil_mode CBool
_count_include_pad Int64
_divisor_override =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::avg_pool3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, $(bool _ceil_mode)
, $(bool _count_include_pad)
, $(int64_t _divisor_override)));
}|]
fractional_max_pool2d_out_tttllt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
fractional_max_pool2d_out_tttllt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
fractional_max_pool2d_out_tttllt Ptr Tensor
_output Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_random_samples =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::fractional_max_pool2d_out(
*$(at::Tensor* _output)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _random_samples)));
}|]
fractional_max_pool2d_tllt
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
fractional_max_pool2d_tllt :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
fractional_max_pool2d_tllt Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_random_samples =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::fractional_max_pool2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _random_samples)));
}|]
fractional_max_pool2d_backward_out_tttllt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool2d_backward_out_tttllt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool2d_backward_out_tttllt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fractional_max_pool2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _indices)));
}|]
fractional_max_pool2d_backward_ttllt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool2d_backward_ttllt :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool2d_backward_ttllt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fractional_max_pool2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _indices)));
}|]
fractional_max_pool3d_out_tttllt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
fractional_max_pool3d_out_tttllt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
fractional_max_pool3d_out_tttllt Ptr Tensor
_output Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_random_samples =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::fractional_max_pool3d_out(
*$(at::Tensor* _output)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _random_samples)));
}|]
fractional_max_pool3d_tllt
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
fractional_max_pool3d_tllt :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
fractional_max_pool3d_tllt Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_random_samples =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::fractional_max_pool3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _random_samples)));
}|]
fractional_max_pool3d_backward_out_tttllt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool3d_backward_out_tttllt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool3d_backward_out_tttllt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fractional_max_pool3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _indices)));
}|]
fractional_max_pool3d_backward_ttllt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool3d_backward_ttllt :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
fractional_max_pool3d_backward_ttllt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_output_size Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fractional_max_pool3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _output_size)
, *$(at::Tensor* _indices)));
}|]
max_pool2d_with_indices_out_tttllllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_out_tttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_out_tttllllb Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)));
}|]
max_pool2d_with_indices_out_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_out_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_out_tttllll Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
max_pool2d_with_indices_out_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_out_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_out_tttlll Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_pool2d_with_indices_out_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_out_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_out_tttll Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
max_pool2d_with_indices_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_out_tttl Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
max_pool2d_with_indices_tllllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_tllllb :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_tllllb Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)));
}|]
max_pool2d_with_indices_tllll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_tllll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_tllll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
max_pool2d_with_indices_tlll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_tlll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_tlll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_pool2d_with_indices_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_tll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_tll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
max_pool2d_with_indices_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool2d_with_indices_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool2d_with_indices_tl Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool2d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
max_pool2d_with_indices_backward_out_tttllllbt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool2d_with_indices_backward_out_tttllllbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool2d_with_indices_backward_out_tttllllbt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool2d_with_indices_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)
, *$(at::Tensor* _indices)));
}|]
max_pool2d_with_indices_backward_ttllllbt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool2d_with_indices_backward_ttllllbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool2d_with_indices_backward_ttllllbt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool2d_with_indices_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)
, *$(at::Tensor* _indices)));
}|]
max_pool3d_with_indices_out_tttllllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_out_tttllllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_out_tttllllb Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)));
}|]
max_pool3d_with_indices_out_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_out_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_out_tttllll Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
max_pool3d_with_indices_out_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_out_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_out_tttlll Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_pool3d_with_indices_out_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_out_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_out_tttll Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
max_pool3d_with_indices_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_out_tttl Ptr Tensor
_out Ptr Tensor
_indices Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _indices)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
max_pool3d_with_indices_tllllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_tllllb :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_tllllb Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)));
}|]
max_pool3d_with_indices_tllll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_tllll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_tllll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
max_pool3d_with_indices_tlll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_tlll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_tlll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_pool3d_with_indices_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_tll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_tll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)));
}|]
max_pool3d_with_indices_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
max_pool3d_with_indices_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr (StdTuple '(Tensor, Tensor)))
max_pool3d_with_indices_tl Ptr Tensor
_self Ptr IntArray
_kernel_size =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::max_pool3d_with_indices(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
max_pool3d_with_indices_backward_out_tttllllbt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool3d_with_indices_backward_out_tttllllbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool3d_with_indices_backward_out_tttllllbt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool3d_with_indices_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)
, *$(at::Tensor* _indices)));
}|]
max_pool3d_with_indices_backward_ttllllbt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool3d_with_indices_backward_ttllllbt :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO (Ptr Tensor)
max_pool3d_with_indices_backward_ttllllbt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_ceil_mode Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_pool3d_with_indices_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _ceil_mode)
, *$(at::Tensor* _indices)));
}|]
max_unpool2d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool2d_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
max_unpool2d_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)));
}|]
max_unpool2d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool2d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
max_unpool2d_ttl Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)));
}|]
max_unpool2d_backward_out_ttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool2d_backward_out_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool2d_backward_out_ttttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)));
}|]
max_unpool2d_backward_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool2d_backward_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
max_unpool2d_backward_tttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)));
}|]
max_unpool3d_out_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_out_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_out_tttlll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_unpool3d_ttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_ttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_ttlll Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_unpool3d_backward_out_ttttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_backward_out_ttttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_backward_out_ttttlll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
max_unpool3d_backward_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_backward_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
max_unpool3d_backward_tttlll Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_indices Ptr IntArray
_output_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::max_unpool3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad1d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad1d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad1d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad1d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad1d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad1d_tl Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad1d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad1d_backward_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad1d_backward_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad1d_backward_out_tttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad1d_backward_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad1d_backward_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad1d_backward_ttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad1d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad2d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad2d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad2d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad2d_tl Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad2d_backward_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad2d_backward_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad2d_backward_out_tttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad2d_backward_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad2d_backward_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad2d_backward_ttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad3d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad3d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad3d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad3d_tl Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad3d_backward_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad3d_backward_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad3d_backward_out_tttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
reflection_pad3d_backward_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
reflection_pad3d_backward_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
reflection_pad3d_backward_ttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::reflection_pad3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad1d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad1d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad1d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad1d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad1d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad1d_tl Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad1d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad1d_backward_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad1d_backward_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad1d_backward_out_tttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad1d_backward_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad1d_backward_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad1d_backward_ttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad1d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad2d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad2d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad2d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad2d_tl Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad2d_backward_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad2d_backward_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad2d_backward_out_tttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad2d_backward_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad2d_backward_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad2d_backward_ttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad3d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad3d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad3d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad3d_tl Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad3d_backward_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad3d_backward_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad3d_backward_out_tttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
replication_pad3d_backward_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
replication_pad3d_backward_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
replication_pad3d_backward_ttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::replication_pad3d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _padding)));
}|]
upsample_linear1d_tlba
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_linear1d_tlba :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_linear1d_tlba Ptr Tensor
_input Ptr IntArray
_output_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_linear1d_backward_tllba
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_linear1d_backward_tllba :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_linear1d_backward_tllba Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_bilinear2d_tlba
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bilinear2d_tlba :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bilinear2d_tlba Ptr Tensor
_input Ptr IntArray
_output_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_bilinear2d_backward_tllba
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_tllba :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_tllba Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_bilinear2d_aa_tlba
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_tlba :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_tlba Ptr Tensor
_input Ptr IntArray
_output_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_bilinear2d_aa_backward_tllba
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_tllba :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_tllba Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_trilinear3d_tlba
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_trilinear3d_tlba :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_trilinear3d_tlba Ptr Tensor
_input Ptr IntArray
_output_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_trilinear3d_backward_tllba
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllba :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllba Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_bicubic2d_tlba
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bicubic2d_tlba :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bicubic2d_tlba Ptr Tensor
_input Ptr IntArray
_output_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_bicubic2d_backward_tllba
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllba :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllba Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_bicubic2d_aa_tlba
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlba :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlba Ptr Tensor
_input Ptr IntArray
_output_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_bicubic2d_aa_backward_tllba
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllba :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllba Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_nearest1d_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest1d_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
upsample_nearest1d_tla Ptr Tensor
_input Ptr IntArray
_output_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_nearest_exact1d_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
_upsample_nearest_exact1d_tla Ptr Tensor
_input Ptr IntArray
_output_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_nearest1d_backward_tlla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest1d_backward_tlla :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest1d_backward_tlla Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_nearest_exact1d_backward_tlla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_tlla :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_tlla Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_nearest2d_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest2d_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
upsample_nearest2d_tla Ptr Tensor
_input Ptr IntArray
_output_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_nearest_exact2d_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
_upsample_nearest_exact2d_tla Ptr Tensor
_input Ptr IntArray
_output_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_nearest2d_backward_tlla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest2d_backward_tlla :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest2d_backward_tlla Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_nearest_exact2d_backward_tlla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tlla :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tlla Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_nearest3d_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest3d_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
upsample_nearest3d_tla Ptr Tensor
_input Ptr IntArray
_output_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_nearest_exact3d_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
_upsample_nearest_exact3d_tla Ptr Tensor
_input Ptr IntArray
_output_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d(
*$(at::Tensor* _input)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_nearest3d_backward_tlla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tlla :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tlla Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, *$(std::vector<double>* _scale_factors)));
}|]
_upsample_nearest_exact3d_backward_tlla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tlla :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tlla Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size Ptr (StdVector CDouble)
_scale_factors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, *$(std::vector<double>* _scale_factors)));
}|]
upsample_linear1d_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_linear1d_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_linear1d_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales)));
}|]
upsample_linear1d_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_linear1d_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_linear1d_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_linear1d_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_linear1d_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_linear1d_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_linear1d_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_linear1d_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_linear1d_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales)));
}|]
upsample_linear1d_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_linear1d_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_linear1d_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_linear1d_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_linear1d_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_linear1d_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_linear1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_bilinear2d_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bilinear2d_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
upsample_bilinear2d_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bilinear2d_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bilinear2d_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_bilinear2d_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_bilinear2d_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bilinear2d_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bilinear2d_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bilinear2d_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_bilinear2d_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bilinear2d_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
upsample_bilinear2d_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_bilinear2d_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bilinear2d_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bilinear2d_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bilinear2d_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bilinear2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
_upsample_bilinear2d_aa_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bilinear2d_aa_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bilinear2d_aa_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bilinear2d_aa_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
_upsample_bilinear2d_aa_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
_upsample_bilinear2d_aa_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bilinear2d_aa_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bilinear2d_aa_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
_upsample_bilinear2d_aa_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bilinear2d_aa_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bilinear2d_aa_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
_upsample_bilinear2d_aa_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bilinear2d_aa_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bilinear2d_aa_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bilinear2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_bicubic2d_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bicubic2d_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
upsample_bicubic2d_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bicubic2d_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_bicubic2d_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_bicubic2d_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bicubic2d_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bicubic2d_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_bicubic2d_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bicubic2d_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
upsample_bicubic2d_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_bicubic2d_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bicubic2d_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bicubic2d_aa_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bicubic2d_aa_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_out_ttlbddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbddd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_trilinear3d_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)));
}|]
upsample_trilinear3d_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_tlbddd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_tlbddd :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_tlbddd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_trilinear3d_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_trilinear3d_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_trilinear3d_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_backward_out_ttllbddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbddd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]