-- generated by using spec/Declarations.yaml {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} module Torch.Internal.Unmanaged.Native.Native11 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 "" fft_rfft_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_rfft_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_irfft_tlls :: Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor) fft_irfft_tlls _self _n _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft( *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim) , *$(std::string* _norm))); }|] fft_irfft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) fft_irfft_tll _self _n _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft( *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim))); }|] fft_irfft_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_irfft_tl _self _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft( *$(at::Tensor* _self) , $(int64_t _n))); }|] fft_irfft_t :: Ptr Tensor -> IO (Ptr Tensor) fft_irfft_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft( *$(at::Tensor* _self))); }|] fft_irfft_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor) fft_irfft_out_ttlls _out _self _n _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim) , *$(std::string* _norm))); }|] fft_irfft_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) fft_irfft_out_ttll _out _self _n _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim))); }|] fft_irfft_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_irfft_out_ttl _out _self _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n))); }|] fft_irfft_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_irfft_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_hfft_tlls :: Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor) fft_hfft_tlls _self _n _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft( *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim) , *$(std::string* _norm))); }|] fft_hfft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) fft_hfft_tll _self _n _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft( *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim))); }|] fft_hfft_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_hfft_tl _self _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft( *$(at::Tensor* _self) , $(int64_t _n))); }|] fft_hfft_t :: Ptr Tensor -> IO (Ptr Tensor) fft_hfft_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft( *$(at::Tensor* _self))); }|] fft_hfft_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor) fft_hfft_out_ttlls _out _self _n _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim) , *$(std::string* _norm))); }|] fft_hfft_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) fft_hfft_out_ttll _out _self _n _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim))); }|] fft_hfft_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_hfft_out_ttl _out _self _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n))); }|] fft_hfft_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_hfft_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_ihfft_tlls :: Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor) fft_ihfft_tlls _self _n _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft( *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim) , *$(std::string* _norm))); }|] fft_ihfft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) fft_ihfft_tll _self _n _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft( *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim))); }|] fft_ihfft_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_ihfft_tl _self _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft( *$(at::Tensor* _self) , $(int64_t _n))); }|] fft_ihfft_t :: Ptr Tensor -> IO (Ptr Tensor) fft_ihfft_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft( *$(at::Tensor* _self))); }|] fft_ihfft_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor) fft_ihfft_out_ttlls _out _self _n _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim) , *$(std::string* _norm))); }|] fft_ihfft_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor) fft_ihfft_out_ttll _out _self _n _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n) , $(int64_t _dim))); }|] fft_ihfft_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_ihfft_out_ttl _out _self _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(int64_t _n))); }|] fft_ihfft_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_ihfft_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_fft2_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_fft2_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_fft2_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_fft2_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_fft2_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_fft2_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_fft2_t :: Ptr Tensor -> IO (Ptr Tensor) fft_fft2_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2( *$(at::Tensor* _self))); }|] fft_fft2_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_fft2_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_fft2_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_fft2_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_fft2_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_fft2_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_fft2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_fft2_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_ifft2_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ifft2_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ifft2_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ifft2_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ifft2_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ifft2_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ifft2_t :: Ptr Tensor -> IO (Ptr Tensor) fft_ifft2_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2( *$(at::Tensor* _self))); }|] fft_ifft2_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ifft2_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ifft2_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ifft2_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ifft2_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ifft2_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ifft2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_ifft2_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_rfft2_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_rfft2_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_rfft2_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_rfft2_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_rfft2_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_rfft2_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_rfft2_t :: Ptr Tensor -> IO (Ptr Tensor) fft_rfft2_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2( *$(at::Tensor* _self))); }|] fft_rfft2_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_rfft2_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_rfft2_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_rfft2_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_rfft2_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_rfft2_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_rfft2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_rfft2_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_irfft2_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_irfft2_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_irfft2_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_irfft2_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_irfft2_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_irfft2_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_irfft2_t :: Ptr Tensor -> IO (Ptr Tensor) fft_irfft2_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2( *$(at::Tensor* _self))); }|] fft_irfft2_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_irfft2_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_irfft2_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_irfft2_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_irfft2_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_irfft2_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_irfft2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_irfft2_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_hfft2_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_hfft2_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_hfft2_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_hfft2_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_hfft2_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_hfft2_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_hfft2_t :: Ptr Tensor -> IO (Ptr Tensor) fft_hfft2_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2( *$(at::Tensor* _self))); }|] fft_hfft2_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_hfft2_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_hfft2_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_hfft2_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_hfft2_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_hfft2_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_hfft2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_hfft2_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_ihfft2_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ihfft2_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ihfft2_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfft2_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ihfft2_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfft2_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ihfft2_t :: Ptr Tensor -> IO (Ptr Tensor) fft_ihfft2_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2( *$(at::Tensor* _self))); }|] fft_ihfft2_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ihfft2_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ihfft2_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfft2_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ihfft2_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfft2_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ihfft2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_ihfft2_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfft2_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_fftn_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_fftn_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_fftn_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_fftn_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_fftn_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_fftn_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_fftn_t :: Ptr Tensor -> IO (Ptr Tensor) fft_fftn_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn( *$(at::Tensor* _self))); }|] fft_fftn_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_fftn_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_fftn_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_fftn_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_fftn_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_fftn_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_fftn_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_fftn_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_ifftn_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ifftn_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ifftn_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ifftn_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ifftn_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ifftn_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ifftn_t :: Ptr Tensor -> IO (Ptr Tensor) fft_ifftn_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn( *$(at::Tensor* _self))); }|] fft_ifftn_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ifftn_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ifftn_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ifftn_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ifftn_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ifftn_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ifftn_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_ifftn_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_rfftn_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_rfftn_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_rfftn_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_rfftn_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_rfftn_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_rfftn_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_rfftn_t :: Ptr Tensor -> IO (Ptr Tensor) fft_rfftn_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn( *$(at::Tensor* _self))); }|] fft_rfftn_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_rfftn_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_rfftn_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_rfftn_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_rfftn_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_rfftn_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_rfftn_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_rfftn_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_irfftn_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_irfftn_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_irfftn_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_irfftn_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_irfftn_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_irfftn_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_irfftn_t :: Ptr Tensor -> IO (Ptr Tensor) fft_irfftn_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn( *$(at::Tensor* _self))); }|] fft_irfftn_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_irfftn_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_irfftn_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_irfftn_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_irfftn_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_irfftn_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_irfftn_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_irfftn_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_irfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_hfftn_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_hfftn_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_hfftn_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_hfftn_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_hfftn_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_hfftn_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_hfftn_t :: Ptr Tensor -> IO (Ptr Tensor) fft_hfftn_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn( *$(at::Tensor* _self))); }|] fft_hfftn_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_hfftn_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_hfftn_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_hfftn_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_hfftn_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_hfftn_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_hfftn_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_hfftn_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_hfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_ihfftn_tlls :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ihfftn_tlls _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ihfftn_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfftn_tll _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn( *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ihfftn_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfftn_tl _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn( *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ihfftn_t :: Ptr Tensor -> IO (Ptr Tensor) fft_ihfftn_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn( *$(at::Tensor* _self))); }|] fft_ihfftn_out_ttlls :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> Ptr StdString -> IO (Ptr Tensor) fft_ihfftn_out_ttlls _out _self _s _dim _norm = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim) , *$(std::string* _norm))); }|] fft_ihfftn_out_ttll :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfftn_out_ttll _out _self _s _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s) , *$(std::vector* _dim))); }|] fft_ihfftn_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ihfftn_out_ttl _out _self _s = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::vector* _s))); }|] fft_ihfftn_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) fft_ihfftn_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ihfftn_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] fft_fftfreq_ldo :: Int64 -> CDouble -> Ptr TensorOptions -> IO (Ptr Tensor) fft_fftfreq_ldo _n _d _options = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftfreq( $(int64_t _n) , $(double _d) , *$(at::TensorOptions* _options))); }|] fft_fftfreq_ld :: Int64 -> CDouble -> IO (Ptr Tensor) fft_fftfreq_ld _n _d = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftfreq( $(int64_t _n) , $(double _d))); }|] fft_fftfreq_l :: Int64 -> IO (Ptr Tensor) fft_fftfreq_l _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftfreq( $(int64_t _n))); }|] fft_fftfreq_out_tld :: Ptr Tensor -> Int64 -> CDouble -> IO (Ptr Tensor) fft_fftfreq_out_tld _out _n _d = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftfreq_out( *$(at::Tensor* _out) , $(int64_t _n) , $(double _d))); }|] fft_fftfreq_out_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_fftfreq_out_tl _out _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftfreq_out( *$(at::Tensor* _out) , $(int64_t _n))); }|] fft_rfftfreq_ldo :: Int64 -> CDouble -> Ptr TensorOptions -> IO (Ptr Tensor) fft_rfftfreq_ldo _n _d _options = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftfreq( $(int64_t _n) , $(double _d) , *$(at::TensorOptions* _options))); }|] fft_rfftfreq_ld :: Int64 -> CDouble -> IO (Ptr Tensor) fft_rfftfreq_ld _n _d = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftfreq( $(int64_t _n) , $(double _d))); }|] fft_rfftfreq_l :: Int64 -> IO (Ptr Tensor) fft_rfftfreq_l _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftfreq( $(int64_t _n))); }|] fft_rfftfreq_out_tld :: Ptr Tensor -> Int64 -> CDouble -> IO (Ptr Tensor) fft_rfftfreq_out_tld _out _n _d = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftfreq_out( *$(at::Tensor* _out) , $(int64_t _n) , $(double _d))); }|] fft_rfftfreq_out_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor) fft_rfftfreq_out_tl _out _n = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfftfreq_out( *$(at::Tensor* _out) , $(int64_t _n))); }|] fft_fftshift_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_fftshift_tl _self _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftshift( *$(at::Tensor* _self) , *$(std::vector* _dim))); }|] fft_fftshift_t :: Ptr Tensor -> IO (Ptr Tensor) fft_fftshift_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fftshift( *$(at::Tensor* _self))); }|] fft_ifftshift_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor) fft_ifftshift_tl _self _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftshift( *$(at::Tensor* _self) , *$(std::vector* _dim))); }|] fft_ifftshift_t :: Ptr Tensor -> IO (Ptr Tensor) fft_ifftshift_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifftshift( *$(at::Tensor* _self))); }|] linalg_cholesky_ex_tbb :: Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_cholesky_ex_tbb _self _upper _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_cholesky_ex( *$(at::Tensor* _self) , $(bool _upper) , $(bool _check_errors))); }|] linalg_cholesky_ex_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_cholesky_ex_tb _self _upper = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_cholesky_ex( *$(at::Tensor* _self) , $(bool _upper))); }|] linalg_cholesky_ex_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_cholesky_ex_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_cholesky_ex( *$(at::Tensor* _self))); }|] linalg_cholesky_ex_out_tttbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_cholesky_ex_out_tttbb _L _info _self _upper _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_cholesky_ex_out( *$(at::Tensor* _L) , *$(at::Tensor* _info) , *$(at::Tensor* _self) , $(bool _upper) , $(bool _check_errors))); }|] linalg_cholesky_ex_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_cholesky_ex_out_tttb _L _info _self _upper = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_cholesky_ex_out( *$(at::Tensor* _L) , *$(at::Tensor* _info) , *$(at::Tensor* _self) , $(bool _upper))); }|] linalg_cholesky_ex_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_cholesky_ex_out_ttt _L _info _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_cholesky_ex_out( *$(at::Tensor* _L) , *$(at::Tensor* _info) , *$(at::Tensor* _self))); }|] linalg_cholesky_tb :: Ptr Tensor -> CBool -> IO (Ptr Tensor) linalg_cholesky_tb _self _upper = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cholesky( *$(at::Tensor* _self) , $(bool _upper))); }|] linalg_cholesky_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_cholesky_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cholesky( *$(at::Tensor* _self))); }|] linalg_cholesky_out_ttb :: Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor) linalg_cholesky_out_ttb _out _self _upper = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cholesky_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , $(bool _upper))); }|] linalg_cholesky_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_cholesky_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cholesky_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] linalg_cross_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) linalg_cross_ttl _self _other _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cross( *$(at::Tensor* _self) , *$(at::Tensor* _other) , $(int64_t _dim))); }|] linalg_cross_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_cross_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cross( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] linalg_cross_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) linalg_cross_out_tttl _out _self _other _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cross_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other) , $(int64_t _dim))); }|] linalg_cross_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_cross_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_cross_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] linalg_lu_factor_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_lu_factor_tb _A _pivot = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor( *$(at::Tensor* _A) , $(bool _pivot))); }|] linalg_lu_factor_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_lu_factor_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor( *$(at::Tensor* _A))); }|] linalg_lu_factor_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_lu_factor_out_tttb _LU _pivots _A _pivot = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_out( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _A) , $(bool _pivot))); }|] linalg_lu_factor_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_lu_factor_out_ttt _LU _pivots _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_out( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _A))); }|] linalg_lu_factor_ex_tbb :: Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_factor_ex_tbb _A _pivot _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_ex( *$(at::Tensor* _A) , $(bool _pivot) , $(bool _check_errors))); }|] linalg_lu_factor_ex_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_factor_ex_tb _A _pivot = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_ex( *$(at::Tensor* _A) , $(bool _pivot))); }|] linalg_lu_factor_ex_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_factor_ex_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_ex( *$(at::Tensor* _A))); }|] linalg_lu_factor_ex_out_ttttbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_factor_ex_out_ttttbb _LU _pivots _info _A _pivot _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_ex_out( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _info) , *$(at::Tensor* _A) , $(bool _pivot) , $(bool _check_errors))); }|] linalg_lu_factor_ex_out_ttttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_factor_ex_out_ttttb _LU _pivots _info _A _pivot = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_ex_out( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _info) , *$(at::Tensor* _A) , $(bool _pivot))); }|] linalg_lu_factor_ex_out_tttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_factor_ex_out_tttt _LU _pivots _info _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_factor_ex_out( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _info) , *$(at::Tensor* _A))); }|] linalg_lu_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_tb _A _pivot = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu( *$(at::Tensor* _A) , $(bool _pivot))); }|] linalg_lu_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu( *$(at::Tensor* _A))); }|] linalg_lu_out_ttttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_out_ttttb _P _L _U _A _pivot = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_out( *$(at::Tensor* _P) , *$(at::Tensor* _L) , *$(at::Tensor* _U) , *$(at::Tensor* _A) , $(bool _pivot))); }|] linalg_lu_out_tttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_lu_out_tttt _P _L _U _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lu_out( *$(at::Tensor* _P) , *$(at::Tensor* _L) , *$(at::Tensor* _U) , *$(at::Tensor* _A))); }|] linalg_lu_solve_tttbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor) linalg_lu_solve_tttbb _LU _pivots _B _left _adjoint = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_lu_solve( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B) , $(bool _left) , $(bool _adjoint))); }|] linalg_lu_solve_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor) linalg_lu_solve_tttb _LU _pivots _B _left = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_lu_solve( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B) , $(bool _left))); }|] linalg_lu_solve_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_lu_solve_ttt _LU _pivots _B = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_lu_solve( *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B))); }|] linalg_lu_solve_out_ttttbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor) linalg_lu_solve_out_ttttbb _out _LU _pivots _B _left _adjoint = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_lu_solve_out( *$(at::Tensor* _out) , *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B) , $(bool _left) , $(bool _adjoint))); }|] linalg_lu_solve_out_ttttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor) linalg_lu_solve_out_ttttb _out _LU _pivots _B _left = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_lu_solve_out( *$(at::Tensor* _out) , *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B) , $(bool _left))); }|] linalg_lu_solve_out_tttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_lu_solve_out_tttt _out _LU _pivots _B = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_lu_solve_out( *$(at::Tensor* _out) , *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B))); }|] _linalg_det_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) _linalg_det_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_det( *$(at::Tensor* _A))); }|] _linalg_det_out_tttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) _linalg_det_out_tttt _result _LU _pivots _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_det_out( *$(at::Tensor* _result) , *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _A))); }|] linalg_det_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_det_t _A = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_det( *$(at::Tensor* _A))); }|] linalg_det_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_det_out_tt _out _A = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_det_out( *$(at::Tensor* _out) , *$(at::Tensor* _A))); }|] det_t :: Ptr Tensor -> IO (Ptr Tensor) det_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::det( *$(at::Tensor* _self))); }|] linalg_ldl_factor_ex_tbb :: Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_ldl_factor_ex_tbb _self _hermitian _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_ex( *$(at::Tensor* _self) , $(bool _hermitian) , $(bool _check_errors))); }|] linalg_ldl_factor_ex_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_ldl_factor_ex_tb _self _hermitian = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_ex( *$(at::Tensor* _self) , $(bool _hermitian))); }|] linalg_ldl_factor_ex_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_ldl_factor_ex_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_ex( *$(at::Tensor* _self))); }|] linalg_ldl_factor_ex_out_ttttbb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_ldl_factor_ex_out_ttttbb _LD _pivots _info _self _hermitian _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_ex_out( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _info) , *$(at::Tensor* _self) , $(bool _hermitian) , $(bool _check_errors))); }|] linalg_ldl_factor_ex_out_ttttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_ldl_factor_ex_out_ttttb _LD _pivots _info _self _hermitian = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_ex_out( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _info) , *$(at::Tensor* _self) , $(bool _hermitian))); }|] linalg_ldl_factor_ex_out_tttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) linalg_ldl_factor_ex_out_tttt _LD _pivots _info _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_ex_out( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _info) , *$(at::Tensor* _self))); }|] linalg_ldl_factor_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_ldl_factor_tb _self _hermitian = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor( *$(at::Tensor* _self) , $(bool _hermitian))); }|] linalg_ldl_factor_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_ldl_factor_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor( *$(at::Tensor* _self))); }|] linalg_ldl_factor_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_ldl_factor_out_tttb _LD _pivots _self _hermitian = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_out( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _self) , $(bool _hermitian))); }|] linalg_ldl_factor_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_ldl_factor_out_ttt _LD _pivots _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_ldl_factor_out( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _self))); }|] linalg_ldl_solve_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor) linalg_ldl_solve_tttb _LD _pivots _B _hermitian = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_ldl_solve( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B) , $(bool _hermitian))); }|] linalg_ldl_solve_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_ldl_solve_ttt _LD _pivots _B = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_ldl_solve( *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B))); }|] linalg_ldl_solve_out_ttttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor) linalg_ldl_solve_out_ttttb _out _LD _pivots _B _hermitian = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_ldl_solve_out( *$(at::Tensor* _out) , *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B) , $(bool _hermitian))); }|] linalg_ldl_solve_out_tttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_ldl_solve_out_tttt _out _LD _pivots _B = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_ldl_solve_out( *$(at::Tensor* _out) , *$(at::Tensor* _LD) , *$(at::Tensor* _pivots) , *$(at::Tensor* _B))); }|] linalg_lstsq_ttds :: Ptr Tensor -> Ptr Tensor -> CDouble -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) linalg_lstsq_ttds _self _b _rcond _driver = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lstsq( *$(at::Tensor* _self) , *$(at::Tensor* _b) , $(double _rcond) , *$(std::string* _driver))); }|] linalg_lstsq_ttd :: Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) linalg_lstsq_ttd _self _b _rcond = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lstsq( *$(at::Tensor* _self) , *$(at::Tensor* _b) , $(double _rcond))); }|] linalg_lstsq_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) linalg_lstsq_tt _self _b = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lstsq( *$(at::Tensor* _self) , *$(at::Tensor* _b))); }|] linalg_lstsq_out_ttttttds :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CDouble -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) linalg_lstsq_out_ttttttds _solution _residuals _rank _singular_values _self _b _rcond _driver = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lstsq_out( *$(at::Tensor* _solution) , *$(at::Tensor* _residuals) , *$(at::Tensor* _rank) , *$(at::Tensor* _singular_values) , *$(at::Tensor* _self) , *$(at::Tensor* _b) , $(double _rcond) , *$(std::string* _driver))); }|] linalg_lstsq_out_ttttttd :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) linalg_lstsq_out_ttttttd _solution _residuals _rank _singular_values _self _b _rcond = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lstsq_out( *$(at::Tensor* _solution) , *$(at::Tensor* _residuals) , *$(at::Tensor* _rank) , *$(at::Tensor* _singular_values) , *$(at::Tensor* _self) , *$(at::Tensor* _b) , $(double _rcond))); }|] linalg_lstsq_out_tttttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) linalg_lstsq_out_tttttt _solution _residuals _rank _singular_values _self _b = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_lstsq_out( *$(at::Tensor* _solution) , *$(at::Tensor* _residuals) , *$(at::Tensor* _rank) , *$(at::Tensor* _singular_values) , *$(at::Tensor* _self) , *$(at::Tensor* _b))); }|] linalg_matmul_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_matmul_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matmul( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] linalg_matmul_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_matmul_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matmul_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] linalg_vecdot_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) linalg_vecdot_ttl _x _y _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vecdot( *$(at::Tensor* _x) , *$(at::Tensor* _y) , $(int64_t _dim))); }|] linalg_vecdot_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_vecdot_tt _x _y = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vecdot( *$(at::Tensor* _x) , *$(at::Tensor* _y))); }|] linalg_vecdot_out_tttl :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor) linalg_vecdot_out_tttl _out _x _y _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vecdot_out( *$(at::Tensor* _out) , *$(at::Tensor* _x) , *$(at::Tensor* _y) , $(int64_t _dim))); }|] linalg_vecdot_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_vecdot_out_ttt _out _x _y = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vecdot_out( *$(at::Tensor* _out) , *$(at::Tensor* _x) , *$(at::Tensor* _y))); }|] linalg_matrix_exp_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_matrix_exp_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_exp( *$(at::Tensor* _self))); }|] _linalg_slogdet_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) _linalg_slogdet_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_slogdet( *$(at::Tensor* _A))); }|] _linalg_slogdet_out_ttttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) _linalg_slogdet_out_ttttt _sign _logabsdet _LU _pivots _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_slogdet_out( *$(at::Tensor* _sign) , *$(at::Tensor* _logabsdet) , *$(at::Tensor* _LU) , *$(at::Tensor* _pivots) , *$(at::Tensor* _A))); }|] linalg_slogdet_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_slogdet_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_slogdet( *$(at::Tensor* _A))); }|] linalg_slogdet_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_slogdet_out_ttt _sign _logabsdet _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_slogdet_out( *$(at::Tensor* _sign) , *$(at::Tensor* _logabsdet) , *$(at::Tensor* _A))); }|] slogdet_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) slogdet_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::slogdet( *$(at::Tensor* _self))); }|] slogdet_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) slogdet_out_ttt _sign _logabsdet _self = [C.throwBlock| std::tuple* { return new std::tuple(at::slogdet_out( *$(at::Tensor* _sign) , *$(at::Tensor* _logabsdet) , *$(at::Tensor* _self))); }|] logdet_t :: Ptr Tensor -> IO (Ptr Tensor) logdet_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::logdet( *$(at::Tensor* _self))); }|] linalg_eig_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_eig_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_eig( *$(at::Tensor* _self))); }|] linalg_eig_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_eig_out_ttt _eigenvalues _eigenvectors _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_eig_out( *$(at::Tensor* _eigenvalues) , *$(at::Tensor* _eigenvectors) , *$(at::Tensor* _self))); }|] linalg_eigvals_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_eigvals_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_eigvals( *$(at::Tensor* _self))); }|] linalg_eigvals_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_eigvals_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_eigvals_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] _linalg_eigh_tsb :: Ptr Tensor -> Ptr StdString -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) _linalg_eigh_tsb _A _UPLO _compute_v = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_eigh( *$(at::Tensor* _A) , *$(std::string* _UPLO) , $(bool _compute_v))); }|] _linalg_eigh_ts :: Ptr Tensor -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor))) _linalg_eigh_ts _A _UPLO = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_eigh( *$(at::Tensor* _A) , *$(std::string* _UPLO))); }|] _linalg_eigh_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) _linalg_eigh_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_eigh( *$(at::Tensor* _A))); }|] _linalg_eigh_out_tttsb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr StdString -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) _linalg_eigh_out_tttsb _eigenvalues _eigenvectors _A _UPLO _compute_v = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_eigh_out( *$(at::Tensor* _eigenvalues) , *$(at::Tensor* _eigenvectors) , *$(at::Tensor* _A) , *$(std::string* _UPLO) , $(bool _compute_v))); }|] _linalg_eigh_out_ttts :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor))) _linalg_eigh_out_ttts _eigenvalues _eigenvectors _A _UPLO = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_eigh_out( *$(at::Tensor* _eigenvalues) , *$(at::Tensor* _eigenvectors) , *$(at::Tensor* _A) , *$(std::string* _UPLO))); }|] _linalg_eigh_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) _linalg_eigh_out_ttt _eigenvalues _eigenvectors _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_eigh_out( *$(at::Tensor* _eigenvalues) , *$(at::Tensor* _eigenvectors) , *$(at::Tensor* _A))); }|] linalg_eigh_ts :: Ptr Tensor -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_eigh_ts _self _UPLO = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_eigh( *$(at::Tensor* _self) , *$(std::string* _UPLO))); }|] linalg_eigh_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_eigh_t _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_eigh( *$(at::Tensor* _self))); }|] linalg_eigh_out_ttts :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_eigh_out_ttts _eigvals _eigvecs _self _UPLO = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_eigh_out( *$(at::Tensor* _eigvals) , *$(at::Tensor* _eigvecs) , *$(at::Tensor* _self) , *$(std::string* _UPLO))); }|] linalg_eigh_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_eigh_out_ttt _eigvals _eigvecs _self = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_eigh_out( *$(at::Tensor* _eigvals) , *$(at::Tensor* _eigvecs) , *$(at::Tensor* _self))); }|] linalg_eigvalsh_ts :: Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor) linalg_eigvalsh_ts _self _UPLO = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_eigvalsh( *$(at::Tensor* _self) , *$(std::string* _UPLO))); }|] linalg_eigvalsh_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_eigvalsh_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_eigvalsh( *$(at::Tensor* _self))); }|] linalg_eigvalsh_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr StdString -> IO (Ptr Tensor) linalg_eigvalsh_out_tts _out _self _UPLO = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_eigvalsh_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(std::string* _UPLO))); }|] linalg_eigvalsh_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_eigvalsh_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_eigvalsh_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] linalg_householder_product_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_householder_product_tt _input _tau = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_householder_product( *$(at::Tensor* _input) , *$(at::Tensor* _tau))); }|] linalg_householder_product_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_householder_product_out_ttt _out _input _tau = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_householder_product_out( *$(at::Tensor* _out) , *$(at::Tensor* _input) , *$(at::Tensor* _tau))); }|] linalg_inv_ex_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_inv_ex_tb _A _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_inv_ex( *$(at::Tensor* _A) , $(bool _check_errors))); }|] linalg_inv_ex_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_inv_ex_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_inv_ex( *$(at::Tensor* _A))); }|] linalg_inv_ex_out_tttb :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_inv_ex_out_tttb _inverse _info _A _check_errors = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_inv_ex_out( *$(at::Tensor* _inverse) , *$(at::Tensor* _info) , *$(at::Tensor* _A) , $(bool _check_errors))); }|] linalg_inv_ex_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor))) linalg_inv_ex_out_ttt _inverse _info _A = [C.throwBlock| std::tuple* { return new std::tuple(at::linalg_inv_ex_out( *$(at::Tensor* _inverse) , *$(at::Tensor* _info) , *$(at::Tensor* _A))); }|] linalg_inv_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_inv_t _A = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_inv( *$(at::Tensor* _A))); }|] linalg_inv_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_inv_out_tt _out _A = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_inv_out( *$(at::Tensor* _out) , *$(at::Tensor* _A))); }|] inverse_t :: Ptr Tensor -> IO (Ptr Tensor) inverse_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::inverse( *$(at::Tensor* _self))); }|] inverse_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) inverse_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::inverse_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] inner_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) inner_tt _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::inner( *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] inner_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) inner_out_ttt _out _self _other = [C.throwBlock| at::Tensor* { return new at::Tensor(at::inner_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _other))); }|] outer_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) outer_tt _self _vec2 = [C.throwBlock| at::Tensor* { return new at::Tensor(at::outer( *$(at::Tensor* _self) , *$(at::Tensor* _vec2))); }|] outer_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) outer_out_ttt _out _self _vec2 = [C.throwBlock| at::Tensor* { return new at::Tensor(at::outer_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _vec2))); }|] ger_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) ger_tt _self _vec2 = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ger( *$(at::Tensor* _self) , *$(at::Tensor* _vec2))); }|] ger_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) ger_out_ttt _out _self _vec2 = [C.throwBlock| at::Tensor* { return new at::Tensor(at::ger_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Tensor* _vec2))); }|] linalg_norm_tslbs :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor) linalg_norm_tslbs _self _ord _dim _keepdim _dtype = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim) , $(at::ScalarType _dtype))); }|] linalg_norm_tslb :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor) linalg_norm_tslb _self _ord _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim))); }|] linalg_norm_tsl :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> IO (Ptr Tensor) linalg_norm_tsl _self _ord _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim))); }|] linalg_norm_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) linalg_norm_ts _self _ord = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord))); }|] linalg_norm_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_norm_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm( *$(at::Tensor* _self))); }|] linalg_norm_out_ttslbs :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor) linalg_norm_out_ttslbs _out _self _ord _dim _keepdim _dtype = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim) , $(at::ScalarType _dtype))); }|] linalg_norm_out_ttslb :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor) linalg_norm_out_ttslb _out _self _ord _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim))); }|] linalg_norm_out_ttsl :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> IO (Ptr Tensor) linalg_norm_out_ttsl _out _self _ord _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim))); }|] linalg_norm_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) linalg_norm_out_tts _out _self _ord = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord))); }|] linalg_norm_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_norm_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] linalg_vector_norm_tslbs :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor) linalg_vector_norm_tslbs _self _ord _dim _keepdim _dtype = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim) , $(at::ScalarType _dtype))); }|] linalg_vector_norm_tslb :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor) linalg_vector_norm_tslb _self _ord _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim))); }|] linalg_vector_norm_tsl :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> IO (Ptr Tensor) linalg_vector_norm_tsl _self _ord _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim))); }|] linalg_vector_norm_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) linalg_vector_norm_ts _self _ord = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord))); }|] linalg_vector_norm_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_vector_norm_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm( *$(at::Tensor* _self))); }|] linalg_vector_norm_out_ttslbs :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor) linalg_vector_norm_out_ttslbs _out _self _ord _dim _keepdim _dtype = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim) , $(at::ScalarType _dtype))); }|] linalg_vector_norm_out_ttslb :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor) linalg_vector_norm_out_ttslb _out _self _ord _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim))); }|] linalg_vector_norm_out_ttsl :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> IO (Ptr Tensor) linalg_vector_norm_out_ttsl _out _self _ord _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim))); }|] linalg_vector_norm_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) linalg_vector_norm_out_tts _out _self _ord = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord))); }|] linalg_vector_norm_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_vector_norm_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_vector_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] linalg_matrix_norm_tslbs :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor) linalg_matrix_norm_tslbs _self _ord _dim _keepdim _dtype = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim) , $(at::ScalarType _dtype))); }|] linalg_matrix_norm_tslb :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor) linalg_matrix_norm_tslb _self _ord _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim))); }|] linalg_matrix_norm_tsl :: Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> IO (Ptr Tensor) linalg_matrix_norm_tsl _self _ord _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim))); }|] linalg_matrix_norm_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) linalg_matrix_norm_ts _self _ord = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm( *$(at::Tensor* _self) , *$(at::Scalar* _ord))); }|] linalg_matrix_norm_out_ttslbs :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor) linalg_matrix_norm_out_ttslbs _out _self _ord _dim _keepdim _dtype = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim) , $(at::ScalarType _dtype))); }|] linalg_matrix_norm_out_ttslb :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor) linalg_matrix_norm_out_ttslb _out _self _ord _dim _keepdim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim) , $(bool _keepdim))); }|] linalg_matrix_norm_out_ttsl :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> Ptr IntArray -> IO (Ptr Tensor) linalg_matrix_norm_out_ttsl _out _self _ord _dim = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord) , *$(std::vector* _dim))); }|] linalg_matrix_norm_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor) linalg_matrix_norm_out_tts _out _self _ord = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self) , *$(at::Scalar* _ord))); }|] linalg_matrix_norm_t :: Ptr Tensor -> IO (Ptr Tensor) linalg_matrix_norm_t _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm( *$(at::Tensor* _self))); }|] linalg_matrix_norm_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor) linalg_matrix_norm_out_tt _out _self = [C.throwBlock| at::Tensor* { return new at::Tensor(at::linalg_matrix_norm_out( *$(at::Tensor* _out) , *$(at::Tensor* _self))); }|] _linalg_svd_tbbs :: Ptr Tensor -> CBool -> CBool -> Ptr StdString -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) _linalg_svd_tbbs _A _full_matrices _compute_uv _driver = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_svd( *$(at::Tensor* _A) , $(bool _full_matrices) , $(bool _compute_uv) , *$(std::string* _driver))); }|] _linalg_svd_tbb :: Ptr Tensor -> CBool -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) _linalg_svd_tbb _A _full_matrices _compute_uv = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_svd( *$(at::Tensor* _A) , $(bool _full_matrices) , $(bool _compute_uv))); }|] _linalg_svd_tb :: Ptr Tensor -> CBool -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) _linalg_svd_tb _A _full_matrices = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_svd( *$(at::Tensor* _A) , $(bool _full_matrices))); }|] _linalg_svd_t :: Ptr Tensor -> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor))) _linalg_svd_t _A = [C.throwBlock| std::tuple* { return new std::tuple(at::_linalg_svd( *$(at::Tensor* _A))); }|]