{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Internal.Unmanaged.Native.Native1 where
import Foreign.C.String
import Foreign.C.Types
import Foreign
import Torch.Internal.Type
import qualified Language.C.Inline.Cpp as C
import qualified Language.C.Inline.Cpp.Unsafe as C
import qualified Language.C.Inline.Context as C
import qualified Language.C.Types as C
C.context $ C.cppCtx <> mempty { C.ctxTypesTable = typeTable }
C.include "<vector>"
C.include "<ATen/Tensor.h>"
C.include "<ATen/Functions.h>"
bernoulli_tG
:: Ptr Tensor
-> Ptr Generator
-> IO (Ptr Tensor)
bernoulli_tG :: Ptr Tensor -> Ptr Generator -> IO (Ptr Tensor)
bernoulli_tG Ptr Tensor
_self Ptr Generator
_generator =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli(
*$(at::Tensor* _self)
, *$(at::Generator* _generator)));
}|]
bernoulli_t
:: Ptr Tensor
-> IO (Ptr Tensor)
bernoulli_t :: Ptr Tensor -> IO (Ptr Tensor)
bernoulli_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli(
*$(at::Tensor* _self)));
}|]
bernoulli_out_ttG
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Generator
-> IO (Ptr Tensor)
bernoulli_out_ttG :: Ptr Tensor -> Ptr Tensor -> Ptr Generator -> IO (Ptr Tensor)
bernoulli_out_ttG Ptr Tensor
_out Ptr Tensor
_self Ptr Generator
_generator =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Generator* _generator)));
}|]
bernoulli_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bernoulli_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bernoulli_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
bernoulli_tdG
:: Ptr Tensor
-> CDouble
-> Ptr Generator
-> IO (Ptr Tensor)
bernoulli_tdG :: Ptr Tensor -> CDouble -> Ptr Generator -> IO (Ptr Tensor)
bernoulli_tdG Ptr Tensor
_self CDouble
_p Ptr Generator
_generator =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli(
*$(at::Tensor* _self)
, $(double _p)
, *$(at::Generator* _generator)));
}|]
bernoulli_td
:: Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
bernoulli_td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor)
bernoulli_td Ptr Tensor
_self CDouble
_p =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bernoulli(
*$(at::Tensor* _self)
, $(double _p)));
}|]
bilinear_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bilinear_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bilinear_tttt Ptr Tensor
_input1 Ptr Tensor
_input2 Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bilinear(
*$(at::Tensor* _input1)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
bilinear_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bilinear_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bilinear_ttt Ptr Tensor
_input1 Ptr Tensor
_input2 Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bilinear(
*$(at::Tensor* _input1)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
binary_cross_entropy_tttl Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)));
}|]
binary_cross_entropy_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_ttt Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_tt Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
binary_cross_entropy_out_ttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_out_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_out_ttttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)));
}|]
binary_cross_entropy_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
binary_cross_entropy_backward_ttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_backward_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_backward_ttttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)));
}|]
binary_cross_entropy_backward_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_backward_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_backward_tttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_backward_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_backward_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_backward_ttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
binary_cross_entropy_backward_out_tttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_backward_out_tttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_backward_out_tttttl Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)));
}|]
binary_cross_entropy_backward_out_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_backward_out_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_backward_out_ttttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_backward_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_backward_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_backward_out_tttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
binary_cross_entropy_with_logits_ttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_ttttl Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Ptr Tensor
_pos_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _pos_weight)
, $(int64_t _reduction)));
}|]
binary_cross_entropy_with_logits_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_with_logits_tttt Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Ptr Tensor
_pos_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _pos_weight)));
}|]
binary_cross_entropy_with_logits_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_with_logits_ttt Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_with_logits_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_with_logits_tt Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
binary_cross_entropy_with_logits_backward_tttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_tttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_tttttl Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Ptr Tensor
_pos_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _pos_weight)
, $(int64_t _reduction)));
}|]
binary_cross_entropy_with_logits_backward_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_ttttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Ptr Tensor
_pos_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _pos_weight)));
}|]
binary_cross_entropy_with_logits_backward_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_tttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
binary_cross_entropy_with_logits_backward_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
binary_cross_entropy_with_logits_backward_ttt Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::binary_cross_entropy_with_logits_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
bincount_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
bincount_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
bincount_ttl Ptr Tensor
_self Ptr Tensor
_weights Int64
_minlength =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bincount(
*$(at::Tensor* _self)
, *$(at::Tensor* _weights)
, $(int64_t _minlength)));
}|]
bincount_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bincount_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bincount_tt Ptr Tensor
_self Ptr Tensor
_weights =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bincount(
*$(at::Tensor* _self)
, *$(at::Tensor* _weights)));
}|]
bincount_t
:: Ptr Tensor
-> IO (Ptr Tensor)
bincount_t :: Ptr Tensor -> IO (Ptr Tensor)
bincount_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bincount(
*$(at::Tensor* _self)));
}|]
bitwise_not_t
:: Ptr Tensor
-> IO (Ptr Tensor)
bitwise_not_t :: Ptr Tensor -> IO (Ptr Tensor)
bitwise_not_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_not(
*$(at::Tensor* _self)));
}|]
bitwise_not_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bitwise_not_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bitwise_not_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bitwise_not_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
copysign_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
copysign_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
copysign_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::copysign_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
copysign_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
copysign_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
copysign_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::copysign(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
copysign_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
copysign_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
copysign_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::copysign(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
copysign_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
copysign_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
copysign_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::copysign_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
logical_not_t
:: Ptr Tensor
-> IO (Ptr Tensor)
logical_not_t :: Ptr Tensor -> IO (Ptr Tensor)
logical_not_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_not(
*$(at::Tensor* _self)));
}|]
logical_not_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_not_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_not_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_not_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
logical_xor_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_xor_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_xor_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_xor(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
logical_xor_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_xor_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_xor_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_xor_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
logical_and_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_and_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_and_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_and(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
logical_and_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_and_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_and_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_and_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
logical_or_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_or_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_or_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_or(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
logical_or_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logical_or_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logical_or_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logical_or_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
blackman_window_lo
:: Int64
-> Ptr TensorOptions
-> IO (Ptr Tensor)
blackman_window_lo :: Int64 -> Ptr TensorOptions -> IO (Ptr Tensor)
blackman_window_lo Int64
_window_length Ptr TensorOptions
_options =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::blackman_window(
$(int64_t _window_length)
, *$(at::TensorOptions* _options)));
}|]
blackman_window_l
:: Int64
-> IO (Ptr Tensor)
blackman_window_l :: Int64 -> IO (Ptr Tensor)
blackman_window_l Int64
_window_length =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::blackman_window(
$(int64_t _window_length)));
}|]
blackman_window_lbo
:: Int64
-> CBool
-> Ptr TensorOptions
-> IO (Ptr Tensor)
blackman_window_lbo :: Int64 -> CBool -> Ptr TensorOptions -> IO (Ptr Tensor)
blackman_window_lbo Int64
_window_length CBool
_periodic Ptr TensorOptions
_options =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::blackman_window(
$(int64_t _window_length)
, $(bool _periodic)
, *$(at::TensorOptions* _options)));
}|]
blackman_window_lb
:: Int64
-> CBool
-> IO (Ptr Tensor)
blackman_window_lb :: Int64 -> CBool -> IO (Ptr Tensor)
blackman_window_lb Int64
_window_length CBool
_periodic =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::blackman_window(
$(int64_t _window_length)
, $(bool _periodic)));
}|]
bmm_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bmm_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bmm_tt Ptr Tensor
_self Ptr Tensor
_mat2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bmm(
*$(at::Tensor* _self)
, *$(at::Tensor* _mat2)));
}|]
bmm_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
bmm_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
bmm_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_mat2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::bmm_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _mat2)));
}|]
broadcast_tensors_l
:: Ptr TensorList
-> IO (Ptr TensorList)
broadcast_tensors_l :: Ptr TensorList -> IO (Ptr TensorList)
broadcast_tensors_l Ptr TensorList
_tensors =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::broadcast_tensors(
*$(std::vector<at::Tensor>* _tensors)));
}|]
broadcast_to_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
broadcast_to_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
broadcast_to_tl Ptr Tensor
_self Ptr IntArray
_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::broadcast_to(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _size)));
}|]
_sparse_broadcast_to_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_sparse_broadcast_to_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_sparse_broadcast_to_tl Ptr Tensor
_self Ptr IntArray
_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_sparse_broadcast_to(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _size)));
}|]
cat_ll
:: Ptr TensorList
-> Int64
-> IO (Ptr Tensor)
cat_ll :: Ptr TensorList -> Int64 -> IO (Ptr Tensor)
cat_ll Ptr TensorList
_tensors Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cat(
*$(std::vector<at::Tensor>* _tensors)
, $(int64_t _dim)));
}|]
cat_l
:: Ptr TensorList
-> IO (Ptr Tensor)
cat_l :: Ptr TensorList -> IO (Ptr Tensor)
cat_l Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cat(
*$(std::vector<at::Tensor>* _tensors)));
}|]
cat_out_tll
:: Ptr Tensor
-> Ptr TensorList
-> Int64
-> IO (Ptr Tensor)
cat_out_tll :: Ptr Tensor -> Ptr TensorList -> Int64 -> IO (Ptr Tensor)
cat_out_tll Ptr Tensor
_out Ptr TensorList
_tensors Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cat_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)
, $(int64_t _dim)));
}|]
cat_out_tl
:: Ptr Tensor
-> Ptr TensorList
-> IO (Ptr Tensor)
cat_out_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor)
cat_out_tl Ptr Tensor
_out Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cat_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)));
}|]
cat_ln
:: Ptr TensorList
-> Ptr Dimname
-> IO (Ptr Tensor)
cat_ln :: Ptr TensorList -> Ptr Dimname -> IO (Ptr Tensor)
cat_ln Ptr TensorList
_tensors Ptr Dimname
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cat(
*$(std::vector<at::Tensor>* _tensors)
, *$(at::Dimname* _dim)));
}|]
cat_out_tln
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Dimname
-> IO (Ptr Tensor)
cat_out_tln :: Ptr Tensor -> Ptr TensorList -> Ptr Dimname -> IO (Ptr Tensor)
cat_out_tln Ptr Tensor
_out Ptr TensorList
_tensors Ptr Dimname
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cat_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)
, *$(at::Dimname* _dim)));
}|]
concat_ll
:: Ptr TensorList
-> Int64
-> IO (Ptr Tensor)
concat_ll :: Ptr TensorList -> Int64 -> IO (Ptr Tensor)
concat_ll Ptr TensorList
_tensors Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::concat(
*$(std::vector<at::Tensor>* _tensors)
, $(int64_t _dim)));
}|]
concat_l
:: Ptr TensorList
-> IO (Ptr Tensor)
concat_l :: Ptr TensorList -> IO (Ptr Tensor)
concat_l Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::concat(
*$(std::vector<at::Tensor>* _tensors)));
}|]
concat_out_tll
:: Ptr Tensor
-> Ptr TensorList
-> Int64
-> IO (Ptr Tensor)
concat_out_tll :: Ptr Tensor -> Ptr TensorList -> Int64 -> IO (Ptr Tensor)
concat_out_tll Ptr Tensor
_out Ptr TensorList
_tensors Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::concat_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)
, $(int64_t _dim)));
}|]
concat_out_tl
:: Ptr Tensor
-> Ptr TensorList
-> IO (Ptr Tensor)
concat_out_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor)
concat_out_tl Ptr Tensor
_out Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::concat_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)));
}|]
concat_ln
:: Ptr TensorList
-> Ptr Dimname
-> IO (Ptr Tensor)
concat_ln :: Ptr TensorList -> Ptr Dimname -> IO (Ptr Tensor)
concat_ln Ptr TensorList
_tensors Ptr Dimname
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::concat(
*$(std::vector<at::Tensor>* _tensors)
, *$(at::Dimname* _dim)));
}|]
concat_out_tln
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Dimname
-> IO (Ptr Tensor)
concat_out_tln :: Ptr Tensor -> Ptr TensorList -> Ptr Dimname -> IO (Ptr Tensor)
concat_out_tln Ptr Tensor
_out Ptr TensorList
_tensors Ptr Dimname
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::concat_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)
, *$(at::Dimname* _dim)));
}|]
block_diag_l
:: Ptr TensorList
-> IO (Ptr Tensor)
block_diag_l :: Ptr TensorList -> IO (Ptr Tensor)
block_diag_l Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::block_diag(
*$(std::vector<at::Tensor>* _tensors)));
}|]
ceil_t
:: Ptr Tensor
-> IO (Ptr Tensor)
ceil_t :: Ptr Tensor -> IO (Ptr Tensor)
ceil_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ceil(
*$(at::Tensor* _self)));
}|]
ceil__t
:: Ptr Tensor
-> IO (Ptr Tensor)
ceil__t :: Ptr Tensor -> IO (Ptr Tensor)
ceil__t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ceil_(
*$(at::Tensor* _self)));
}|]
ceil_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ceil_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ceil_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ceil_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
chain_matmul_l
:: Ptr TensorList
-> IO (Ptr Tensor)
chain_matmul_l :: Ptr TensorList -> IO (Ptr Tensor)
chain_matmul_l Ptr TensorList
_matrices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::chain_matmul(
*$(std::vector<at::Tensor>* _matrices)));
}|]
chain_matmul_out_tl
:: Ptr Tensor
-> Ptr TensorList
-> IO (Ptr Tensor)
chain_matmul_out_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor)
chain_matmul_out_tl Ptr Tensor
_out Ptr TensorList
_matrices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::chain_matmul_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _matrices)));
}|]
unsafe_chunk_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr TensorList)
unsafe_chunk_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList)
unsafe_chunk_tll Ptr Tensor
_self Int64
_chunks Int64
_dim =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::unsafe_chunk(
*$(at::Tensor* _self)
, $(int64_t _chunks)
, $(int64_t _dim)));
}|]
unsafe_chunk_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr TensorList)
unsafe_chunk_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
unsafe_chunk_tl Ptr Tensor
_self Int64
_chunks =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::unsafe_chunk(
*$(at::Tensor* _self)
, $(int64_t _chunks)));
}|]
chunk_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr TensorList)
chunk_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList)
chunk_tll Ptr Tensor
_self Int64
_chunks Int64
_dim =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::chunk(
*$(at::Tensor* _self)
, $(int64_t _chunks)
, $(int64_t _dim)));
}|]
chunk_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr TensorList)
chunk_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
chunk_tl Ptr Tensor
_self Int64
_chunks =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::chunk(
*$(at::Tensor* _self)
, $(int64_t _chunks)));
}|]
tensor_split_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr TensorList)
tensor_split_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList)
tensor_split_tll Ptr Tensor
_self Int64
_sections Int64
_dim =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::tensor_split(
*$(at::Tensor* _self)
, $(int64_t _sections)
, $(int64_t _dim)));
}|]
tensor_split_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr TensorList)
tensor_split_tl :: Ptr Tensor -> Int64 -> IO (Ptr TensorList)
tensor_split_tl Ptr Tensor
_self Int64
_sections =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::tensor_split(
*$(at::Tensor* _self)
, $(int64_t _sections)));
}|]
tensor_split_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr TensorList)
tensor_split_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr TensorList)
tensor_split_ttl Ptr Tensor
_self Ptr Tensor
_tensor_indices_or_sections Int64
_dim =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::tensor_split(
*$(at::Tensor* _self)
, *$(at::Tensor* _tensor_indices_or_sections)
, $(int64_t _dim)));
}|]
tensor_split_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr TensorList)
tensor_split_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr TensorList)
tensor_split_tt Ptr Tensor
_self Ptr Tensor
_tensor_indices_or_sections =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::tensor_split(
*$(at::Tensor* _self)
, *$(at::Tensor* _tensor_indices_or_sections)));
}|]
clamp_tss
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clamp_tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
clamp_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_ts Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clamp_t
:: Ptr Tensor
-> IO (Ptr Tensor)
clamp_t :: Ptr Tensor -> IO (Ptr Tensor)
clamp_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
*$(at::Tensor* _self)));
}|]
clamp_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)
, *$(at::Tensor* _max)));
}|]
clamp_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_tt Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clamp__tss
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp__tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clamp__tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
clamp__ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp__ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp__ts Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clamp__t
:: Ptr Tensor
-> IO (Ptr Tensor)
clamp__t :: Ptr Tensor -> IO (Ptr Tensor)
clamp__t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
*$(at::Tensor* _self)));
}|]
clamp__ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp__ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp__ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)
, *$(at::Tensor* _max)));
}|]
clamp__tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp__tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp__tt Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clamp_out_ttss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_out_ttss :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clamp_out_ttss Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
clamp_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clamp_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
clamp_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _min)
, *$(at::Tensor* _max)));
}|]
clamp_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clamp_max_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_max_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_max_ts Ptr Tensor
_self Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_max(
*$(at::Tensor* _self)
, *$(at::Scalar* _max)));
}|]
clamp_max_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_max_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_max_tt Ptr Tensor
_self Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_max(
*$(at::Tensor* _self)
, *$(at::Tensor* _max)));
}|]
clamp_max__ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_max__ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_max__ts Ptr Tensor
_self Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_max_(
*$(at::Tensor* _self)
, *$(at::Scalar* _max)));
}|]
clamp_max__tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_max__tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_max__tt Ptr Tensor
_self Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_max_(
*$(at::Tensor* _self)
, *$(at::Tensor* _max)));
}|]
clamp_max_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_max_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_max_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_max_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _max)));
}|]
clamp_max_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_max_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_max_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_max_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _max)));
}|]
clamp_min_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_min_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_min_ts Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_min(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clamp_min_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_min_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_min_tt Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_min(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clamp_min__ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_min__ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_min__ts Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_min_(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clamp_min__tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_min__tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_min__tt Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_min_(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clamp_min_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clamp_min_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clamp_min_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_min_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clamp_min_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clamp_min_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clamp_min_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clamp_min_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clip_tss
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
clip_tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clip_tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
clip_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clip_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clip_ts Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clip_t
:: Ptr Tensor
-> IO (Ptr Tensor)
clip_t :: Ptr Tensor -> IO (Ptr Tensor)
clip_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
*$(at::Tensor* _self)));
}|]
clip_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip_ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)
, *$(at::Tensor* _max)));
}|]
clip_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip_tt Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clip__tss
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
clip__tss :: Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clip__tss Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
clip__ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clip__ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clip__ts Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
*$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clip__t
:: Ptr Tensor
-> IO (Ptr Tensor)
clip__t :: Ptr Tensor -> IO (Ptr Tensor)
clip__t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
*$(at::Tensor* _self)));
}|]
clip__ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip__ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip__ttt Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)
, *$(at::Tensor* _max)));
}|]
clip__tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip__tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip__tt Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_(
*$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
clip_out_ttss
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
clip_out_ttss :: Ptr Tensor
-> Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
clip_out_ttss Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
clip_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
clip_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
clip_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _min)));
}|]
clip_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
clip_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_min Ptr Tensor
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _min)
, *$(at::Tensor* _max)));
}|]
clip_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
clip_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
clip_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::clip_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _min)));
}|]
cudnn_is_acceptable_t
:: Ptr Tensor
-> IO (CBool)
cudnn_is_acceptable_t :: Ptr Tensor -> IO CBool
cudnn_is_acceptable_t Ptr Tensor
_self =
[C.throwBlock| bool { return (at::cudnn_is_acceptable(
*$(at::Tensor* _self)));
}|]
complex_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
complex_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
complex_tt Ptr Tensor
_real Ptr Tensor
_imag =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::complex(
*$(at::Tensor* _real)
, *$(at::Tensor* _imag)));
}|]
complex_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
complex_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
complex_out_ttt Ptr Tensor
_out Ptr Tensor
_real Ptr Tensor
_imag =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::complex_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _real)
, *$(at::Tensor* _imag)));
}|]
polar_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
polar_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
polar_tt Ptr Tensor
_abs Ptr Tensor
_angle =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::polar(
*$(at::Tensor* _abs)
, *$(at::Tensor* _angle)));
}|]
polar_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
polar_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
polar_out_ttt Ptr Tensor
_out Ptr Tensor
_abs Ptr Tensor
_angle =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::polar_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _abs)
, *$(at::Tensor* _angle)));
}|]
constant_pad_nd_tls
:: Ptr Tensor
-> Ptr IntArray
-> Ptr Scalar
-> IO (Ptr Tensor)
constant_pad_nd_tls :: Ptr Tensor -> Ptr IntArray -> Ptr Scalar -> IO (Ptr Tensor)
constant_pad_nd_tls Ptr Tensor
_self Ptr IntArray
_pad Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::constant_pad_nd(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _pad)
, *$(at::Scalar* _value)));
}|]
constant_pad_nd_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
constant_pad_nd_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
constant_pad_nd_tl Ptr Tensor
_self Ptr IntArray
_pad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::constant_pad_nd(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _pad)));
}|]
convolution_tttlllbll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_tttlllbll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_tttlllbll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::convolution(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)));
}|]
convolution_backward_tttllllblla
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool,3))
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
convolution_backward_tttllllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
convolution_backward_tttllllblla Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_weight Ptr IntArray
_bias_sizes Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups Ptr (StdArray '(CBool, 3))
_output_mask =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::convolution_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _bias_sizes)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, *$(std::array<bool,3>* _output_mask)));
}|]
convolution_overrideable_tttlllbll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_overrideable_tttlllbll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
convolution_overrideable_tttlllbll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::convolution_overrideable(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)));
}|]
convolution_backward_overrideable_tttlllblla
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool,3))
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
convolution_backward_overrideable_tttlllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
convolution_backward_overrideable_tttlllblla Ptr Tensor
_grad_output Ptr Tensor
_input Ptr Tensor
_weight Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups Ptr (StdArray '(CBool, 3))
_output_mask =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::convolution_backward_overrideable(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, *$(std::array<bool,3>* _output_mask)));
}|]
_convolution_tttlllbllbbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
_convolution_tttlllbllbbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
_convolution_tttlllbllbbbb Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups CBool
_benchmark CBool
_deterministic CBool
_cudnn_enabled CBool
_allow_tf32 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_convolution(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, $(bool _benchmark)
, $(bool _deterministic)
, $(bool _cudnn_enabled)
, $(bool _allow_tf32)));
}|]
_convolution_tttlllbllbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
_convolution_tttlllbllbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
_convolution_tttlllbllbbb Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups CBool
_benchmark CBool
_deterministic CBool
_cudnn_enabled =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_convolution(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, $(bool _benchmark)
, $(bool _deterministic)
, $(bool _cudnn_enabled)));
}|]
_convolution_mode_tttlsll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
_convolution_mode_tttlsll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
_convolution_mode_tttlsll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_convolution_mode(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
_convolution_double_backward_ttttttlllblla
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool,3))
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_convolution_double_backward_ttttttlllblla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_convolution_double_backward_ttttttlllblla Ptr Tensor
_ggI Ptr Tensor
_ggW Ptr Tensor
_ggb Ptr Tensor
_gO Ptr Tensor
_weight Ptr Tensor
_self Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation CBool
_transposed Ptr IntArray
_output_padding Int64
_groups Ptr (StdArray '(CBool, 3))
_output_mask =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_convolution_double_backward(
*$(at::Tensor* _ggI)
, *$(at::Tensor* _ggW)
, *$(at::Tensor* _ggb)
, *$(at::Tensor* _gO)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(bool _transposed)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, *$(std::array<bool,3>* _output_mask)));
}|]
conv1d_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv1d_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv1d_tttllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
conv1d_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttlll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv1d_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
conv1d_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
conv1d_tttl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
conv1d_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv1d_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv1d_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv1d_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv1d_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv1d_tt Ptr Tensor
_input Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)));
}|]
conv2d_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv2d_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv2d_tttllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
conv2d_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttlll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv2d_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
conv2d_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
conv2d_tttl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
conv2d_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv2d_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv2d_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv2d_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv2d_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv2d_tt Ptr Tensor
_input Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)));
}|]
conv3d_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv3d_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv3d_tttllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
conv3d_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttlll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv3d_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
conv3d_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
conv3d_tttl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
conv3d_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv3d_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv3d_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv3d_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv3d_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv3d_tt Ptr Tensor
_input Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)));
}|]
conv1d_tttlsll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv1d_tttlsll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv1d_tttlsll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
conv1d_tttlsl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttlsl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv1d_tttlsl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv1d_tttls
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv1d_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv1d_tttls Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)));
}|]
conv2d_tttlsll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv2d_tttlsll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv2d_tttlsll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
conv2d_tttlsl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttlsl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv2d_tttlsl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv2d_tttls
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv2d_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv2d_tttls Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)));
}|]
conv3d_tttlsll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv3d_tttlsll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv3d_tttlsll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)
, $(int64_t _groups)));
}|]
conv3d_tttlsl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttlsl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> Ptr IntArray
-> IO (Ptr Tensor)
conv3d_tttlsl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv3d_tttls
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv3d_tttls :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr StdString
-> IO (Ptr Tensor)
conv3d_tttls Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr StdString
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::string* _padding)));
}|]
conv_tbc_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
conv_tbc_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
conv_tbc_tttl Ptr Tensor
_self Ptr Tensor
_weight Ptr Tensor
_bias Int64
_pad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_tbc(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, $(int64_t _pad)));
}|]
conv_tbc_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_tbc_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_tbc_ttt Ptr Tensor
_self Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_tbc(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv_tbc_backward_ttttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
conv_tbc_backward_ttttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
conv_tbc_backward_ttttl Ptr Tensor
_self Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Int64
_pad =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::conv_tbc_backward(
*$(at::Tensor* _self)
, *$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, $(int64_t _pad)));
}|]
conv_transpose1d_tttlllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttlllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttlllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Int64
_groups Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv_transpose1d_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv_transpose1d_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv_transpose1d_tttllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)));
}|]
conv_transpose1d_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttlll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
conv_transpose1d_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
conv_transpose1d_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose1d_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
conv_transpose1d_tttl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
conv_transpose1d_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_transpose1d_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_transpose1d_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv_transpose1d_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_transpose1d_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_transpose1d_tt Ptr Tensor
_input Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose1d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)));
}|]
conv_transpose2d_tttlllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttlllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttlllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Int64
_groups Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv_transpose2d_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv_transpose2d_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv_transpose2d_tttllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)));
}|]
conv_transpose2d_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttlll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
conv_transpose2d_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
conv_transpose2d_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose2d_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
conv_transpose2d_tttl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
conv_transpose2d_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_transpose2d_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_transpose2d_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv_transpose2d_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_transpose2d_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_transpose2d_tt Ptr Tensor
_input Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose2d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)));
}|]
conv_transpose3d_tttlllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttlllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttlllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Int64
_groups Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv_transpose3d_tttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv_transpose3d_tttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
conv_transpose3d_tttllll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Int64
_groups =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, $(int64_t _groups)));
}|]
conv_transpose3d_tttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttlll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
conv_transpose3d_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttll Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
conv_transpose3d_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_transpose3d_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
conv_transpose3d_tttl Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
conv_transpose3d_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_transpose3d_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_transpose3d_ttt Ptr Tensor
_input Ptr Tensor
_weight Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)
, *$(at::Tensor* _bias)));
}|]
conv_transpose3d_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
conv_transpose3d_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
conv_transpose3d_tt Ptr Tensor
_input Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_transpose3d(
*$(at::Tensor* _input)
, *$(at::Tensor* _weight)));
}|]
_copy_from_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_copy_from_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
_copy_from_ttb Ptr Tensor
_self Ptr Tensor
_dst CBool
_non_blocking =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_copy_from(
*$(at::Tensor* _self)
, *$(at::Tensor* _dst)
, $(bool _non_blocking)));
}|]
_copy_from_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_copy_from_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_copy_from_tt Ptr Tensor
_self Ptr Tensor
_dst =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_copy_from(
*$(at::Tensor* _self)
, *$(at::Tensor* _dst)));
}|]
_copy_from_and_resize_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_copy_from_and_resize_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_copy_from_and_resize_tt Ptr Tensor
_self Ptr Tensor
_dst =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_copy_from_and_resize(
*$(at::Tensor* _self)
, *$(at::Tensor* _dst)));
}|]
cos_t
:: Ptr Tensor
-> IO (Ptr Tensor)
cos_t :: Ptr Tensor -> IO (Ptr Tensor)
cos_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cos(
*$(at::Tensor* _self)));
}|]
cos__t
:: Ptr Tensor
-> IO (Ptr Tensor)
cos__t :: Ptr Tensor -> IO (Ptr Tensor)
cos__t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cos_(
*$(at::Tensor* _self)));
}|]
cos_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cos_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cos_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cos_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
cosh_t
:: Ptr Tensor
-> IO (Ptr Tensor)
cosh_t :: Ptr Tensor -> IO (Ptr Tensor)
cosh_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cosh(
*$(at::Tensor* _self)));
}|]
cosh__t
:: Ptr Tensor
-> IO (Ptr Tensor)
cosh__t :: Ptr Tensor -> IO (Ptr Tensor)
cosh__t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cosh_(
*$(at::Tensor* _self)));
}|]
cosh_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cosh_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cosh_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cosh_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]