-- generated by using spec/Declarations.yaml {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} module Torch.Internal.Unmanaged.Native.Native7 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 "" C.include "" C.include "" triu_indices_lllo :: Int64 -> Int64 -> Int64 -> Ptr TensorOptions -> IO (Ptr Tensor) triu_indices_lllo _row _col _offset _options = [C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices( $(int64_t _row) , $(int64_t _col) , $(int64_t _offset) , *$(at::TensorOptions* _options))); }|] triu_indices_lll :: Int64 -> Int64 -> Int64 -> IO (Ptr Tensor) triu_indices_lll _row _col _offset = [C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices( $(int64_t _row) , $(int64_t _col) , $(int64_t _offset))); }|] triu_indices_ll :: Int64 -> Int64 -> IO (Ptr Tensor) triu_indices_ll _row _col = [C.throwBlock| at::Tensor* { return new at::Tensor(at::triu_indices( $(int64_t _row) , $(int64_t _col))); }|] trace_t :: Ptr Tensor -> IO (Ptr Tensor) trace_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::trace( *$(at::Tensor* _self))); }|] trace_backward_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) trace_backward_tl _grad _sizes = [C.throwBlock| at::Tensor* { return new at::Tensor(at::trace_backward( *$(at::Tensor* _grad) , *$(std::vector* _sizes))); }|] ne_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) ne_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ne_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] ne_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) ne_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ne( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] ne_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) ne_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ne_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] ne_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) ne_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ne( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] not_equal_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) not_equal_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] not_equal_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) not_equal_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] not_equal_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) not_equal_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] not_equal_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) not_equal_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::not_equal( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] eq_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) eq_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::eq_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] eq_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) eq_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::eq( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] eq_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) eq_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::eq_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] eq_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) eq_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::eq( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] ge_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) ge_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ge_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] ge_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) ge_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ge( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] ge_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) ge_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ge_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] ge_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) ge_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ge( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] greater_equal_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) greater_equal_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] greater_equal_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) greater_equal_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] greater_equal_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) greater_equal_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] greater_equal_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) greater_equal_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::greater_equal( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] le_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) le_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::le_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] le_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) le_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::le( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] le_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) le_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::le_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] le_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) le_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::le( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] less_equal_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) less_equal_out_tts _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _indices _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 _out _self _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 _self _indices _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 _self _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 _out _self _dim _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 _self _dim _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 _out _self _dim _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 _self _dim _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 _grad _self_sizes _dim _index = [C.throwBlock| at::Tensor* { return new at::Tensor(at::index_select_backward( *$(at::Tensor* _grad) , *$(std::vector* _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 _out _self _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 _self _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 _grad _input _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 _out _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 _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 _self = [C.throwBlock| std::vector* { return new std::vector(at::nonzero_numpy( *$(at::Tensor* _self))); }|] argwhere_t :: Ptr Tensor -> IO (Ptr Tensor) argwhere_t _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 _out _self _dim _index _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 _out _self _dim _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 _self _dim _index _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 _self _dim _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 _grad _self _dim _index _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 _out _self _dim _index _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 _out _self _dim _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 _self _dim _index _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 _self _dim _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 _self _dim _index _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 _out _self _tensor1 _tensor2 _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 _out _self _tensor1 _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 _self _tensor1 _tensor2 _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 _self _tensor1 _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 _out _self _tensor1 _tensor2 _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 _out _self _tensor1 _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 _self _tensor1 _tensor2 _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 _self _tensor1 _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 _self _target _weight _reduction _ignore_index _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 _self _target _weight _reduction _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 _self _target _weight _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 _self _target _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 _self _target = [C.throwBlock| at::Tensor* { return new at::Tensor(at::cross_entropy_loss( *$(at::Tensor* _self) , *$(at::Tensor* _target))); }|] triangular_solve_out_ttttbbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) triangular_solve_out_ttttbbb _X _M _self _A _upper _transpose _unitriangular = [C.throwBlock| std::tuple* { return new std::tuple(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 _X _M _self _A _upper _transpose = [C.throwBlock| std::tuple* { return new std::tuple(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 _X _M _self _A _upper = [C.throwBlock| std::tuple* { return new std::tuple(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 _X _M _self _A = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _A _upper _transpose _unitriangular = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _A _upper _transpose = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _A _upper = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _A = [C.throwBlock| std::tuple* { return new std::tuple(at::triangular_solve( *$(at::Tensor* _self) , *$(at::Tensor* _A))); }|] _linalg_check_errors_tsb :: Ptr Tensor -> Ptr StdString -> CBool -> IO (()) _linalg_check_errors_tsb _info _api_name _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 _out _self _B _upper _left _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 _out _self _B _upper _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 _out _self _B _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 _self _B _upper _left _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 _self _B _upper _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 _self _B _upper = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_solve_triangular( *$(at::Tensor* _self) , *$(at::Tensor* _B) , $(bool _upper))); }|] linalg_vander_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor) linalg_vander_tl _x _N = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vander( *$(at::Tensor* _x) , $(int64_t _N))); }|] linalg_vander_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_vander_t _x = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vander( *$(at::Tensor* _x))); }|] svd_out_ttttbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) svd_out_ttttbb _U _S _V _self _some _compute_uv = [C.throwBlock| std::tuple* { return new std::tuple(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 _U _S _V _self _some = [C.throwBlock| std::tuple* { return new std::tuple(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 _U _S _V _self = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _some _compute_uv = [C.throwBlock| std::tuple* { return new std::tuple(at::svd( *$(at::Tensor* _self) , $(bool _some) , $(bool _compute_uv))); }|] svd_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) svd_tb _self _some = [C.throwBlock| std::tuple* { return new std::tuple(at::svd( *$(at::Tensor* _self) , $(bool _some))); }|] svd_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) svd_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::svd( *$(at::Tensor* _self))); }|] swapaxes_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) swapaxes_tll _self _axis0 _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 _self _dim0 _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 _out _self _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 _out _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 _self _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 _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 _out _self _input2 _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 _out _self _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 _self _input2 _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 _self _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 _self _A _upper = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_cholesky_solve_helper( *$(at::Tensor* _self) , *$(at::Tensor* _A) , $(bool _upper))); }|] cholesky_inverse_tb :: Ptr Tensor -> CBool -> IO (Ptr Tensor) cholesky_inverse_tb _self _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 _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 _out _self _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 _out _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 _Q _R _self _some = [C.throwBlock| std::tuple* { return new std::tuple(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 _Q _R _self = [C.throwBlock| std::tuple* { return new std::tuple(at::qr_out( *$(at::Tensor* _Q) , *$(at::Tensor* _R) , *$(at::Tensor* _self))); }|] qr_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) qr_tb _self _some = [C.throwBlock| std::tuple* { return new std::tuple(at::qr( *$(at::Tensor* _self) , $(bool _some))); }|] qr_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) qr_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::qr( *$(at::Tensor* _self))); }|] geqrf_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) geqrf_out_ttt _a _tau _self = [C.throwBlock| std::tuple* { return new std::tuple(at::geqrf_out( *$(at::Tensor* _a) , *$(at::Tensor* _tau) , *$(at::Tensor* _self))); }|] geqrf_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) geqrf_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::geqrf( *$(at::Tensor* _self))); }|] orgqr_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) orgqr_tt _self _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 _out _self _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 _out _self _input2 _input3 _left _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 _out _self _input2 _input3 _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 _out _self _input2 _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 _self _input2 _input3 _left _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 _self _input2 _input3 _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 _self _input2 _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 _self _pivot _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _pivot = [C.throwBlock| std::tuple* { return new std::tuple(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 _self = [C.throwBlock| std::tuple* { return new std::tuple(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 _out _self _LU_data _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 _self _LU_data _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 _LU_data _LU_pivots _unpack_data _unpack_pivots = [C.throwBlock| std::tuple* { return new std::tuple(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 _LU_data _LU_pivots _unpack_data = [C.throwBlock| std::tuple* { return new std::tuple(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 _LU_data _LU_pivots = [C.throwBlock| std::tuple* { return new std::tuple(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 _P _L _U _LU_data _LU_pivots _unpack_data _unpack_pivots = [C.throwBlock| std::tuple* { return new std::tuple(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 _P _L _U _LU_data _LU_pivots _unpack_data = [C.throwBlock| std::tuple* { return new std::tuple(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 _P _L _U _LU_data _LU_pivots = [C.throwBlock| std::tuple* { return new std::tuple(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 _out _self _num_samples _replacement _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 _out _self _num_samples _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 _out _self _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 _self _num_samples _replacement _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 _self _num_samples _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 _self _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 _out _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 _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 _out _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 _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 _out _n _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 _n _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 _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 _out _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 _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::i0( *$(at::Tensor* _self))); }|] i0__t :: Ptr Tensor -> IO (Ptr Tensor) i0__t _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 _out _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 _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 _out _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 _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 _out _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 _self _other _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 _self _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 _out _self _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 _self _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 _self _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 _out _self _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 _out _self _end _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 _out _self _end _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 _self _end _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 _self _end _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 _out _self _bins _min _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 _out _self _bins _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 _out _self _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 _out _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 _self _bins _min _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 _self _bins _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 _self _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 _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 _hist _bin_edges _self _bins _weight _density = [C.throwBlock| std::tuple* { return new std::tuple(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 _hist _bin_edges _self _bins _weight = [C.throwBlock| std::tuple* { return new std::tuple(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 _hist _bin_edges _self _bins = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _bins _weight _density = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _bins _weight = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram( *$(at::Tensor* _self) , *$(at::Tensor* _bins) , *$(at::Tensor* _weight))); }|] histogram_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) histogram_tt _self _bins = [C.throwBlock| std::tuple* { return new std::tuple(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 _hist _bin_edges _self _bins _range _weight _density = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram_out( *$(at::Tensor* _hist) , *$(at::Tensor* _bin_edges) , *$(at::Tensor* _self) , $(int64_t _bins) , *$(std::vector* _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 _hist _bin_edges _self _bins _range _weight = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram_out( *$(at::Tensor* _hist) , *$(at::Tensor* _bin_edges) , *$(at::Tensor* _self) , $(int64_t _bins) , *$(std::vector* _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 _hist _bin_edges _self _bins _range = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram_out( *$(at::Tensor* _hist) , *$(at::Tensor* _bin_edges) , *$(at::Tensor* _self) , $(int64_t _bins) , *$(std::vector* _range))); }|] histogram_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr (StdTuple '(Tensor,Tensor))) histogram_out_tttl _hist _bin_edges _self _bins = [C.throwBlock| std::tuple* { return new std::tuple(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 _hist _bin_edges _self = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _bins _range _weight _density = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram( *$(at::Tensor* _self) , $(int64_t _bins) , *$(std::vector* _range) , *$(at::Tensor* _weight) , $(bool _density))); }|] histogram_tlat :: Ptr Tensor -> Int64 -> Ptr (StdVector CDouble) -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) histogram_tlat _self _bins _range _weight = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram( *$(at::Tensor* _self) , $(int64_t _bins) , *$(std::vector* _range) , *$(at::Tensor* _weight))); }|] histogram_tla :: Ptr Tensor -> Int64 -> Ptr (StdVector CDouble) -> IO (Ptr (StdTuple '(Tensor,Tensor))) histogram_tla _self _bins _range = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram( *$(at::Tensor* _self) , $(int64_t _bins) , *$(std::vector* _range))); }|] histogram_tl :: Ptr Tensor -> Int64 -> IO (Ptr (StdTuple '(Tensor,Tensor))) histogram_tl _self _bins = [C.throwBlock| std::tuple* { return new std::tuple(at::histogram( *$(at::Tensor* _self) , $(int64_t _bins))); }|] histogram_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) histogram_t _self = [C.throwBlock| std::tuple* { return new std::tuple(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 _self _bins _range _weight _density = [C.throwBlock| std::vector* { return new std::vector(at::_histogramdd_bin_edges( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _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 _self _bins _range _weight = [C.throwBlock| std::vector* { return new std::vector(at::_histogramdd_bin_edges( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range) , *$(at::Tensor* _weight))); }|] _histogramdd_bin_edges_tla :: Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr TensorList) _histogramdd_bin_edges_tla _self _bins _range = [C.throwBlock| std::vector* { return new std::vector(at::_histogramdd_bin_edges( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range))); }|] _histogramdd_bin_edges_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr TensorList) _histogramdd_bin_edges_tl _self _bins = [C.throwBlock| std::vector* { return new std::vector(at::_histogramdd_bin_edges( *$(at::Tensor* _self) , *$(std::vector* _bins))); }|] _histogramdd_from_bin_cts_tlatb :: Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> Ptr Tensor -> CBool -> IO (Ptr Tensor) _histogramdd_from_bin_cts_tlatb _self _bins _range _weight _density = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _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 _self _bins _range _weight = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range) , *$(at::Tensor* _weight))); }|] _histogramdd_from_bin_cts_tla :: Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr Tensor) _histogramdd_from_bin_cts_tla _self _bins _range = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range))); }|] _histogramdd_from_bin_cts_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) _histogramdd_from_bin_cts_tl _self _bins = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_cts( *$(at::Tensor* _self) , *$(std::vector* _bins))); }|] _histogramdd_from_bin_tensors_tltb :: Ptr Tensor -> Ptr TensorList -> Ptr Tensor -> CBool -> IO (Ptr Tensor) _histogramdd_from_bin_tensors_tltb _self _bins _weight _density = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors( *$(at::Tensor* _self) , *$(std::vector* _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 _self _bins _weight = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(at::Tensor* _weight))); }|] _histogramdd_from_bin_tensors_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor) _histogramdd_from_bin_tensors_tl _self _bins = [C.throwBlock| at::Tensor* { return new at::Tensor(at::_histogramdd_from_bin_tensors( *$(at::Tensor* _self) , *$(std::vector* _bins))); }|] histogramdd_tlatb :: Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,TensorList))) histogramdd_tlatb _self _bins _range _weight _density = [C.throwBlock| std::tuple>* { return new std::tuple>(at::histogramdd( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range) , *$(at::Tensor* _weight) , $(bool _density))); }|] histogramdd_tlat :: Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,TensorList))) histogramdd_tlat _self _bins _range _weight = [C.throwBlock| std::tuple>* { return new std::tuple>(at::histogramdd( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range) , *$(at::Tensor* _weight))); }|] histogramdd_tla :: Ptr Tensor -> Ptr IntArray -> Ptr (StdVector CDouble) -> IO (Ptr (StdTuple '(Tensor,TensorList))) histogramdd_tla _self _bins _range = [C.throwBlock| std::tuple>* { return new std::tuple>(at::histogramdd( *$(at::Tensor* _self) , *$(std::vector* _bins) , *$(std::vector* _range))); }|] histogramdd_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr (StdTuple '(Tensor,TensorList))) histogramdd_tl _self _bins = [C.throwBlock| std::tuple>* { return new std::tuple>(at::histogramdd( *$(at::Tensor* _self) , *$(std::vector* _bins))); }|] fmod_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) fmod_out_tts _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _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 _out _self _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 _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::igammac( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] nextafter_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) nextafter_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nextafter_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] nextafter_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) nextafter_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nextafter( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] remainder_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) remainder_out_tts _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::remainder_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] remainder_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) remainder_ts _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::remainder( *$(at::Tensor* _self) , *$(at::Scalar* _other))); }|] remainder_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) remainder_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::remainder_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] remainder_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) remainder_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::remainder( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] remainder_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor) remainder_st _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::remainder( *$(at::Scalar* _self) , *$(at::Tensor* _other))); }|] min_t :: Ptr Tensor -> IO (Ptr Tensor) min_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::min( *$(at::Tensor* _self))); }|] fmin_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fmin_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fmin( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] fmin_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fmin_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fmin_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] max_t :: Ptr Tensor -> IO (Ptr Tensor) max_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::max( *$(at::Tensor* _self))); }|] fmax_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fmax_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fmax( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] fmax_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fmax_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fmax_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] maximum_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) maximum_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::maximum( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] maximum_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) maximum_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::maximum_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] max_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) max_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::max( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] max_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) max_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::max_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] max_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) max_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::max_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] minimum_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) minimum_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::minimum( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] minimum_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) minimum_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::minimum_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] min_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) min_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::min_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] min_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) min_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::min( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] quantile_ttlbs :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) quantile_ttlbs _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] quantile_ttlb :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor) quantile_ttlb _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim))); }|] quantile_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) quantile_ttl _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim))); }|] quantile_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) quantile_tt _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , *$(at::Tensor* _q))); }|] quantile_out_tttlbs :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) quantile_out_tttlbs _out _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] quantile_out_tttlb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor) quantile_out_tttlb _out _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim))); }|] quantile_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) quantile_out_tttl _out _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim))); }|] quantile_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) quantile_out_ttt _out _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q))); }|] quantile_tdlbs :: Ptr Tensor -> CDouble -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) quantile_tdlbs _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] quantile_tdlb :: Ptr Tensor -> CDouble -> Int64 -> CBool -> IO (Ptr Tensor) quantile_tdlb _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim))); }|] quantile_tdl :: Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor) quantile_tdl _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim))); }|] quantile_td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor) quantile_td _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile( *$(at::Tensor* _self) , $(double _q))); }|] quantile_out_ttdlbs :: Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) quantile_out_ttdlbs _out _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] quantile_out_ttdlb :: Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> CBool -> IO (Ptr Tensor) quantile_out_ttdlb _out _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim))); }|] quantile_out_ttdl :: Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor) quantile_out_ttdl _out _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim))); }|] quantile_out_ttd :: Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor) quantile_out_ttd _out _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::quantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(double _q))); }|] nanquantile_ttlbs :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) nanquantile_ttlbs _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] nanquantile_ttlb :: Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor) nanquantile_ttlb _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim))); }|] nanquantile_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) nanquantile_ttl _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim))); }|] nanquantile_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) nanquantile_tt _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , *$(at::Tensor* _q))); }|] nanquantile_out_tttlbs :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) nanquantile_out_tttlbs _out _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] nanquantile_out_tttlb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor) nanquantile_out_tttlb _out _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim) , $(bool _keepdim))); }|] nanquantile_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) nanquantile_out_tttl _out _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q) , $(int64_t _dim))); }|] nanquantile_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) nanquantile_out_ttt _out _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _q))); }|] nanquantile_tdlbs :: Ptr Tensor -> CDouble -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) nanquantile_tdlbs _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|] nanquantile_tdlb :: Ptr Tensor -> CDouble -> Int64 -> CBool -> IO (Ptr Tensor) nanquantile_tdlb _self _q _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim))); }|] nanquantile_tdl :: Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor) nanquantile_tdl _self _q _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim))); }|] nanquantile_td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor) nanquantile_td _self _q = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile( *$(at::Tensor* _self) , $(double _q))); }|] nanquantile_out_ttdlbs :: Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> CBool -> Ptr StdString -> IO (Ptr Tensor) nanquantile_out_ttdlbs _out _self _q _dim _keepdim _interpolation = [C.throwBlock| at::Tensor* { return new at::Tensor(at::nanquantile_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(double _q) , $(int64_t _dim) , $(bool _keepdim) , *$(std::string* _interpolation))); }|]