{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Internal.Unmanaged.Native.Native10 where
import Foreign.C.String
import Foreign.C.Types
import Foreign
import Torch.Internal.Type
import qualified Language.C.Inline.Cpp as C
import qualified Language.C.Inline.Cpp.Unsafe as C
import qualified Language.C.Inline.Context as C
import qualified Language.C.Types as C
C.context $ C.cppCtx <> mempty { C.ctxTypesTable = typeTable }
C.include "<vector>"
C.include "<ATen/Tensor.h>"
C.include "<ATen/Functions.h>"
upsample_bicubic2d_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bicubic2d_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
upsample_bicubic2d_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_bicubic2d_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_bicubic2d_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_bicubic2d_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_bicubic2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bicubic2d_aa_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bicubic2d_aa_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
_upsample_bicubic2d_aa_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_bicubic2d_aa_backward_tllbd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllbd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllbd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_h)));
}|]
_upsample_bicubic2d_aa_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
_upsample_bicubic2d_aa_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_bicubic2d_aa_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_out_ttlbddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbddd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_out_ttlbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbdd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_trilinear3d_out_ttlbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlbd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)));
}|]
upsample_trilinear3d_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_trilinear3d_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_tlbddd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_tlbddd :: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_tlbddd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_tlbdd
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_tlbdd :: Ptr Tensor
-> Ptr IntArray -> CBool -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_trilinear3d_tlbdd Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_trilinear3d_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_trilinear3d_tlb Ptr Tensor
_self Ptr IntArray
_output_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_backward_out_ttllbddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbddd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_backward_out_ttllbdd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbdd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbdd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_trilinear3d_backward_out_ttllbd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllbd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)));
}|]
upsample_trilinear3d_backward_out_ttllb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllb :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_out_ttllb Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_trilinear3d_backward_tllbddd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllbddd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllbddd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_trilinear3d_backward_tllbdd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllbdd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllbdd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_trilinear3d_backward_tllb
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllb :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
upsample_trilinear3d_backward_tllb Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CBool
_align_corners =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_trilinear3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(bool _align_corners)));
}|]
upsample_nearest1d_out_ttld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest1d_out_ttld :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
upsample_nearest1d_out_ttld Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales)));
}|]
upsample_nearest1d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest1d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest1d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_upsample_nearest_exact1d_out_ttld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_out_ttld :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact1d_out_ttld Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales)));
}|]
_upsample_nearest_exact1d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact1d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
upsample_nearest1d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest1d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest1d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_upsample_nearest_exact1d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact1d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
upsample_nearest1d_backward_out_ttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest1d_backward_out_ttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest1d_backward_out_ttlld Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales)));
}|]
upsample_nearest1d_backward_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest1d_backward_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest1d_backward_out_ttll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
_upsample_nearest_exact1d_backward_out_ttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_out_ttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_out_ttlld Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales)));
}|]
_upsample_nearest_exact1d_backward_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_out_ttll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
upsample_nearest1d_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest1d_backward_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest1d_backward_tll Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
_upsample_nearest_exact1d_backward_tlld
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_tlld :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_tlld Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales)));
}|]
_upsample_nearest_exact1d_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact1d_backward_tll Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact1d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
upsample_nearest2d_out_ttldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_out_ttldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_out_ttldd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest2d_out_ttld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_out_ttld :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
upsample_nearest2d_out_ttld Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_h)));
}|]
upsample_nearest2d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest2d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest2d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_upsample_nearest_exact2d_out_ttldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_out_ttldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_out_ttldd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact2d_out_ttld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_out_ttld :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact2d_out_ttld Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_h)));
}|]
_upsample_nearest_exact2d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact2d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
upsample_nearest2d_tldd
:: Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_tldd :: Ptr Tensor -> Ptr IntArray -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_nearest2d_tldd Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest2d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_upsample_nearest_exact2d_tldd
:: Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_tldd :: Ptr Tensor -> Ptr IntArray -> CDouble -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact2d_tldd Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact2d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact2d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
upsample_nearest2d_backward_out_ttlldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_backward_out_ttlldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_backward_out_ttlldd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest2d_backward_out_ttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_backward_out_ttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_backward_out_ttlld Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)));
}|]
upsample_nearest2d_backward_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest2d_backward_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest2d_backward_out_ttll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
_upsample_nearest_exact2d_backward_out_ttlldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_out_ttlldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_out_ttlldd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact2d_backward_out_ttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_out_ttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_out_ttlld Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)));
}|]
_upsample_nearest_exact2d_backward_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_out_ttll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
upsample_nearest2d_backward_tlldd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_backward_tlldd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest2d_backward_tlldd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest2d_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest2d_backward_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest2d_backward_tll Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
_upsample_nearest_exact2d_backward_tlldd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tlldd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tlldd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact2d_backward_tlld
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tlld :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tlld Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_h)));
}|]
_upsample_nearest_exact2d_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact2d_backward_tll Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact2d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
upsample_nearest3d_out_ttlddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_out_ttlddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_out_ttlddd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest3d_out_ttldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_out_ttldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_out_ttldd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_nearest3d_out_ttld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_out_ttld :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
upsample_nearest3d_out_ttld Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)));
}|]
upsample_nearest3d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest3d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest3d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_upsample_nearest_exact3d_out_ttlddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttlddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttlddd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact3d_out_ttldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttldd Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
_upsample_nearest_exact3d_out_ttld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttld :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttld Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)));
}|]
_upsample_nearest_exact3d_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact3d_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
upsample_nearest3d_tlddd
:: Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_tlddd :: Ptr Tensor
-> Ptr IntArray -> CDouble -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_nearest3d_tlddd Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest3d_tldd
:: Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_tldd :: Ptr Tensor -> Ptr IntArray -> CDouble -> CDouble -> IO (Ptr Tensor)
upsample_nearest3d_tldd Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_nearest3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest3d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
_upsample_nearest_exact3d_tlddd
:: Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_tlddd :: Ptr Tensor
-> Ptr IntArray -> CDouble -> CDouble -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact3d_tlddd Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact3d_tldd
:: Ptr Tensor
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_tldd :: Ptr Tensor -> Ptr IntArray -> CDouble -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact3d_tldd Ptr Tensor
_self Ptr IntArray
_output_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
_upsample_nearest_exact3d_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact3d_tl Ptr Tensor
_self Ptr IntArray
_output_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)));
}|]
upsample_nearest3d_backward_out_ttllddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttllddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttllddd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest3d_backward_out_ttlldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttlldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttlldd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_nearest3d_backward_out_ttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttlld Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)));
}|]
upsample_nearest3d_backward_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest3d_backward_out_ttll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
_upsample_nearest_exact3d_backward_out_ttllddd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttllddd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttllddd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact3d_backward_out_ttlldd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttlldd :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttlldd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
_upsample_nearest_exact3d_backward_out_ttlld
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttlld :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttlld Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)));
}|]
_upsample_nearest_exact3d_backward_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttll :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_out_ttll Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
upsample_nearest3d_backward_tllddd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tllddd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tllddd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
upsample_nearest3d_backward_tlldd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tlldd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tlldd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
upsample_nearest3d_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
upsample_nearest3d_backward_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
upsample_nearest3d_backward_tll Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::upsample_nearest3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
_upsample_nearest_exact3d_backward_tllddd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tllddd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tllddd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h CDouble
_scales_w =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)
, $(double _scales_w)));
}|]
_upsample_nearest_exact3d_backward_tlldd
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tlldd :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tlldd Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d CDouble
_scales_h =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)
, $(double _scales_h)));
}|]
_upsample_nearest_exact3d_backward_tlld
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> CDouble
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tlld :: Ptr Tensor
-> Ptr IntArray -> Ptr IntArray -> CDouble -> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tlld Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size CDouble
_scales_d =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)
, $(double _scales_d)));
}|]
_upsample_nearest_exact3d_backward_tll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tll :: Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
_upsample_nearest_exact3d_backward_tll Ptr Tensor
_grad_output Ptr IntArray
_output_size Ptr IntArray
_input_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_upsample_nearest_exact3d_backward(
*$(at::Tensor* _grad_output)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _input_size)));
}|]
sigmoid_backward_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
sigmoid_backward_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
sigmoid_backward_out_ttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_output =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::sigmoid_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _output)));
}|]
sigmoid_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
sigmoid_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
sigmoid_backward_tt Ptr Tensor
_grad_output Ptr Tensor
_output =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::sigmoid_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _output)));
}|]
logit_backward_out_tttd
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
logit_backward_out_tttd :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
logit_backward_out_tttd Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self CDouble
_eps =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logit_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, $(double _eps)));
}|]
logit_backward_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logit_backward_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logit_backward_out_ttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logit_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)));
}|]
logit_backward_ttd
:: Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
logit_backward_ttd :: Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
logit_backward_ttd Ptr Tensor
_grad_output Ptr Tensor
_self CDouble
_eps =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logit_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, $(double _eps)));
}|]
logit_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
logit_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
logit_backward_tt Ptr Tensor
_grad_output Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::logit_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)));
}|]
tanh_backward_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
tanh_backward_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
tanh_backward_out_ttt Ptr Tensor
_grad_input Ptr Tensor
_grad_output Ptr Tensor
_output =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tanh_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _output)));
}|]
tanh_backward_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
tanh_backward_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
tanh_backward_tt Ptr Tensor
_grad_output Ptr Tensor
_output =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::tanh_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _output)));
}|]
slow_conv_transpose2d_out_tttltllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltllll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv_transpose2d_out_tttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltlll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
slow_conv_transpose2d_out_tttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_transpose2d_out_tttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttltl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv_transpose2d_out_tttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttlt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttlt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv_transpose2d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv_transpose2d_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
slow_conv_transpose2d_ttltllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltllll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv_transpose2d_ttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltlll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
slow_conv_transpose2d_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_transpose2d_ttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttltl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv_transpose2d_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
slow_conv_transpose2d_ttlt Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv_transpose2d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose2d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv_transpose2d_ttl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
slow_conv_transpose3d_out_tttltllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltllll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv_transpose3d_out_tttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltlll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
slow_conv_transpose3d_out_tttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_transpose3d_out_tttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttltl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv_transpose3d_out_tttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttlt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttlt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv_transpose3d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv_transpose3d_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
slow_conv_transpose3d_ttltllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltllll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv_transpose3d_ttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltlll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_output_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _output_padding)));
}|]
slow_conv_transpose3d_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_transpose3d_ttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttltl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv_transpose3d_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
slow_conv_transpose3d_ttlt Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv_transpose3d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_transpose3d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv_transpose3d_ttl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_transpose3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
thnn_conv2d_out_tttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_out_tttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_out_tttltll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
thnn_conv2d_out_tttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_out_tttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_out_tttltl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
thnn_conv2d_out_tttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
thnn_conv2d_out_tttlt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
thnn_conv2d_out_tttlt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
thnn_conv2d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
thnn_conv2d_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
thnn_conv2d_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
thnn_conv2d_ttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_ttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_ttltl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
thnn_conv2d_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
thnn_conv2d_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
thnn_conv2d_ttlt Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
thnn_conv2d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
thnn_conv2d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
thnn_conv2d_ttl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::thnn_conv2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
_slow_conv2d_forward_out_tttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_slow_conv2d_forward_out_tttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_slow_conv2d_forward_out_tttltll Ptr Tensor
_output Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_slow_conv2d_forward_out(
*$(at::Tensor* _output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
_slow_conv2d_forward_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_slow_conv2d_forward_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_slow_conv2d_forward_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_slow_conv2d_forward(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
_slow_conv2d_backward_out_ttttttlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_slow_conv2d_backward_out_ttttttlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_slow_conv2d_backward_out_ttttttlll Ptr Tensor
_grad_input Ptr Tensor
_grad_weight Ptr Tensor
_grad_bias Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_slow_conv2d_backward_out(
*$(at::Tensor* _grad_input)
, *$(at::Tensor* _grad_weight)
, *$(at::Tensor* _grad_bias)
, *$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
_slow_conv2d_backward_tttllla
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdArray '(CBool,3))
-> IO (Ptr (StdTuple '(Tensor,Tensor,Tensor)))
_slow_conv2d_backward_tttllla :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
_slow_conv2d_backward_tttllla Ptr Tensor
_grad_output Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr IntArray
_stride Ptr IntArray
_padding Ptr (StdArray '(CBool, 3))
_output_mask =
[C.throwBlock| std::tuple<at::Tensor,at::Tensor,at::Tensor>* { return new std::tuple<at::Tensor,at::Tensor,at::Tensor>(at::_slow_conv2d_backward(
*$(at::Tensor* _grad_output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::array<bool,3>* _output_mask)));
}|]
_conv_depthwise2d_out_tttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_conv_depthwise2d_out_tttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_conv_depthwise2d_out_tttltlll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_conv_depthwise2d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
_conv_depthwise2d_ttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_conv_depthwise2d_ttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
_conv_depthwise2d_ttltlll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_conv_depthwise2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
conv_depthwise3d_ttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_depthwise3d_ttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
conv_depthwise3d_ttltlll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::conv_depthwise3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv3d_out_tttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_out_tttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_out_tttltll Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv3d_out_tttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_out_tttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_out_tttltl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv3d_out_tttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv3d_out_tttlt :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv3d_out_tttlt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv3d_out_tttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_out_tttl :: Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv3d_out_tttl Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
slow_conv3d_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv3d_ttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_ttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_ttltl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv3d_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv3d_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
slow_conv3d_ttlt Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv3d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv3d_ttl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
slow_conv3d_forward_out_tttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_forward_out_tttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_forward_out_tttltll Ptr Tensor
_output Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d_forward_out(
*$(at::Tensor* _output)
, *$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv3d_forward_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_forward_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv3d_forward_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv3d_forward(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_dilated2d_ttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttltlll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv_dilated2d_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_dilated2d_ttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttltl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv_dilated2d_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
slow_conv_dilated2d_ttlt Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv_dilated2d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated2d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv_dilated2d_ttl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated2d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
slow_conv_dilated3d_ttltlll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttltlll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttltlll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding Ptr IntArray
_dilation =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _dilation)));
}|]
slow_conv_dilated3d_ttltll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttltll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttltll Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride Ptr IntArray
_padding =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)
, *$(std::vector<int64_t>* _padding)));
}|]
slow_conv_dilated3d_ttltl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttltl :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttltl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)
, *$(std::vector<int64_t>* _stride)));
}|]
slow_conv_dilated3d_ttlt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttlt :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr Tensor -> IO (Ptr Tensor)
slow_conv_dilated3d_ttlt Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size Ptr Tensor
_bias =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)
, *$(at::Tensor* _bias)));
}|]
slow_conv_dilated3d_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
slow_conv_dilated3d_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
slow_conv_dilated3d_ttl Ptr Tensor
_self Ptr Tensor
_weight Ptr IntArray
_kernel_size =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::slow_conv_dilated3d(
*$(at::Tensor* _self)
, *$(at::Tensor* _weight)
, *$(std::vector<int64_t>* _kernel_size)));
}|]
col2im_out_ttlllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
col2im_out_ttlllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
col2im_out_ttlllll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_output_size Ptr IntArray
_kernel_size Ptr IntArray
_dilation Ptr IntArray
_padding Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::col2im_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _dilation)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _stride)));
}|]
col2im_tlllll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
col2im_tlllll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
col2im_tlllll Ptr Tensor
_self Ptr IntArray
_output_size Ptr IntArray
_kernel_size Ptr IntArray
_dilation Ptr IntArray
_padding Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::col2im(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _output_size)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _dilation)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _stride)));
}|]
column_stack_l
:: Ptr TensorList
-> IO (Ptr Tensor)
column_stack_l :: Ptr TensorList -> IO (Ptr Tensor)
column_stack_l Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::column_stack(
*$(std::vector<at::Tensor>* _tensors)));
}|]
column_stack_out_tl
:: Ptr Tensor
-> Ptr TensorList
-> IO (Ptr Tensor)
column_stack_out_tl :: Ptr Tensor -> Ptr TensorList -> IO (Ptr Tensor)
column_stack_out_tl Ptr Tensor
_out Ptr TensorList
_tensors =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::column_stack_out(
*$(at::Tensor* _out)
, *$(std::vector<at::Tensor>* _tensors)));
}|]
im2col_out_ttllll
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
im2col_out_ttllll :: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
im2col_out_ttllll Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_dilation Ptr IntArray
_padding Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::im2col_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _dilation)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _stride)));
}|]
im2col_tllll
:: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
im2col_tllll :: Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
im2col_tllll Ptr Tensor
_self Ptr IntArray
_kernel_size Ptr IntArray
_dilation Ptr IntArray
_padding Ptr IntArray
_stride =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::im2col(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _kernel_size)
, *$(std::vector<int64_t>* _dilation)
, *$(std::vector<int64_t>* _padding)
, *$(std::vector<int64_t>* _stride)));
}|]
isfinite_t
:: Ptr Tensor
-> IO (Ptr Tensor)
isfinite_t :: Ptr Tensor -> IO (Ptr Tensor)
isfinite_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::isfinite(
*$(at::Tensor* _self)));
}|]
isinf_t
:: Ptr Tensor
-> IO (Ptr Tensor)
isinf_t :: Ptr Tensor -> IO (Ptr Tensor)
isinf_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::isinf(
*$(at::Tensor* _self)));
}|]
isposinf_t
:: Ptr Tensor
-> IO (Ptr Tensor)
isposinf_t :: Ptr Tensor -> IO (Ptr Tensor)
isposinf_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::isposinf(
*$(at::Tensor* _self)));
}|]
isposinf_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
isposinf_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
isposinf_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::isposinf_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
isneginf_t
:: Ptr Tensor
-> IO (Ptr Tensor)
isneginf_t :: Ptr Tensor -> IO (Ptr Tensor)
isneginf_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::isneginf(
*$(at::Tensor* _self)));
}|]
isneginf_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
isneginf_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
isneginf_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::isneginf_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
_add_batch_dim_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
_add_batch_dim_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
_add_batch_dim_tll Ptr Tensor
_self Int64
_batch_dim Int64
_level =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_add_batch_dim(
*$(at::Tensor* _self)
, $(int64_t _batch_dim)
, $(int64_t _level)));
}|]
_remove_batch_dim_tlll
:: Ptr Tensor
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
_remove_batch_dim_tlll :: Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
_remove_batch_dim_tlll Ptr Tensor
_self Int64
_level Int64
_batch_size Int64
_out_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::_remove_batch_dim(
*$(at::Tensor* _self)
, $(int64_t _level)
, $(int64_t _batch_size)
, $(int64_t _out_dim)));
}|]
special_entr_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_entr_t :: Ptr Tensor -> IO (Ptr Tensor)
special_entr_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_entr(
*$(at::Tensor* _self)));
}|]
special_entr_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_entr_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_entr_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_entr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_ndtri_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_ndtri_t :: Ptr Tensor -> IO (Ptr Tensor)
special_ndtri_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_ndtri(
*$(at::Tensor* _self)));
}|]
special_ndtri_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_ndtri_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_ndtri_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_ndtri_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_log_ndtr_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_log_ndtr_t :: Ptr Tensor -> IO (Ptr Tensor)
special_log_ndtr_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_log_ndtr(
*$(at::Tensor* _self)));
}|]
special_log_ndtr_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_log_ndtr_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_log_ndtr_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_log_ndtr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_expm1_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_expm1_t :: Ptr Tensor -> IO (Ptr Tensor)
special_expm1_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_expm1(
*$(at::Tensor* _self)));
}|]
special_expm1_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_expm1_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_expm1_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_expm1_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_exp2_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_exp2_t :: Ptr Tensor -> IO (Ptr Tensor)
special_exp2_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_exp2(
*$(at::Tensor* _self)));
}|]
special_exp2_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_exp2_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_exp2_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_exp2_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_psi_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_psi_t :: Ptr Tensor -> IO (Ptr Tensor)
special_psi_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_psi(
*$(at::Tensor* _self)));
}|]
special_psi_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_psi_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_psi_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_psi_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_digamma_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_digamma_t :: Ptr Tensor -> IO (Ptr Tensor)
special_digamma_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_digamma(
*$(at::Tensor* _self)));
}|]
special_digamma_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_digamma_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_digamma_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_digamma_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_gammaln_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_gammaln_t :: Ptr Tensor -> IO (Ptr Tensor)
special_gammaln_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_gammaln(
*$(at::Tensor* _self)));
}|]
special_gammaln_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_gammaln_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_gammaln_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_gammaln_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_erf_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_erf_t :: Ptr Tensor -> IO (Ptr Tensor)
special_erf_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erf(
*$(at::Tensor* _self)));
}|]
special_erf_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_erf_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_erf_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erf_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_erfc_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_erfc_t :: Ptr Tensor -> IO (Ptr Tensor)
special_erfc_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erfc(
*$(at::Tensor* _self)));
}|]
special_erfc_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_erfc_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_erfc_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erfc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_erfcx_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_erfcx_t :: Ptr Tensor -> IO (Ptr Tensor)
special_erfcx_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erfcx(
*$(at::Tensor* _self)));
}|]
special_erfcx_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_erfcx_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_erfcx_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erfcx_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_erfinv_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_erfinv_t :: Ptr Tensor -> IO (Ptr Tensor)
special_erfinv_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erfinv(
*$(at::Tensor* _self)));
}|]
special_erfinv_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_erfinv_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_erfinv_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_erfinv_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_ndtr_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_ndtr_t :: Ptr Tensor -> IO (Ptr Tensor)
special_ndtr_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_ndtr(
*$(at::Tensor* _self)));
}|]
special_ndtr_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_ndtr_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_ndtr_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_ndtr_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_xlog1py_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlog1py_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_xlog1py_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlog1py(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_xlog1py_st
:: Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlog1py_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_xlog1py_st Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlog1py(
*$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
special_xlog1py_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
special_xlog1py_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_xlog1py_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlog1py(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
special_xlog1py_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlog1py_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_xlog1py_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlog1py_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_xlog1py_out_tst
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlog1py_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_xlog1py_out_tst Ptr Tensor
_out Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlog1py_out(
*$(at::Tensor* _out)
, *$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
special_xlog1py_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
special_xlog1py_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_xlog1py_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlog1py_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
special_xlogy_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlogy_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_xlogy_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlogy(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_xlogy_st
:: Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlogy_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_xlogy_st Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlogy(
*$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
special_xlogy_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
special_xlogy_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_xlogy_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlogy(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
special_xlogy_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlogy_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_xlogy_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlogy_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_xlogy_out_tst
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
special_xlogy_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_xlogy_out_tst Ptr Tensor
_out Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlogy_out(
*$(at::Tensor* _out)
, *$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
special_xlogy_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
special_xlogy_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_xlogy_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_xlogy_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
special_zeta_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_zeta_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_zeta_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_zeta(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_zeta_st
:: Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
special_zeta_st :: Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_zeta_st Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_zeta(
*$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
special_zeta_ts
:: Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
special_zeta_ts :: Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_zeta_ts Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_zeta(
*$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
special_zeta_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_zeta_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_zeta_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_zeta_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_zeta_out_tst
:: Ptr Tensor
-> Ptr Scalar
-> Ptr Tensor
-> IO (Ptr Tensor)
special_zeta_out_tst :: Ptr Tensor -> Ptr Scalar -> Ptr Tensor -> IO (Ptr Tensor)
special_zeta_out_tst Ptr Tensor
_out Ptr Scalar
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_zeta_out(
*$(at::Tensor* _out)
, *$(at::Scalar* _self)
, *$(at::Tensor* _other)));
}|]
special_zeta_out_tts
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
special_zeta_out_tts :: Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
special_zeta_out_tts Ptr Tensor
_out Ptr Tensor
_self Ptr Scalar
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_zeta_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Scalar* _other)));
}|]
special_i0_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_i0_t :: Ptr Tensor -> IO (Ptr Tensor)
special_i0_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i0(
*$(at::Tensor* _self)));
}|]
special_i0_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_i0_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_i0_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i0_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_i0e_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_i0e_t :: Ptr Tensor -> IO (Ptr Tensor)
special_i0e_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i0e(
*$(at::Tensor* _self)));
}|]
special_i0e_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_i0e_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_i0e_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i0e_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_i1_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_i1_t :: Ptr Tensor -> IO (Ptr Tensor)
special_i1_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i1(
*$(at::Tensor* _self)));
}|]
special_i1_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_i1_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_i1_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i1_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_i1e_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_i1e_t :: Ptr Tensor -> IO (Ptr Tensor)
special_i1e_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i1e(
*$(at::Tensor* _self)));
}|]
special_i1e_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_i1e_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_i1e_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_i1e_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_logit_td
:: Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
special_logit_td :: Ptr Tensor -> CDouble -> IO (Ptr Tensor)
special_logit_td Ptr Tensor
_self CDouble
_eps =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logit(
*$(at::Tensor* _self)
, $(double _eps)));
}|]
special_logit_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_logit_t :: Ptr Tensor -> IO (Ptr Tensor)
special_logit_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logit(
*$(at::Tensor* _self)));
}|]
special_logit_out_ttd
:: Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
special_logit_out_ttd :: Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
special_logit_out_ttd Ptr Tensor
_out Ptr Tensor
_self CDouble
_eps =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logit_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(double _eps)));
}|]
special_logit_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_logit_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_logit_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logit_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_polygamma_lt
:: Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
special_polygamma_lt :: Int64 -> Ptr Tensor -> IO (Ptr Tensor)
special_polygamma_lt Int64
_n Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_polygamma(
$(int64_t _n)
, *$(at::Tensor* _self)));
}|]
special_polygamma_out_tlt
:: Ptr Tensor
-> Int64
-> Ptr Tensor
-> IO (Ptr Tensor)
special_polygamma_out_tlt :: Ptr Tensor -> Int64 -> Ptr Tensor -> IO (Ptr Tensor)
special_polygamma_out_tlt Ptr Tensor
_out Int64
_n Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_polygamma_out(
*$(at::Tensor* _out)
, $(int64_t _n)
, *$(at::Tensor* _self)));
}|]
special_logsumexp_tlb
:: Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
special_logsumexp_tlb :: Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
special_logsumexp_tlb Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logsumexp(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _dim)
, $(bool _keepdim)));
}|]
special_logsumexp_tl
:: Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
special_logsumexp_tl :: Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
special_logsumexp_tl Ptr Tensor
_self Ptr IntArray
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logsumexp(
*$(at::Tensor* _self)
, *$(std::vector<int64_t>* _dim)));
}|]
special_logsumexp_out_ttlb
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
special_logsumexp_out_ttlb :: Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
special_logsumexp_out_ttlb Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim CBool
_keepdim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logsumexp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _dim)
, $(bool _keepdim)));
}|]
special_logsumexp_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
special_logsumexp_out_ttl :: Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
special_logsumexp_out_ttl Ptr Tensor
_out Ptr Tensor
_self Ptr IntArray
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_logsumexp_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(std::vector<int64_t>* _dim)));
}|]
special_expit_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_expit_t :: Ptr Tensor -> IO (Ptr Tensor)
special_expit_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_expit(
*$(at::Tensor* _self)));
}|]
special_expit_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_expit_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_expit_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_expit_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_sinc_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_sinc_t :: Ptr Tensor -> IO (Ptr Tensor)
special_sinc_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_sinc(
*$(at::Tensor* _self)));
}|]
special_sinc_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_sinc_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_sinc_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_sinc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_round_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
special_round_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
special_round_tl Ptr Tensor
_self Int64
_decimals =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_round(
*$(at::Tensor* _self)
, $(int64_t _decimals)));
}|]
special_round_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_round_t :: Ptr Tensor -> IO (Ptr Tensor)
special_round_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_round(
*$(at::Tensor* _self)));
}|]
special_round_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
special_round_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
special_round_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_decimals =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_round_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _decimals)));
}|]
special_round_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_round_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_round_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_round_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_log1p_t
:: Ptr Tensor
-> IO (Ptr Tensor)
special_log1p_t :: Ptr Tensor -> IO (Ptr Tensor)
special_log1p_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_log1p(
*$(at::Tensor* _self)));
}|]
special_log1p_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_log1p_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_log1p_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_log1p_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
special_log_softmax_tls
:: Ptr Tensor
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
special_log_softmax_tls :: Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
special_log_softmax_tls Ptr Tensor
_self Int64
_dim ScalarType
_dtype =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_log_softmax(
*$(at::Tensor* _self)
, $(int64_t _dim)
, $(at::ScalarType _dtype)));
}|]
special_log_softmax_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
special_log_softmax_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
special_log_softmax_tl Ptr Tensor
_self Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_log_softmax(
*$(at::Tensor* _self)
, $(int64_t _dim)));
}|]
special_gammainc_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_gammainc_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_gammainc_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_gammainc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_gammainc_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_gammainc_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_gammainc_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_gammainc(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_gammaincc_out_ttt
:: Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_gammaincc_out_ttt :: Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_gammaincc_out_ttt Ptr Tensor
_out Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_gammaincc_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_gammaincc_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
special_gammaincc_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
special_gammaincc_tt Ptr Tensor
_self Ptr Tensor
_other =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_gammaincc(
*$(at::Tensor* _self)
, *$(at::Tensor* _other)));
}|]
special_multigammaln_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
special_multigammaln_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
special_multigammaln_tl Ptr Tensor
_self Int64
_p =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_multigammaln(
*$(at::Tensor* _self)
, $(int64_t _p)));
}|]
special_multigammaln_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
special_multigammaln_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
special_multigammaln_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_p =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_multigammaln_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _p)));
}|]
special_softmax_tls
:: Ptr Tensor
-> Int64
-> ScalarType
-> IO (Ptr Tensor)
special_softmax_tls :: Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
special_softmax_tls Ptr Tensor
_self Int64
_dim ScalarType
_dtype =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_softmax(
*$(at::Tensor* _self)
, $(int64_t _dim)
, $(at::ScalarType _dtype)));
}|]
special_softmax_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
special_softmax_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
special_softmax_tl Ptr Tensor
_self Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::special_softmax(
*$(at::Tensor* _self)
, $(int64_t _dim)));
}|]
fft_fft_tlls
:: Ptr Tensor
-> Int64
-> Int64
-> Ptr StdString
-> IO (Ptr Tensor)
fft_fft_tlls :: Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor)
fft_fft_tlls Ptr Tensor
_self Int64
_n Int64
_dim Ptr StdString
_norm =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft(
*$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)
, *$(std::string* _norm)));
}|]
fft_fft_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fft_fft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fft_fft_tll Ptr Tensor
_self Int64
_n Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft(
*$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)));
}|]
fft_fft_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
fft_fft_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
fft_fft_tl Ptr Tensor
_self Int64
_n =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft(
*$(at::Tensor* _self)
, $(int64_t _n)));
}|]
fft_fft_t
:: Ptr Tensor
-> IO (Ptr Tensor)
fft_fft_t :: Ptr Tensor -> IO (Ptr Tensor)
fft_fft_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft(
*$(at::Tensor* _self)));
}|]
fft_fft_out_ttlls
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr StdString
-> IO (Ptr Tensor)
fft_fft_out_ttlls :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor)
fft_fft_out_ttlls Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim Ptr StdString
_norm =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)
, *$(std::string* _norm)));
}|]
fft_fft_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fft_fft_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fft_fft_out_ttll Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)));
}|]
fft_fft_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
fft_fft_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
fft_fft_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_n =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)));
}|]
fft_fft_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
fft_fft_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fft_fft_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_fft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
fft_ifft_tlls
:: Ptr Tensor
-> Int64
-> Int64
-> Ptr StdString
-> IO (Ptr Tensor)
fft_ifft_tlls :: Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor)
fft_ifft_tlls Ptr Tensor
_self Int64
_n Int64
_dim Ptr StdString
_norm =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft(
*$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)
, *$(std::string* _norm)));
}|]
fft_ifft_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fft_ifft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fft_ifft_tll Ptr Tensor
_self Int64
_n Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft(
*$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)));
}|]
fft_ifft_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
fft_ifft_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
fft_ifft_tl Ptr Tensor
_self Int64
_n =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft(
*$(at::Tensor* _self)
, $(int64_t _n)));
}|]
fft_ifft_t
:: Ptr Tensor
-> IO (Ptr Tensor)
fft_ifft_t :: Ptr Tensor -> IO (Ptr Tensor)
fft_ifft_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft(
*$(at::Tensor* _self)));
}|]
fft_ifft_out_ttlls
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr StdString
-> IO (Ptr Tensor)
fft_ifft_out_ttlls :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor)
fft_ifft_out_ttlls Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim Ptr StdString
_norm =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)
, *$(std::string* _norm)));
}|]
fft_ifft_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fft_ifft_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fft_ifft_out_ttll Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)));
}|]
fft_ifft_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
fft_ifft_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
fft_ifft_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_n =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)));
}|]
fft_ifft_out_tt
:: Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
fft_ifft_out_tt :: Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
fft_ifft_out_tt Ptr Tensor
_out Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_ifft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)));
}|]
fft_rfft_tlls
:: Ptr Tensor
-> Int64
-> Int64
-> Ptr StdString
-> IO (Ptr Tensor)
fft_rfft_tlls :: Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor)
fft_rfft_tlls Ptr Tensor
_self Int64
_n Int64
_dim Ptr StdString
_norm =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft(
*$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)
, *$(std::string* _norm)));
}|]
fft_rfft_tll
:: Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fft_rfft_tll :: Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fft_rfft_tll Ptr Tensor
_self Int64
_n Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft(
*$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)));
}|]
fft_rfft_tl
:: Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
fft_rfft_tl :: Ptr Tensor -> Int64 -> IO (Ptr Tensor)
fft_rfft_tl Ptr Tensor
_self Int64
_n =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft(
*$(at::Tensor* _self)
, $(int64_t _n)));
}|]
fft_rfft_t
:: Ptr Tensor
-> IO (Ptr Tensor)
fft_rfft_t :: Ptr Tensor -> IO (Ptr Tensor)
fft_rfft_t Ptr Tensor
_self =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft(
*$(at::Tensor* _self)));
}|]
fft_rfft_out_ttlls
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr StdString
-> IO (Ptr Tensor)
fft_rfft_out_ttlls :: Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Ptr StdString -> IO (Ptr Tensor)
fft_rfft_out_ttlls Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim Ptr StdString
_norm =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)
, *$(std::string* _norm)));
}|]
fft_rfft_out_ttll
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> IO (Ptr Tensor)
fft_rfft_out_ttll :: Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
fft_rfft_out_ttll Ptr Tensor
_out Ptr Tensor
_self Int64
_n Int64
_dim =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)
, $(int64_t _dim)));
}|]
fft_rfft_out_ttl
:: Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr Tensor)
fft_rfft_out_ttl :: Ptr Tensor -> Ptr Tensor -> Int64 -> IO (Ptr Tensor)
fft_rfft_out_ttl Ptr Tensor
_out Ptr Tensor
_self Int64
_n =
[C.throwBlock| at::Tensor* { return new at::Tensor(at::fft_rfft_out(
*$(at::Tensor* _out)
, *$(at::Tensor* _self)
, $(int64_t _n)));
}|]