{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Internal.Unmanaged.Native.Native9 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>"
less_equal_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
less_equal_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
less_equal_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less_equal_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
less_equal_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
less_equal_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
less_equal_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less_equal(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
less_equal_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
less_equal_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
less_equal_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less_equal_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
less_equal_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
less_equal_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
less_equal_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less_equal(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
gt_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
gt_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
gt_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gt_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
gt_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
gt_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
gt_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gt(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
gt_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gt_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
gt_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gt_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
gt_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
gt_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
gt_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gt(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
greater_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
greater_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
greater_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
greater_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
greater_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
greater_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
greater_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
greater_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
greater_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
greater_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
greater_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
greater_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::greater(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
lt_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
lt_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
lt_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lt_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
lt_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
lt_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
lt_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lt(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
lt_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lt_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lt_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lt_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
lt_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lt_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lt_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lt(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
less_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
less_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
less_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
less_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
less_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
less_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
less_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
less_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
less_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
less_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
less_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
less_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::less(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
take_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
take_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
take_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::take_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _index)));
}|]
take_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
take_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
take_tt Ptr Tensor
_self Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::take(
*$(at::Tensor* _self)
, *$(at::Tensor* _index)));
}|]
take_along_dim_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
take_along_dim_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
take_along_dim_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_indices Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::take_along_dim_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, $(int64_t _dim)));
}|]
take_along_dim_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
take_along_dim_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
take_along_dim_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::take_along_dim_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _indices)));
}|]
take_along_dim_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
take_along_dim_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
take_along_dim_ttl Ptr Tensor
_self Ptr Tensor
_indices Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::take_along_dim(
*$(at::Tensor* _self)
, *$(at::Tensor* _indices)
, $(int64_t _dim)));
}|]
take_along_dim_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
take_along_dim_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
take_along_dim_tt Ptr Tensor
_self Ptr Tensor
_indices =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::take_along_dim(
*$(at::Tensor* _self)
, *$(at::Tensor* _indices)));
}|]
index_select_out_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
index_select_out_ttlt :: Ptr Tensor -> Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
index_select_out_ttlt Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_select_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)));
}|]
index_select_tlt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
index_select_tlt :: Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
index_select_tlt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_select(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)));
}|]
index_select_out_ttnt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> IO (Ptr Tensor)
index_select_out_ttnt :: Ptr Tensor
-> Ptr Tensor -> Ptr Dimname -> Ptr Tensor -> IO (Ptr Tensor)
index_select_out_ttnt Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_select_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)));
}|]
index_select_tnt
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> IO (Ptr Tensor)
index_select_tnt :: Ptr Tensor -> Ptr Dimname -> Ptr Tensor -> IO (Ptr Tensor)
index_select_tnt Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_select(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)));
}|]
index_select_backward_tllt
:: Ptr Tensor
-> Ptr IntArray
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
index_select_backward_tllt :: Ptr Tensor
-> Ptr IntArray -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
index_select_backward_tllt Ptr Tensor
_grad Ptr IntArray
_self_sizes Int64
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::index_select_backward(
*$(at::Tensor* _grad)
, *$(std::vector<int64_t>* _self_sizes)
, $(int64_t _dim)
, *$(at::Tensor* _index)));
}|]
masked_select_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
masked_select_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
masked_select_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_mask =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::masked_select_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _mask)));
}|]
masked_select_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
masked_select_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
masked_select_tt Ptr Tensor
_self Ptr Tensor
_mask =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::masked_select(
*$(at::Tensor* _self)
, *$(at::Tensor* _mask)));
}|]
masked_select_backward_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
masked_select_backward_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
masked_select_backward_ttt Ptr Tensor
_grad Ptr Tensor
_input Ptr Tensor
_mask =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::masked_select_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _input)
, *$(at::Tensor* _mask)));
}|]
nonzero_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
nonzero_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
nonzero_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::nonzero_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
nonzero_t
:: Ptr Tensor
-> IO (Ptr Tensor)
nonzero_t :: Ptr Tensor -> IO (Ptr Tensor)
nonzero_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::nonzero(
*$(at::Tensor* _self)));
}|]
nonzero_numpy_t
:: Ptr Tensor
-> IO (Ptr TensorList)
nonzero_numpy_t :: Ptr Tensor -> IO (Ptr TensorList)
nonzero_numpy_t Ptr Tensor
_self =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::nonzero_numpy(
*$(at::Tensor* _self)));
}|]
argwhere_t
:: Ptr Tensor
-> IO (Ptr Tensor)
argwhere_t :: Ptr Tensor -> IO (Ptr Tensor)
argwhere_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::argwhere(
*$(at::Tensor* _self)));
}|]
gather_out_ttltb
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
gather_out_ttltb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
gather_out_ttltb Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index CBool
_sparse_grad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, $(bool _sparse_grad)));
}|]
gather_out_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
gather_out_ttlt :: Ptr Tensor -> Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
gather_out_ttlt Ptr Tensor
_out Ptr Tensor
_self Int64
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)));
}|]
gather_tltb
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
gather_tltb :: Ptr Tensor -> Int64 -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
gather_tltb Ptr Tensor
_self Int64
_dim Ptr Tensor
_index CBool
_sparse_grad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, $(bool _sparse_grad)));
}|]
gather_tlt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
gather_tlt :: Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
gather_tlt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)));
}|]
gather_backward_ttltb
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
gather_backward_ttltb :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
gather_backward_ttltb Ptr Tensor
_grad Ptr Tensor
_self Int64
_dim Ptr Tensor
_index CBool
_sparse_grad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather_backward(
*$(at::Tensor* _grad)
, *$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, $(bool _sparse_grad)));
}|]
gather_out_ttntb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
gather_out_ttntb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
gather_out_ttntb Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index CBool
_sparse_grad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, $(bool _sparse_grad)));
}|]
gather_out_ttnt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> IO (Ptr Tensor)
gather_out_ttnt :: Ptr Tensor
-> Ptr Tensor -> Ptr Dimname -> Ptr Tensor -> IO (Ptr Tensor)
gather_out_ttnt Ptr Tensor
_out Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)));
}|]
gather_tntb
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
gather_tntb :: Ptr Tensor -> Ptr Dimname -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
gather_tntb Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index CBool
_sparse_grad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)
, $(bool _sparse_grad)));
}|]
gather_tnt
:: Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> IO (Ptr Tensor)
gather_tnt :: Ptr Tensor -> Ptr Dimname -> Ptr Tensor -> IO (Ptr Tensor)
gather_tnt Ptr Tensor
_self Ptr Dimname
_dim Ptr Tensor
_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::gather(
*$(at::Tensor* _self)
, *$(at::Dimname* _dim)
, *$(at::Tensor* _index)));
}|]
_gather_sparse_backward_tltt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
_gather_sparse_backward_tltt :: Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
_gather_sparse_backward_tltt Ptr Tensor
_self Int64
_dim Ptr Tensor
_index Ptr Tensor
_grad =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_gather_sparse_backward(
*$(at::Tensor* _self)
, $(int64_t _dim)
, *$(at::Tensor* _index)
, *$(at::Tensor* _grad)));
}|]
addcmul_out_tttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addcmul_out_tttts :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addcmul_out_tttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcmul_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)
, *$(at::Scalar* _value)));
}|]
addcmul_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
addcmul_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
addcmul_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcmul_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)));
}|]
addcmul_ttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addcmul_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
addcmul_ttts Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcmul(
*$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)
, *$(at::Scalar* _value)));
}|]
addcmul_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
addcmul_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
addcmul_ttt Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcmul(
*$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)));
}|]
addcdiv_out_tttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addcdiv_out_tttts :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addcdiv_out_tttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcdiv_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)
, *$(at::Scalar* _value)));
}|]
addcdiv_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
addcdiv_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
addcdiv_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcdiv_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)));
}|]
addcdiv_ttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
addcdiv_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
addcdiv_ttts Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 Ptr Scalar
_value =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcdiv(
*$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)
, *$(at::Scalar* _value)));
}|]
addcdiv_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
addcdiv_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
addcdiv_ttt Ptr Tensor
_self Ptr Tensor
_tensor1 Ptr Tensor
_tensor2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::addcdiv(
*$(at::Tensor* _self)
, *$(at::Tensor* _tensor1)
, *$(at::Tensor* _tensor2)));
}|]
cross_entropy_loss_tttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (Ptr Tensor)
cross_entropy_loss_tttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (Ptr Tensor)
cross_entropy_loss_tttlld Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction Int64
_ignore_index CDouble
_label_smoothing =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_entropy_loss(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)
, $(int64_t _ignore_index)
, $(double _label_smoothing)));
}|]
cross_entropy_loss_tttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
cross_entropy_loss_tttll :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
cross_entropy_loss_tttll Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction Int64
_ignore_index =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_entropy_loss(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)
, $(int64_t _ignore_index)));
}|]
cross_entropy_loss_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
cross_entropy_loss_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
cross_entropy_loss_tttl Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight Int64
_reduction =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_entropy_loss(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)
, $(int64_t _reduction)));
}|]
cross_entropy_loss_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cross_entropy_loss_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cross_entropy_loss_ttt Ptr Tensor
_self Ptr Tensor
_target Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_entropy_loss(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)
, *$(at::Tensor* _weight)));
}|]
cross_entropy_loss_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cross_entropy_loss_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cross_entropy_loss_tt Ptr Tensor
_self Ptr Tensor
_target =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_entropy_loss(
*$(at::Tensor* _self)
, *$(at::Tensor* _target)));
}|]
lstsq_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
lstsq_out_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
lstsq_out_tttt Ptr Tensor
_X Ptr Tensor
_qr Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::lstsq_out(
*$(at::Tensor* _X)
, *$(at::Tensor* _qr)
, *$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
lstsq_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
lstsq_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
lstsq_tt Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::lstsq(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
triangular_solve_out_ttttbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_out_ttttbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_out_ttttbbb Ptr Tensor
_X Ptr Tensor
_M Ptr Tensor
_self Ptr Tensor
_A CBool
_upper CBool
_transpose CBool
_unitriangular =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve_out(
*$(at::Tensor* _X)
, *$(at::Tensor* _M)
, *$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)
, $(bool _transpose)
, $(bool _unitriangular)));
}|]
triangular_solve_out_ttttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_out_ttttbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_out_ttttbb Ptr Tensor
_X Ptr Tensor
_M Ptr Tensor
_self Ptr Tensor
_A CBool
_upper CBool
_transpose =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve_out(
*$(at::Tensor* _X)
, *$(at::Tensor* _M)
, *$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)
, $(bool _transpose)));
}|]
triangular_solve_out_ttttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_out_ttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_out_ttttb Ptr Tensor
_X Ptr Tensor
_M Ptr Tensor
_self Ptr Tensor
_A CBool
_upper =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve_out(
*$(at::Tensor* _X)
, *$(at::Tensor* _M)
, *$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)));
}|]
triangular_solve_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_out_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_out_tttt Ptr Tensor
_X Ptr Tensor
_M Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve_out(
*$(at::Tensor* _X)
, *$(at::Tensor* _M)
, *$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
triangular_solve_ttbbb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_ttbbb :: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_ttbbb Ptr Tensor
_self Ptr Tensor
_A CBool
_upper CBool
_transpose CBool
_unitriangular =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)
, $(bool _transpose)
, $(bool _unitriangular)));
}|]
triangular_solve_ttbb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_ttbb :: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_ttbb Ptr Tensor
_self Ptr Tensor
_A CBool
_upper CBool
_transpose =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)
, $(bool _transpose)));
}|]
triangular_solve_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_ttb :: Ptr Tensor
-> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_ttb Ptr Tensor
_self Ptr Tensor
_A CBool
_upper =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)));
}|]
triangular_solve_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
triangular_solve_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
triangular_solve_tt Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::triangular_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
_linalg_check_errors_tsb
:: Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (())
_linalg_check_errors_tsb :: Ptr Tensor -> Ptr StdString -> CBool -> IO ()
_linalg_check_errors_tsb Ptr Tensor
_info Ptr StdString
_api_name CBool
_is_matrix =
[C.throwBlock| void { (at::_linalg_check_errors(
*$(at::Tensor* _info)
, *$(std::string* _api_name)
, $(bool _is_matrix)));
}|]
linalg_solve_triangular_out_tttbbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_out_tttbbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_out_tttbbb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_B CBool
_upper CBool
_left CBool
_unitriangular =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _B)
, $(bool _upper)
, $(bool _left)
, $(bool _unitriangular)));
}|]
linalg_solve_triangular_out_tttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_out_tttbb :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
linalg_solve_triangular_out_tttbb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_B CBool
_upper CBool
_left =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _B)
, $(bool _upper)
, $(bool _left)));
}|]
linalg_solve_triangular_out_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
linalg_solve_triangular_out_tttb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_B CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _B)
, $(bool _upper)));
}|]
linalg_solve_triangular_ttbbb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_ttbbb :: Ptr Tensor
-> Ptr Tensor -> CBool -> CBool -> CBool -> IO (Ptr Tensor)
linalg_solve_triangular_ttbbb Ptr Tensor
_self Ptr Tensor
_B CBool
_upper CBool
_left CBool
_unitriangular =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular(
*$(at::Tensor* _self)
, *$(at::Tensor* _B)
, $(bool _upper)
, $(bool _left)
, $(bool _unitriangular)));
}|]
linalg_solve_triangular_ttbb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_ttbb :: Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
linalg_solve_triangular_ttbb Ptr Tensor
_self Ptr Tensor
_B CBool
_upper CBool
_left =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular(
*$(at::Tensor* _self)
, *$(at::Tensor* _B)
, $(bool _upper)
, $(bool _left)));
}|]
linalg_solve_triangular_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
linalg_solve_triangular_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
linalg_solve_triangular_ttb Ptr Tensor
_self Ptr Tensor
_B CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular(
*$(at::Tensor* _self)
, *$(at::Tensor* _B)
, $(bool _upper)));
}|]
symeig_out_tttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
symeig_out_tttbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
symeig_out_tttbb Ptr Tensor
_e Ptr Tensor
_V Ptr Tensor
_self CBool
_eigenvectors CBool
_upper =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::symeig_out(
*$(at::Tensor* _e)
, *$(at::Tensor* _V)
, *$(at::Tensor* _self)
, $(bool _eigenvectors)
, $(bool _upper)));
}|]
symeig_out_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
symeig_out_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
symeig_out_tttb Ptr Tensor
_e Ptr Tensor
_V Ptr Tensor
_self CBool
_eigenvectors =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::symeig_out(
*$(at::Tensor* _e)
, *$(at::Tensor* _V)
, *$(at::Tensor* _self)
, $(bool _eigenvectors)));
}|]
symeig_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
symeig_out_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
symeig_out_ttt Ptr Tensor
_e Ptr Tensor
_V Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::symeig_out(
*$(at::Tensor* _e)
, *$(at::Tensor* _V)
, *$(at::Tensor* _self)));
}|]
symeig_tbb
:: Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
symeig_tbb :: Ptr Tensor
-> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
symeig_tbb Ptr Tensor
_self CBool
_eigenvectors CBool
_upper =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::symeig(
*$(at::Tensor* _self)
, $(bool _eigenvectors)
, $(bool _upper)));
}|]
symeig_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
symeig_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
symeig_tb Ptr Tensor
_self CBool
_eigenvectors =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::symeig(
*$(at::Tensor* _self)
, $(bool _eigenvectors)));
}|]
symeig_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
symeig_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
symeig_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::symeig(
*$(at::Tensor* _self)));
}|]
_symeig_helper_tbb
:: Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_symeig_helper_tbb :: Ptr Tensor
-> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
_symeig_helper_tbb Ptr Tensor
_self CBool
_eigenvectors CBool
_upper =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_symeig_helper(
*$(at::Tensor* _self)
, $(bool _eigenvectors)
, $(bool _upper)));
}|]
eig_out_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
eig_out_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
eig_out_tttb Ptr Tensor
_e Ptr Tensor
_v Ptr Tensor
_self CBool
_eigenvectors =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::eig_out(
*$(at::Tensor* _e)
, *$(at::Tensor* _v)
, *$(at::Tensor* _self)
, $(bool _eigenvectors)));
}|]
eig_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
eig_out_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
eig_out_ttt Ptr Tensor
_e Ptr Tensor
_v Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::eig_out(
*$(at::Tensor* _e)
, *$(at::Tensor* _v)
, *$(at::Tensor* _self)));
}|]
eig_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
eig_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
eig_tb Ptr Tensor
_self CBool
_eigenvectors =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::eig(
*$(at::Tensor* _self)
, $(bool _eigenvectors)));
}|]
eig_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
eig_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
eig_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::eig(
*$(at::Tensor* _self)));
}|]
svd_out_ttttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
svd_out_ttttbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
svd_out_ttttbb Ptr Tensor
_U Ptr Tensor
_S Ptr Tensor
_V Ptr Tensor
_self CBool
_some CBool
_compute_uv =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::svd_out(
*$(at::Tensor* _U)
, *$(at::Tensor* _S)
, *$(at::Tensor* _V)
, *$(at::Tensor* _self)
, $(bool _some)
, $(bool _compute_uv)));
}|]
svd_out_ttttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
svd_out_ttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
svd_out_ttttb Ptr Tensor
_U Ptr Tensor
_S Ptr Tensor
_V Ptr Tensor
_self CBool
_some =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::svd_out(
*$(at::Tensor* _U)
, *$(at::Tensor* _S)
, *$(at::Tensor* _V)
, *$(at::Tensor* _self)
, $(bool _some)));
}|]
svd_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
svd_out_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
svd_out_tttt Ptr Tensor
_U Ptr Tensor
_S Ptr Tensor
_V Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::svd_out(
*$(at::Tensor* _U)
, *$(at::Tensor* _S)
, *$(at::Tensor* _V)
, *$(at::Tensor* _self)));
}|]
svd_tbb
:: Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
svd_tbb :: Ptr Tensor
-> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
svd_tbb Ptr Tensor
_self CBool
_some CBool
_compute_uv =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::svd(
*$(at::Tensor* _self)
, $(bool _some)
, $(bool _compute_uv)));
}|]
svd_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
svd_tb :: Ptr Tensor
-> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
svd_tb Ptr Tensor
_self CBool
_some =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::svd(
*$(at::Tensor* _self)
, $(bool _some)));
}|]
svd_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
svd_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
svd_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::svd(
*$(at::Tensor* _self)));
}|]
swapaxes_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
swapaxes_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
swapaxes_tll Ptr Tensor
_self Int64
_axis0 Int64
_axis1 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::swapaxes(
*$(at::Tensor* _self)
, $(int64_t _axis0)
, $(int64_t _axis1)));
}|]
swapdims_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
swapdims_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
swapdims_tll Ptr Tensor
_self Int64
_dim0 Int64
_dim1 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::swapdims(
*$(at::Tensor* _self)
, $(int64_t _dim0)
, $(int64_t _dim1)));
}|]
cholesky_out_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
cholesky_out_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
cholesky_out_ttb Ptr Tensor
_out Ptr Tensor
_self CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(bool _upper)));
}|]
cholesky_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cholesky_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cholesky_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
cholesky_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
cholesky_tb :: Ptr Tensor -> CBool -> IO (Ptr Tensor)
cholesky_tb Ptr Tensor
_self CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky(
*$(at::Tensor* _self)
, $(bool _upper)));
}|]
cholesky_t
:: Ptr Tensor
-> IO (Ptr Tensor)
cholesky_t :: Ptr Tensor -> IO (Ptr Tensor)
cholesky_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky(
*$(at::Tensor* _self)));
}|]
cholesky_solve_out_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
cholesky_solve_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
cholesky_solve_out_tttb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_input2 CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_solve_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, $(bool _upper)));
}|]
cholesky_solve_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cholesky_solve_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cholesky_solve_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_input2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_solve_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _input2)));
}|]
cholesky_solve_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
cholesky_solve_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
cholesky_solve_ttb Ptr Tensor
_self Ptr Tensor
_input2 CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, $(bool _upper)));
}|]
cholesky_solve_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cholesky_solve_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cholesky_solve_tt Ptr Tensor
_self Ptr Tensor
_input2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _input2)));
}|]
_cholesky_solve_helper_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_cholesky_solve_helper_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
_cholesky_solve_helper_ttb Ptr Tensor
_self Ptr Tensor
_A CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_cholesky_solve_helper(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)
, $(bool _upper)));
}|]
solve_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
solve_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
solve_tt Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
solve_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
solve_out_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
solve_out_tttt Ptr Tensor
_solution Ptr Tensor
_lu Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::solve_out(
*$(at::Tensor* _solution)
, *$(at::Tensor* _lu)
, *$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
_solve_helper_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
_solve_helper_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
_solve_helper_tt Ptr Tensor
_self Ptr Tensor
_A =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::_solve_helper(
*$(at::Tensor* _self)
, *$(at::Tensor* _A)));
}|]
cholesky_inverse_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
cholesky_inverse_tb :: Ptr Tensor -> CBool -> IO (Ptr Tensor)
cholesky_inverse_tb Ptr Tensor
_self CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_inverse(
*$(at::Tensor* _self)
, $(bool _upper)));
}|]
cholesky_inverse_t
:: Ptr Tensor
-> IO (Ptr Tensor)
cholesky_inverse_t :: Ptr Tensor -> IO (Ptr Tensor)
cholesky_inverse_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_inverse(
*$(at::Tensor* _self)));
}|]
cholesky_inverse_out_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
cholesky_inverse_out_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
cholesky_inverse_out_ttb Ptr Tensor
_out Ptr Tensor
_self CBool
_upper =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_inverse_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(bool _upper)));
}|]
cholesky_inverse_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
cholesky_inverse_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
cholesky_inverse_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::cholesky_inverse_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
qr_out_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
qr_out_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
qr_out_tttb Ptr Tensor
_Q Ptr Tensor
_R Ptr Tensor
_self CBool
_some =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::qr_out(
*$(at::Tensor* _Q)
, *$(at::Tensor* _R)
, *$(at::Tensor* _self)
, $(bool _some)));
}|]
qr_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
qr_out_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
qr_out_ttt Ptr Tensor
_Q Ptr Tensor
_R Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::qr_out(
*$(at::Tensor* _Q)
, *$(at::Tensor* _R)
, *$(at::Tensor* _self)));
}|]
qr_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
qr_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
qr_tb Ptr Tensor
_self CBool
_some =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::qr(
*$(at::Tensor* _self)
, $(bool _some)));
}|]
qr_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
qr_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
qr_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::qr(
*$(at::Tensor* _self)));
}|]
geqrf_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
geqrf_out_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
geqrf_out_ttt Ptr Tensor
_a Ptr Tensor
_tau Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::geqrf_out(
*$(at::Tensor* _a)
, *$(at::Tensor* _tau)
, *$(at::Tensor* _self)));
}|]
geqrf_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
geqrf_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
geqrf_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::geqrf(
*$(at::Tensor* _self)));
}|]
orgqr_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
orgqr_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
orgqr_tt Ptr Tensor
_self Ptr Tensor
_input2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::orgqr(
*$(at::Tensor* _self)
, *$(at::Tensor* _input2)));
}|]
orgqr_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
orgqr_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
orgqr_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_input2 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::orgqr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _input2)));
}|]
ormqr_out_ttttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
ormqr_out_ttttbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
ormqr_out_ttttbb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_input2 Ptr Tensor
_input3 CBool
_left CBool
_transpose =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ormqr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _input3)
, $(bool _left)
, $(bool _transpose)));
}|]
ormqr_out_ttttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
ormqr_out_ttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
ormqr_out_ttttb Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_input2 Ptr Tensor
_input3 CBool
_left =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ormqr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _input3)
, $(bool _left)));
}|]
ormqr_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ormqr_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ormqr_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_input2 Ptr Tensor
_input3 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ormqr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _input3)));
}|]
ormqr_tttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr Tensor)
ormqr_tttbb :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
ormqr_tttbb Ptr Tensor
_self Ptr Tensor
_input2 Ptr Tensor
_input3 CBool
_left CBool
_transpose =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ormqr(
*$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _input3)
, $(bool _left)
, $(bool _transpose)));
}|]
ormqr_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
ormqr_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
ormqr_tttb Ptr Tensor
_self Ptr Tensor
_input2 Ptr Tensor
_input3 CBool
_left =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ormqr(
*$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _input3)
, $(bool _left)));
}|]
ormqr_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
ormqr_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
ormqr_ttt Ptr Tensor
_self Ptr Tensor
_input2 Ptr Tensor
_input3 =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::ormqr(
*$(at::Tensor* _self)
, *$(at::Tensor* _input2)
, *$(at::Tensor* _input3)));
}|]
_lu_with_info_tbb
:: Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_lu_with_info_tbb :: Ptr Tensor
-> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_lu_with_info_tbb Ptr Tensor
_self CBool
_pivot CBool
_check_errors =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_lu_with_info(
*$(at::Tensor* _self)
, $(bool _pivot)
, $(bool _check_errors)));
}|]
_lu_with_info_tb
:: Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_lu_with_info_tb :: Ptr Tensor
-> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_lu_with_info_tb Ptr Tensor
_self CBool
_pivot =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_lu_with_info(
*$(at::Tensor* _self)
, $(bool _pivot)));
}|]
_lu_with_info_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_lu_with_info_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_lu_with_info_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_lu_with_info(
*$(at::Tensor* _self)));
}|]
lu_solve_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lu_solve_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lu_solve_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lu_solve_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)));
}|]
lu_solve_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lu_solve_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lu_solve_ttt Ptr Tensor
_self Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lu_solve(
*$(at::Tensor* _self)
, *$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)));
}|]
lu_unpack_ttbb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lu_unpack_ttbb :: Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lu_unpack_ttbb Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots CBool
_unpack_data CBool
_unpack_pivots =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lu_unpack(
*$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)
, $(bool _unpack_data)
, $(bool _unpack_pivots)));
}|]
lu_unpack_ttb
:: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lu_unpack_ttb :: Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lu_unpack_ttb Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots CBool
_unpack_data =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lu_unpack(
*$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)
, $(bool _unpack_data)));
}|]
lu_unpack_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lu_unpack_tt :: Ptr Tensor
-> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lu_unpack_tt Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lu_unpack(
*$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)));
}|]
lu_unpack_out_tttttbb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lu_unpack_out_tttttbb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lu_unpack_out_tttttbb Ptr Tensor
_P Ptr Tensor
_L Ptr Tensor
_U Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots CBool
_unpack_data CBool
_unpack_pivots =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lu_unpack_out(
*$(at::Tensor* _P)
, *$(at::Tensor* _L)
, *$(at::Tensor* _U)
, *$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)
, $(bool _unpack_data)
, $(bool _unpack_pivots)));
}|]
lu_unpack_out_tttttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lu_unpack_out_tttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lu_unpack_out_tttttb Ptr Tensor
_P Ptr Tensor
_L Ptr Tensor
_U Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots CBool
_unpack_data =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lu_unpack_out(
*$(at::Tensor* _P)
, *$(at::Tensor* _L)
, *$(at::Tensor* _U)
, *$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)
, $(bool _unpack_data)));
}|]
lu_unpack_out_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
lu_unpack_out_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
lu_unpack_out_ttttt Ptr Tensor
_P Ptr Tensor
_L Ptr Tensor
_U Ptr Tensor
_LU_data Ptr Tensor
_LU_pivots =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::lu_unpack_out(
*$(at::Tensor* _P)
, *$(at::Tensor* _L)
, *$(at::Tensor* _U)
, *$(at::Tensor* _LU_data)
, *$(at::Tensor* _LU_pivots)));
}|]
multinomial_out_ttlbG
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> Ptr Generator
-> IO (Ptr Tensor)
multinomial_out_ttlbG :: Ptr Tensor
-> Ptr Tensor -> Int64 -> CBool -> Ptr Generator -> IO (Ptr Tensor)
multinomial_out_ttlbG Ptr Tensor
_out Ptr Tensor
_self Int64
_num_samples CBool
_replacement Ptr Generator
_generator =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::multinomial_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _num_samples)
, $(bool _replacement)
, *$(at::Generator* _generator)));
}|]
multinomial_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr Tensor)
multinomial_out_ttlb :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor)
multinomial_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Int64
_num_samples CBool
_replacement =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::multinomial_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _num_samples)
, $(bool _replacement)));
}|]
multinomial_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
multinomial_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
multinomial_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_num_samples =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::multinomial_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _num_samples)));
}|]
multinomial_tlbG
:: Ptr Tensor
-> Int64
-> CBool
-> Ptr Generator
-> IO (Ptr Tensor)
multinomial_tlbG :: Ptr Tensor -> Int64 -> CBool -> Ptr Generator -> IO (Ptr Tensor)
multinomial_tlbG Ptr Tensor
_self Int64
_num_samples CBool
_replacement Ptr Generator
_generator =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::multinomial(
*$(at::Tensor* _self)
, $(int64_t _num_samples)
, $(bool _replacement)
, *$(at::Generator* _generator)));
}|]
multinomial_tlb
:: Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr Tensor)
multinomial_tlb :: Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor)
multinomial_tlb Ptr Tensor
_self Int64
_num_samples CBool
_replacement =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::multinomial(
*$(at::Tensor* _self)
, $(int64_t _num_samples)
, $(bool _replacement)));
}|]
multinomial_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
multinomial_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
multinomial_tl Ptr Tensor
_self Int64
_num_samples =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::multinomial(
*$(at::Tensor* _self)
, $(int64_t _num_samples)));
}|]
lgamma_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lgamma_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lgamma_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lgamma_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
lgamma_t
:: Ptr Tensor
-> IO (Ptr Tensor)
lgamma_t :: Ptr Tensor -> IO (Ptr Tensor)
lgamma_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lgamma(
*$(at::Tensor* _self)));
}|]
digamma_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
digamma_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
digamma_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::digamma_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
digamma_t
:: Ptr Tensor
-> IO (Ptr Tensor)
digamma_t :: Ptr Tensor -> IO (Ptr Tensor)
digamma_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::digamma(
*$(at::Tensor* _self)));
}|]
polygamma_out_tlt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
polygamma_out_tlt :: Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
polygamma_out_tlt Ptr Tensor
_out Int64
_n Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::polygamma_out(
*$(at::Tensor* _out)
, $(int64_t _n)
, *$(at::Tensor* _self)));
}|]
polygamma_lt
:: Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
polygamma_lt :: Int64 -> Ptr Tensor -> IO (Ptr Tensor)
polygamma_lt Int64
_n Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::polygamma(
$(int64_t _n)
, *$(at::Tensor* _self)));
}|]
erfinv_t
:: Ptr Tensor
-> IO (Ptr Tensor)
erfinv_t :: Ptr Tensor -> IO (Ptr Tensor)
erfinv_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::erfinv(
*$(at::Tensor* _self)));
}|]
erfinv_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
erfinv_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
erfinv_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::erfinv_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
i0_t
:: Ptr Tensor
-> IO (Ptr Tensor)
i0_t :: Ptr Tensor -> IO (Ptr Tensor)
i0_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::i0(
*$(at::Tensor* _self)));
}|]
i0__t
:: Ptr Tensor
-> IO (Ptr Tensor)
i0__t :: Ptr Tensor -> IO (Ptr Tensor)
i0__t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::i0_(
*$(at::Tensor* _self)));
}|]
i0_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
i0_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
i0_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::i0_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
sign_t
:: Ptr Tensor
-> IO (Ptr Tensor)
sign_t :: Ptr Tensor -> IO (Ptr Tensor)
sign_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::sign(
*$(at::Tensor* _self)));
}|]
sign_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
sign_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
sign_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::sign_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
signbit_t
:: Ptr Tensor
-> IO (Ptr Tensor)
signbit_t :: Ptr Tensor -> IO (Ptr Tensor)
signbit_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::signbit(
*$(at::Tensor* _self)));
}|]
signbit_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
signbit_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
signbit_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::signbit_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
dist_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
dist_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
dist_tts Ptr Tensor
_self Ptr Tensor
_other Ptr Scalar
_p =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::dist(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)
, *$(at::Scalar* _p)));
}|]
dist_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
dist_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
dist_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::dist(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
atan2_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
atan2_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
atan2_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::atan2_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
atan2_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
atan2_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
atan2_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::atan2(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
arctan2_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
arctan2_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
arctan2_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::arctan2(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
arctan2_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
arctan2_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
arctan2_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::arctan2_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
lerp_out_ttts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
lerp_out_ttts :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
lerp_out_ttts Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_end Ptr Scalar
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lerp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _end)
, *$(at::Scalar* _weight)));
}|]
lerp_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lerp_out_tttt :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lerp_out_tttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_end Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lerp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _end)
, *$(at::Tensor* _weight)));
}|]
lerp_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
lerp_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
lerp_tts Ptr Tensor
_self Ptr Tensor
_end Ptr Scalar
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lerp(
*$(at::Tensor* _self)
, *$(at::Tensor* _end)
, *$(at::Scalar* _weight)));
}|]
lerp_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
lerp_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
lerp_ttt Ptr Tensor
_self Ptr Tensor
_end Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::lerp(
*$(at::Tensor* _self)
, *$(at::Tensor* _end)
, *$(at::Tensor* _weight)));
}|]
histc_out_ttlss
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
histc_out_ttlss :: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
histc_out_ttlss Ptr Tensor
_out Ptr Tensor
_self Int64
_bins Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _bins)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
histc_out_ttls
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr Scalar
-> IO (Ptr Tensor)
histc_out_ttls :: Ptr Tensor -> Ptr Tensor -> Int64 -> Ptr Scalar -> IO (Ptr Tensor)
histc_out_ttls Ptr Tensor
_out Ptr Tensor
_self Int64
_bins Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _bins)
, *$(at::Scalar* _min)));
}|]
histc_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
histc_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
histc_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_bins =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _bins)));
}|]
histc_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
histc_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
histc_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
histc_tlss
:: Ptr Tensor
-> Int64
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
histc_tlss :: Ptr Tensor -> Int64 -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
histc_tlss Ptr Tensor
_self Int64
_bins Ptr Scalar
_min Ptr Scalar
_max =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc(
*$(at::Tensor* _self)
, $(int64_t _bins)
, *$(at::Scalar* _min)
, *$(at::Scalar* _max)));
}|]
histc_tls
:: Ptr Tensor
-> Int64
-> Ptr Scalar
-> IO (Ptr Tensor)
histc_tls :: Ptr Tensor -> Int64 -> Ptr Scalar -> IO (Ptr Tensor)
histc_tls Ptr Tensor
_self Int64
_bins Ptr Scalar
_min =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc(
*$(at::Tensor* _self)
, $(int64_t _bins)
, *$(at::Scalar* _min)));
}|]
histc_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
histc_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
histc_tl Ptr Tensor
_self Int64
_bins =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc(
*$(at::Tensor* _self)
, $(int64_t _bins)));
}|]
histc_t
:: Ptr Tensor
-> IO (Ptr Tensor)
histc_t :: Ptr Tensor -> IO (Ptr Tensor)
histc_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::histc(
*$(at::Tensor* _self)));
}|]
histogram_out_tttttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_tttttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_tttttb Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Ptr Tensor
_bins Ptr Tensor
_weight CBool
_density =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, *$(at::Tensor* _bins)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
histogram_out_ttttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_ttttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_ttttt Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Ptr Tensor
_bins Ptr Tensor
_weight =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, *$(at::Tensor* _bins)
, *$(at::Tensor* _weight)));
}|]
histogram_out_tttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_tttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_tttt Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Ptr Tensor
_bins =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, *$(at::Tensor* _bins)));
}|]
histogram_tttb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_tttb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_tttb Ptr Tensor
_self Ptr Tensor
_bins Ptr Tensor
_weight CBool
_density =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, *$(at::Tensor* _bins)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
histogram_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_ttt Ptr Tensor
_self Ptr Tensor
_bins Ptr Tensor
_weight =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, *$(at::Tensor* _bins)
, *$(at::Tensor* _weight)));
}|]
histogram_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_tt Ptr Tensor
_self Ptr Tensor
_bins =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, *$(at::Tensor* _bins)));
}|]
histogram_out_tttlatb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_tttlatb :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_tttlatb Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Int64
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight CBool
_density =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, $(int64_t _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
histogram_out_tttlat
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_tttlat :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_tttlat Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Int64
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, $(int64_t _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)));
}|]
histogram_out_tttla
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_tttla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_tttla Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Int64
_bins Ptr (StdVector CDouble)
_range =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, $(int64_t _bins)
, *$(std::vector<double>* _range)));
}|]
histogram_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_tttl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_tttl Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self Int64
_bins =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)
, $(int64_t _bins)));
}|]
histogram_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_out_ttt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_out_ttt Ptr Tensor
_hist Ptr Tensor
_bin_edges Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram_out(
*$(at::Tensor* _hist)
, *$(at::Tensor* _bin_edges)
, *$(at::Tensor* _self)));
}|]
histogram_tlatb
:: Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_tlatb :: Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_tlatb Ptr Tensor
_self Int64
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight CBool
_density =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, $(int64_t _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
histogram_tlat
:: Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_tlat :: Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_tlat Ptr Tensor
_self Int64
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, $(int64_t _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)));
}|]
histogram_tla
:: Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_tla :: Ptr Tensor
-> Int64
-> Ptr (StdVector CDouble)
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_tla Ptr Tensor
_self Int64
_bins Ptr (StdVector CDouble)
_range =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, $(int64_t _bins)
, *$(std::vector<double>* _range)));
}|]
histogram_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_tl :: Ptr Tensor -> Int64 -> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_tl Ptr Tensor
_self Int64
_bins =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)
, $(int64_t _bins)));
}|]
histogram_t
:: Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor,Tensor)))
histogram_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
histogram_t Ptr Tensor
_self =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor>(at::histogram(
*$(at::Tensor* _self)));
}|]
_histogramdd_bin_edges_tlatb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr TensorList)
_histogramdd_bin_edges_tlatb :: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr TensorList)
_histogramdd_bin_edges_tlatb Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight CBool
_density =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::_histogramdd_bin_edges(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
_histogramdd_bin_edges_tlat
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr TensorList)
_histogramdd_bin_edges_tlat :: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr TensorList)
_histogramdd_bin_edges_tlat Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::_histogramdd_bin_edges(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)));
}|]
_histogramdd_bin_edges_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr TensorList)
_histogramdd_bin_edges_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr TensorList)
_histogramdd_bin_edges_tla Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::_histogramdd_bin_edges(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)
, *$(std::vector<double>* _range)));
}|]
_histogramdd_bin_edges_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr TensorList)
_histogramdd_bin_edges_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr TensorList)
_histogramdd_bin_edges_tl Ptr Tensor
_self Ptr IntArray
_bins =
[C.throwBlock| std::vector<at::Tensor>* { return new std::vector<at::Tensor>(at::_histogramdd_bin_edges(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)));
}|]
_histogramdd_from_bin_cts_tlatb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tlatb :: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tlatb Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight CBool
_density =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
_histogramdd_from_bin_cts_tlat
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tlat :: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> Ptr Tensor
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tlat Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)
, *$(std::vector<double>* _range)
, *$(at::Tensor* _weight)));
}|]
_histogramdd_from_bin_cts_tla
:: Ptr Tensor
-> Ptr IntArray
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tla :: Ptr Tensor
-> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tla Ptr Tensor
_self Ptr IntArray
_bins Ptr (StdVector CDouble)
_range =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)
, *$(std::vector<double>* _range)));
}|]
_histogramdd_from_bin_cts_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_histogramdd_from_bin_cts_tl Ptr Tensor
_self Ptr IntArray
_bins =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _bins)));
}|]
_histogramdd_from_bin_tensors_tltb
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> CBool
-> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_tltb :: Ptr Tensor
-> Ptr TensorList -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_tltb Ptr Tensor
_self Ptr TensorList
_bins Ptr Tensor
_weight CBool
_density =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors(
*$(at::Tensor* _self)
, *$(std::vector<at::Tensor>* _bins)
, *$(at::Tensor* _weight)
, $(bool _density)));
}|]
_histogramdd_from_bin_tensors_tlt
:: Ptr Tensor
-> Ptr TensorList
-> Ptr Tensor
-> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_tlt :: Ptr Tensor -> Ptr TensorList -> Ptr Tensor -> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_tlt Ptr Tensor
_self Ptr TensorList
_bins Ptr Tensor
_weight =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors(
*$(at::Tensor* _self)
, *$(std::vector<at::Tensor>* _bins)
, *$(at::Tensor* _weight)));
}|]
_histogramdd_from_bin_tensors_tl
:: Ptr Tensor
-> Ptr TensorList
-> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor)
_histogramdd_from_bin_tensors_tl Ptr Tensor
_self Ptr TensorList
_bins =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors(
*$(at::Tensor* _self)
, *$(std::vector<at::Tensor>* _bins)));
}|]
fmod_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
fmod_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
fmod_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fmod_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
fmod_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
fmod_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
fmod_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fmod(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
fmod_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
fmod_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fmod_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fmod_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
fmod_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
fmod_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fmod_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fmod(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
hypot_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
hypot_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
hypot_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::hypot_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
hypot_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
hypot_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
hypot_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::hypot(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
igamma_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
igamma_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
igamma_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::igamma_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
igamma_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
igamma_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
igamma_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::igamma(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
igammac_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
igammac_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
igammac_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::igammac_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
igammac_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
igammac_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
igammac_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::igammac(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]