{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Functional.Internal where
import System.IO.Unsafe
import Foreign.ForeignPtr
import qualified Torch.Internal.Managed.Native as ATen
import qualified Torch.Internal.Managed.Type.Tensor as ATen
import qualified Torch.Internal.Managed.Type.Scalar as ATen
import qualified Torch.Internal.Managed.Type.Tuple as ATen
import qualified Torch.Internal.Const as ATen
import qualified Torch.Internal.Type as ATen
import qualified Torch.Internal.Managed.Cast
import Torch.Internal.Cast
import Torch.Tensor
import Torch.Scalar
import Torch.Dimname
import Torch.DType
import Torch.Cast
align_tensors
:: [Tensor]
-> [Tensor]
align_tensors :: [Tensor] -> [Tensor]
align_tensors [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.align_tensors_l) [Tensor]
_tensors
native_dropout
:: Tensor
-> Double
-> Bool
-> (Tensor,Tensor)
native_dropout :: Tensor -> Double -> Bool -> (Tensor, Tensor)
native_dropout Tensor
_input Double
_p Bool
_train = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Double -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CDouble -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.native_dropout_tdb) Tensor
_input Double
_p Bool
_train
dropout
:: Tensor
-> Double
-> Bool
-> Tensor
dropout :: Tensor -> Double -> Bool -> Tensor
dropout Tensor
_input Double
_p Bool
_train = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.dropout_tdb) Tensor
_input Double
_p Bool
_train
feature_dropout
:: Tensor
-> Double
-> Bool
-> Tensor
feature_dropout :: Tensor -> Double -> Bool -> Tensor
feature_dropout Tensor
_input Double
_p Bool
_train = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.feature_dropout_tdb) Tensor
_input Double
_p Bool
_train
alpha_dropout
:: Tensor
-> Double
-> Bool
-> Tensor
alpha_dropout :: Tensor -> Double -> Bool -> Tensor
alpha_dropout Tensor
_input Double
_p Bool
_train = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.alpha_dropout_tdb) Tensor
_input Double
_p Bool
_train
feature_alpha_dropout
:: Tensor
-> Double
-> Bool
-> Tensor
feature_alpha_dropout :: Tensor -> Double -> Bool -> Tensor
feature_alpha_dropout Tensor
_input Double
_p Bool
_train = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.feature_alpha_dropout_tdb) Tensor
_input Double
_p Bool
_train
abs
:: Tensor
-> Tensor
abs :: Tensor -> Tensor
abs Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.abs_t) Tensor
_self
absolute
:: Tensor
-> Tensor
absolute :: Tensor -> Tensor
absolute Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.absolute_t) Tensor
_self
angle
:: Tensor
-> Tensor
angle :: Tensor -> Tensor
angle Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.angle_t) Tensor
_self
view_as_real
:: Tensor
-> Tensor
view_as_real :: Tensor -> Tensor
view_as_real Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.view_as_real_t) Tensor
_self
view_as_complex
:: Tensor
-> Tensor
view_as_complex :: Tensor -> Tensor
view_as_complex Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.view_as_complex_t) Tensor
_self
sgn
:: Tensor
-> Tensor
sgn :: Tensor -> Tensor
sgn Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sgn_t) Tensor
_self
real
:: Tensor
-> Tensor
real :: Tensor -> Tensor
real Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.real_t) Tensor
_self
imag
:: Tensor
-> Tensor
imag :: Tensor -> Tensor
imag Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.imag_t) Tensor
_self
conj
:: Tensor
-> Tensor
conj :: Tensor -> Tensor
conj Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.conj_t) Tensor
_self
conj_physical
:: Tensor
-> Tensor
conj_physical :: Tensor -> Tensor
conj_physical Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.conj_physical_t) Tensor
_self
resolve_conj
:: Tensor
-> Tensor
resolve_conj :: Tensor -> Tensor
resolve_conj Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.resolve_conj_t) Tensor
_self
resolve_neg
:: Tensor
-> Tensor
resolve_neg :: Tensor -> Tensor
resolve_neg Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.resolve_neg_t) Tensor
_self
acos
:: Tensor
-> Tensor
acos :: Tensor -> Tensor
acos Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.acos_t) Tensor
_self
arccos
:: Tensor
-> Tensor
arccos :: Tensor -> Tensor
arccos Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arccos_t) Tensor
_self
avg_pool1d
:: Tensor
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Tensor
avg_pool1d :: Tensor -> Int -> Int -> Int -> Bool -> Bool -> Tensor
avg_pool1d Tensor
_self Int
_kernel_size Int
_stride Int
_padding Bool
_ceil_mode Bool
_count_include_pad = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.avg_pool1d_tlllbb) Tensor
_self Int
_kernel_size Int
_stride Int
_padding Bool
_ceil_mode Bool
_count_include_pad
adaptive_avg_pool1d
:: Tensor
-> Int
-> Tensor
adaptive_avg_pool1d :: Tensor -> Int -> Tensor
adaptive_avg_pool1d Tensor
_self Int
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.adaptive_avg_pool1d_tl) Tensor
_self Int
_output_size
adaptive_max_pool1d
:: Tensor
-> Int
-> (Tensor,Tensor)
adaptive_max_pool1d :: Tensor -> Int -> (Tensor, Tensor)
adaptive_max_pool1d Tensor
_self Int
_output_size = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.adaptive_max_pool1d_tl) Tensor
_self Int
_output_size
add
:: Tensor
-> Tensor
-> Float
-> Tensor
add :: Tensor -> Tensor -> Float -> Tensor
add Tensor
_self Tensor
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.add_tts) Tensor
_self Tensor
_other Float
_alpha
addScalar
:: Tensor
-> Float
-> Float
-> Tensor
addScalar :: Tensor -> Float -> Float -> Tensor
addScalar Tensor
_self Float
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.add_tss) Tensor
_self Float
_other Float
_alpha
addmv
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
addmv :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
addmv Tensor
_self Tensor
_mat Tensor
_vec Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.addmv_tttss) Tensor
_self Tensor
_mat Tensor
_vec Float
_beta Float
_alpha
addr
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
addr :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
addr Tensor
_self Tensor
_vec1 Tensor
_vec2 Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.addr_tttss) Tensor
_self Tensor
_vec1 Tensor
_vec2 Float
_beta Float
_alpha
affine_grid_generator
:: Tensor
-> [Int]
-> Bool
-> Tensor
affine_grid_generator :: Tensor -> [Int] -> Bool -> Tensor
affine_grid_generator Tensor
_theta [Int]
_size Bool
_align_corners = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.affine_grid_generator_tlb) Tensor
_theta [Int]
_size Bool
_align_corners
allDim
:: Tensor
-> Int
-> Bool
-> Tensor
allDim :: Tensor -> Int -> Bool -> Tensor
allDim Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.all_tlb) Tensor
_self Int
_dim Bool
_keepdim
allWithDimname
:: Tensor
-> Dimname
-> Bool
-> Tensor
allWithDimname :: Tensor -> Dimname -> Bool -> Tensor
allWithDimname Tensor
_self Dimname
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> CBool -> IO (ForeignPtr Tensor)
ATen.all_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
allclose
:: Tensor
-> Tensor
-> Double
-> Double
-> Bool
-> Bool
allclose :: Tensor -> Tensor -> Double -> Double -> Bool -> Bool
allclose Tensor
_self Tensor
_other Double
_rtol Double
_atol Bool
_equal_nan = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> CDouble -> CBool -> IO CBool)
-> Tensor -> Tensor -> Double -> Double -> Bool -> IO Bool
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> CDouble -> CBool -> IO CBool
ATen.allclose_ttddb) Tensor
_self Tensor
_other Double
_rtol Double
_atol Bool
_equal_nan
anyDim
:: Tensor
-> Int
-> Bool
-> Tensor
anyDim :: Tensor -> Int -> Bool -> Tensor
anyDim Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.any_tlb) Tensor
_self Int
_dim Bool
_keepdim
anyWithDimname
:: Tensor
-> Dimname
-> Bool
-> Tensor
anyWithDimname :: Tensor -> Dimname -> Bool -> Tensor
anyWithDimname Tensor
_self Dimname
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> CBool -> IO (ForeignPtr Tensor)
ATen.any_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
argmax
:: Tensor
-> Int
-> Bool
-> Tensor
argmax :: Tensor -> Int -> Bool -> Tensor
argmax Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.argmax_tlb) Tensor
_self Int
_dim Bool
_keepdim
argmin
:: Tensor
-> Int
-> Bool
-> Tensor
argmin :: Tensor -> Int -> Bool -> Tensor
argmin Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.argmin_tlb) Tensor
_self Int
_dim Bool
_keepdim
acosh
:: Tensor
-> Tensor
acosh :: Tensor -> Tensor
acosh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.acosh_t) Tensor
_self
arccosh
:: Tensor
-> Tensor
arccosh :: Tensor -> Tensor
arccosh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arccosh_t) Tensor
_self
asinh
:: Tensor
-> Tensor
asinh :: Tensor -> Tensor
asinh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.asinh_t) Tensor
_self
arcsinh
:: Tensor
-> Tensor
arcsinh :: Tensor -> Tensor
arcsinh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arcsinh_t) Tensor
_self
atanh
:: Tensor
-> Tensor
atanh :: Tensor -> Tensor
atanh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.atanh_t) Tensor
_self
arctanh
:: Tensor
-> Tensor
arctanh :: Tensor -> Tensor
arctanh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arctanh_t) Tensor
_self
as_strided
:: Tensor
-> [Int]
-> [Int]
-> Int
-> Tensor
as_strided :: Tensor -> [Int] -> [Int] -> Int -> Tensor
as_strided Tensor
_self [Int]
_size [Int]
_stride Int
_storage_offset = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> [Int] -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.as_strided_tlll) Tensor
_self [Int]
_size [Int]
_stride Int
_storage_offset
asin
:: Tensor
-> Tensor
asin :: Tensor -> Tensor
asin Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.asin_t) Tensor
_self
arcsin
:: Tensor
-> Tensor
arcsin :: Tensor -> Tensor
arcsin Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arcsin_t) Tensor
_self
atan
:: Tensor
-> Tensor
atan :: Tensor -> Tensor
atan Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.atan_t) Tensor
_self
arctan
:: Tensor
-> Tensor
arctan :: Tensor -> Tensor
arctan Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arctan_t) Tensor
_self
atleast_1d_t
:: Tensor
-> Tensor
atleast_1d_t :: Tensor -> Tensor
atleast_1d_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.atleast_1d_t) Tensor
_self
atleast_1d_l
:: [Tensor]
-> [Tensor]
atleast_1d_l :: [Tensor] -> [Tensor]
atleast_1d_l [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.atleast_1d_l) [Tensor]
_tensors
atleast_2d_t
:: Tensor
-> Tensor
atleast_2d_t :: Tensor -> Tensor
atleast_2d_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.atleast_2d_t) Tensor
_self
atleast_2d_l
:: [Tensor]
-> [Tensor]
atleast_2d_l :: [Tensor] -> [Tensor]
atleast_2d_l [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.atleast_2d_l) [Tensor]
_tensors
atleast_3d_t
:: Tensor
-> Tensor
atleast_3d_t :: Tensor -> Tensor
atleast_3d_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.atleast_3d_t) Tensor
_self
atleast_3d_l
:: [Tensor]
-> [Tensor]
atleast_3d_l :: [Tensor] -> [Tensor]
atleast_3d_l [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.atleast_3d_l) [Tensor]
_tensors
baddbmm
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
baddbmm :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
baddbmm Tensor
_self Tensor
_batch1 Tensor
_batch2 Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.baddbmm_tttss) Tensor
_self Tensor
_batch1 Tensor
_batch2 Float
_beta Float
_alpha
batch_norm
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> Bool
-> Tensor
batch_norm :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> Bool
-> Tensor
batch_norm Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_momentum Double
_eps Bool
_cudnn_enabled = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.batch_norm_tttttbddb) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_momentum Double
_eps Bool
_cudnn_enabled
quantized_batch_norm
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Int
-> Tensor
quantized_batch_norm :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Int
-> Tensor
quantized_batch_norm Tensor
_input Tensor
_weight Tensor
_bias Tensor
_mean Tensor
_var Double
_eps Double
_output_scale Int
_output_zero_point = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
ATen.quantized_batch_norm_tttttddl) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_mean Tensor
_var Double
_eps Double
_output_scale Int
_output_zero_point
bilinear
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
bilinear :: Tensor -> Tensor -> Tensor -> Tensor -> Tensor
bilinear Tensor
_input1 Tensor
_input2 Tensor
_weight Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.bilinear_tttt) Tensor
_input1 Tensor
_input2 Tensor
_weight Tensor
_bias
binary_cross_entropy
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Tensor
binary_cross_entropy :: Tensor -> Tensor -> Tensor -> Int -> Tensor
binary_cross_entropy Tensor
_self Tensor
_target Tensor
_weight Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
ATen.binary_cross_entropy_tttl) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction
binary_cross_entropy_with_logits
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Tensor
binary_cross_entropy_with_logits :: Tensor -> Tensor -> Tensor -> Tensor -> Int -> Tensor
binary_cross_entropy_with_logits Tensor
_self Tensor
_target Tensor
_weight Tensor
_pos_weight Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
ATen.binary_cross_entropy_with_logits_ttttl) Tensor
_self Tensor
_target Tensor
_weight Tensor
_pos_weight Int
_reduction
bincount
:: Tensor
-> Tensor
-> Int
-> Tensor
bincount :: Tensor -> Tensor -> Int -> Tensor
bincount Tensor
_self Tensor
_weights Int
_minlength = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.bincount_ttl) Tensor
_self Tensor
_weights Int
_minlength
bitwise_not
:: Tensor
-> Tensor
bitwise_not :: Tensor -> Tensor
bitwise_not Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_not_t) Tensor
_self
copysign_tt
:: Tensor
-> Tensor
-> Tensor
copysign_tt :: Tensor -> Tensor -> Tensor
copysign_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.copysign_tt) Tensor
_self Tensor
_other
copysign_ts
:: Tensor
-> Float
-> Tensor
copysign_ts :: Tensor -> Float -> Tensor
copysign_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.copysign_ts) Tensor
_self Float
_other
logical_not
:: Tensor
-> Tensor
logical_not :: Tensor -> Tensor
logical_not Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logical_not_t) Tensor
_self
logical_xor
:: Tensor
-> Tensor
-> Tensor
logical_xor :: Tensor -> Tensor -> Tensor
logical_xor Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logical_xor_tt) Tensor
_self Tensor
_other
logical_and
:: Tensor
-> Tensor
-> Tensor
logical_and :: Tensor -> Tensor -> Tensor
logical_and Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logical_and_tt) Tensor
_self Tensor
_other
logical_or
:: Tensor
-> Tensor
-> Tensor
logical_or :: Tensor -> Tensor -> Tensor
logical_or Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logical_or_tt) Tensor
_self Tensor
_other
bmm
:: Tensor
-> Tensor
-> Tensor
bmm :: Tensor -> Tensor -> Tensor
bmm Tensor
_self Tensor
_mat2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bmm_tt) Tensor
_self Tensor
_mat2
broadcast_tensors
:: [Tensor]
-> [Tensor]
broadcast_tensors :: [Tensor] -> [Tensor]
broadcast_tensors [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.broadcast_tensors_l) [Tensor]
_tensors
broadcast_to
:: Tensor
-> [Int]
-> Tensor
broadcast_to :: Tensor -> [Int] -> Tensor
broadcast_to Tensor
_self [Int]
_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.broadcast_to_tl) Tensor
_self [Int]
_size
cat
:: [Tensor]
-> Int
-> Tensor
cat :: [Tensor] -> Int -> Tensor
cat [Tensor]
_tensors Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor))
-> [Tensor] -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor)
ATen.cat_ll) [Tensor]
_tensors Int
_dim
catWithDimname
:: [Tensor]
-> Dimname
-> Tensor
catWithDimname :: [Tensor] -> Dimname -> Tensor
catWithDimname [Tensor]
_tensors Dimname
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList
-> ForeignPtr Dimname -> IO (ForeignPtr Tensor))
-> [Tensor] -> Dimname -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList
-> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
ATen.cat_ln) [Tensor]
_tensors Dimname
_dim
concat_ll
:: [Tensor]
-> Int
-> Tensor
concat_ll :: [Tensor] -> Int -> Tensor
concat_ll [Tensor]
_tensors Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor))
-> [Tensor] -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor)
ATen.concat_ll) [Tensor]
_tensors Int
_dim
concat_ln
:: [Tensor]
-> Dimname
-> Tensor
concat_ln :: [Tensor] -> Dimname -> Tensor
concat_ln [Tensor]
_tensors Dimname
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList
-> ForeignPtr Dimname -> IO (ForeignPtr Tensor))
-> [Tensor] -> Dimname -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList
-> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
ATen.concat_ln) [Tensor]
_tensors Dimname
_dim
concatenate_ll
:: [Tensor]
-> Int
-> Tensor
concatenate_ll :: [Tensor] -> Int -> Tensor
concatenate_ll [Tensor]
_tensors Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor))
-> [Tensor] -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor)
ATen.concatenate_ll) [Tensor]
_tensors Int
_dim
concatenate_ln
:: [Tensor]
-> Dimname
-> Tensor
concatenate_ln :: [Tensor] -> Dimname -> Tensor
concatenate_ln [Tensor]
_tensors Dimname
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList
-> ForeignPtr Dimname -> IO (ForeignPtr Tensor))
-> [Tensor] -> Dimname -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList
-> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
ATen.concatenate_ln) [Tensor]
_tensors Dimname
_dim
block_diag
:: [Tensor]
-> Tensor
block_diag :: [Tensor] -> Tensor
block_diag [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.block_diag_l) [Tensor]
_tensors
ceil
:: Tensor
-> Tensor
ceil :: Tensor -> Tensor
ceil Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ceil_t) Tensor
_self
chain_matmul
:: [Tensor]
-> Tensor
chain_matmul :: [Tensor] -> Tensor
chain_matmul [Tensor]
_matrices = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.chain_matmul_l) [Tensor]
_matrices
unsafe_chunk
:: Tensor
-> Int
-> Int
-> [Tensor]
unsafe_chunk :: Tensor -> Int -> Int -> [Tensor]
unsafe_chunk Tensor
_self Int
_chunks Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
ATen.unsafe_chunk_tll) Tensor
_self Int
_chunks Int
_dim
chunk
:: Tensor
-> Int
-> Int
-> [Tensor]
chunk :: Tensor -> Int -> Int -> [Tensor]
chunk Tensor
_self Int
_chunks Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
ATen.chunk_tll) Tensor
_self Int
_chunks Int
_dim
tensor_split_tll
:: Tensor
-> Int
-> Int
-> [Tensor]
tensor_split_tll :: Tensor -> Int -> Int -> [Tensor]
tensor_split_tll Tensor
_self Int
_sections Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
ATen.tensor_split_tll) Tensor
_self Int
_sections Int
_dim
tensor_split_ttl
:: Tensor
-> Tensor
-> Int
-> [Tensor]
tensor_split_ttl :: Tensor -> Tensor -> Int -> [Tensor]
tensor_split_ttl Tensor
_self Tensor
_tensor_indices_or_sections Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Tensor -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
ATen.tensor_split_ttl) Tensor
_self Tensor
_tensor_indices_or_sections Int
_dim
clamp_tss
:: Tensor
-> Float
-> Float
-> Tensor
clamp_tss :: Tensor -> Float -> Float -> Tensor
clamp_tss Tensor
_self Float
_min Float
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.clamp_tss) Tensor
_self Float
_min Float
_max
clamp_ttt
:: Tensor
-> Tensor
-> Tensor
-> Tensor
clamp_ttt :: Tensor -> Tensor -> Tensor -> Tensor
clamp_ttt Tensor
_self Tensor
_min Tensor
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.clamp_ttt) Tensor
_self Tensor
_min Tensor
_max
clamp_max_ts
:: Tensor
-> Float
-> Tensor
clamp_max_ts :: Tensor -> Float -> Tensor
clamp_max_ts Tensor
_self Float
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.clamp_max_ts) Tensor
_self Float
_max
clamp_max_tt
:: Tensor
-> Tensor
-> Tensor
clamp_max_tt :: Tensor -> Tensor -> Tensor
clamp_max_tt Tensor
_self Tensor
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.clamp_max_tt) Tensor
_self Tensor
_max
clamp_min_ts
:: Tensor
-> Float
-> Tensor
clamp_min_ts :: Tensor -> Float -> Tensor
clamp_min_ts Tensor
_self Float
_min = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.clamp_min_ts) Tensor
_self Float
_min
clamp_min_tt
:: Tensor
-> Tensor
-> Tensor
clamp_min_tt :: Tensor -> Tensor -> Tensor
clamp_min_tt Tensor
_self Tensor
_min = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.clamp_min_tt) Tensor
_self Tensor
_min
clip_tss
:: Tensor
-> Float
-> Float
-> Tensor
clip_tss :: Tensor -> Float -> Float -> Tensor
clip_tss Tensor
_self Float
_min Float
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.clip_tss) Tensor
_self Float
_min Float
_max
clip_ttt
:: Tensor
-> Tensor
-> Tensor
-> Tensor
clip_ttt :: Tensor -> Tensor -> Tensor -> Tensor
clip_ttt Tensor
_self Tensor
_min Tensor
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.clip_ttt) Tensor
_self Tensor
_min Tensor
_max
cudnn_is_acceptable
:: Tensor
-> Bool
cudnn_is_acceptable :: Tensor -> Bool
cudnn_is_acceptable Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.cudnn_is_acceptable_t) Tensor
_self
complex
:: Tensor
-> Tensor
-> Tensor
complex :: Tensor -> Tensor -> Tensor
complex Tensor
_real Tensor
_imag = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.complex_tt) Tensor
_real Tensor
_imag
polar
:: Tensor
-> Tensor
-> Tensor
polar :: Tensor -> Tensor -> Tensor
polar Tensor
_abs Tensor
_angle = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.polar_tt) Tensor
_abs Tensor
_angle
constant_pad_nd
:: Tensor
-> [Int]
-> Float
-> Tensor
constant_pad_nd :: Tensor -> [Int] -> Float -> Tensor
constant_pad_nd Tensor
_self [Int]
_pad Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.constant_pad_nd_tls) Tensor
_self [Int]
_pad Float
_value
convolution
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> Tensor
convolution :: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> Tensor
convolution Tensor
_input Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Bool
_transposed [Int]
_output_padding Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.convolution_tttlllbll) Tensor
_input Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Bool
_transposed [Int]
_output_padding Int
_groups
convolution_overrideable
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> Tensor
convolution_overrideable :: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> Tensor
convolution_overrideable Tensor
_input Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Bool
_transposed [Int]
_output_padding Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.convolution_overrideable_tttlllbll) Tensor
_input Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Bool
_transposed [Int]
_output_padding Int
_groups
convolution_backward_overrideable
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> (Bool,Bool,Bool)
-> (Tensor,Tensor,Tensor)
convolution_backward_overrideable :: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> (Bool, Bool, Bool)
-> (Tensor, Tensor, Tensor)
convolution_backward_overrideable Tensor
_grad_output Tensor
_input Tensor
_weight [Int]
_stride [Int]
_padding [Int]
_dilation Bool
_transposed [Int]
_output_padding Int
_groups (Bool, Bool, Bool)
_output_mask = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr (StdArray '(CBool, 3))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Bool
-> [Int]
-> Int
-> (Bool, Bool, Bool)
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
cast10 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr (StdArray '(CBool, 3))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.convolution_backward_overrideable_tttlllblla) Tensor
_grad_output Tensor
_input Tensor
_weight [Int]
_stride [Int]
_padding [Int]
_dilation Bool
_transposed [Int]
_output_padding Int
_groups (Bool, Bool, Bool)
_output_mask
conv1d_tttllll
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Tensor
conv1d_tttllll :: Tensor -> Tensor -> Tensor -> Int -> Int -> Int -> Int -> Tensor
conv1d_tttllll Tensor
_input Tensor
_weight Tensor
_bias Int
_stride Int
_padding Int
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv1d_tttllll) Tensor
_input Tensor
_weight Tensor
_bias Int
_stride Int
_padding Int
_dilation Int
_groups
conv2d
:: Tensor
-> Tensor
-> Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Int
-> Tensor
conv2d :: Tensor
-> Tensor
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Int
-> Tensor
conv2d Tensor
_input Tensor
_weight Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv2d_tttllll) Tensor
_input Tensor
_weight Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Int
_groups
conv3d_tttllll
:: Tensor
-> Tensor
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Int
-> Tensor
conv3d_tttllll :: Tensor
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Int
-> Tensor
conv3d_tttllll Tensor
_input Tensor
_weight Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv3d_tttllll) Tensor
_input Tensor
_weight Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Int
_groups
conv1d_tttlsll
:: Tensor
-> Tensor
-> Tensor
-> Int
-> String
-> Int
-> Int
-> Tensor
conv1d_tttlsll :: Tensor -> Tensor -> Tensor -> Int -> String -> Int -> Int -> Tensor
conv1d_tttlsll Tensor
_input Tensor
_weight Tensor
_bias Int
_stride String
_padding Int
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Int
-> String
-> Int
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv1d_tttlsll) Tensor
_input Tensor
_weight Tensor
_bias Int
_stride String
_padding Int
_dilation Int
_groups
conv2d_tttlsll
:: Tensor
-> Tensor
-> Tensor
-> (Int,Int)
-> String
-> (Int,Int)
-> Int
-> Tensor
conv2d_tttlsll :: Tensor
-> Tensor
-> Tensor
-> (Int, Int)
-> String
-> (Int, Int)
-> Int
-> Tensor
conv2d_tttlsll Tensor
_input Tensor
_weight Tensor
_bias (Int, Int)
_stride String
_padding (Int, Int)
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> (Int, Int)
-> String
-> (Int, Int)
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv2d_tttlsll) Tensor
_input Tensor
_weight Tensor
_bias (Int, Int)
_stride String
_padding (Int, Int)
_dilation Int
_groups
conv3d_tttlsll
:: Tensor
-> Tensor
-> Tensor
-> (Int,Int,Int)
-> String
-> (Int,Int,Int)
-> Int
-> Tensor
conv3d_tttlsll :: Tensor
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> String
-> (Int, Int, Int)
-> Int
-> Tensor
conv3d_tttlsll Tensor
_input Tensor
_weight Tensor
_bias (Int, Int, Int)
_stride String
_padding (Int, Int, Int)
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> String
-> (Int, Int, Int)
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv3d_tttlsll) Tensor
_input Tensor
_weight Tensor
_bias (Int, Int, Int)
_stride String
_padding (Int, Int, Int)
_dilation Int
_groups
conv_tbc
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Tensor
conv_tbc :: Tensor -> Tensor -> Tensor -> Int -> Tensor
conv_tbc Tensor
_self Tensor
_weight Tensor
_bias Int
_pad = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
ATen.conv_tbc_tttl) Tensor
_self Tensor
_weight Tensor
_bias Int
_pad
conv_transpose1d
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Int
-> Tensor
conv_transpose1d :: Tensor
-> Tensor -> Tensor -> Int -> Int -> Int -> Int -> Int -> Tensor
conv_transpose1d Tensor
_input Tensor
_weight Tensor
_bias Int
_stride Int
_padding Int
_output_padding Int
_groups Int
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.conv_transpose1d_tttlllll) Tensor
_input Tensor
_weight Tensor
_bias Int
_stride Int
_padding Int
_output_padding Int
_groups Int
_dilation
conv_transpose2d
:: Tensor
-> Tensor
-> Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Int
-> (Int,Int)
-> Tensor
conv_transpose2d :: Tensor
-> Tensor
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Int
-> (Int, Int)
-> Tensor
conv_transpose2d Tensor
_input Tensor
_weight Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_output_padding Int
_groups (Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Int
-> (Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.conv_transpose2d_tttlllll) Tensor
_input Tensor
_weight Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_output_padding Int
_groups (Int, Int)
_dilation
conv_transpose3d
:: Tensor
-> Tensor
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Int
-> (Int,Int,Int)
-> Tensor
conv_transpose3d :: Tensor
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Int
-> (Int, Int, Int)
-> Tensor
conv_transpose3d Tensor
_input Tensor
_weight Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_output_padding Int
_groups (Int, Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Int
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.conv_transpose3d_tttlllll) Tensor
_input Tensor
_weight Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_output_padding Int
_groups (Int, Int, Int)
_dilation
copy
:: Tensor
-> Tensor
-> Bool
-> Tensor
copy :: Tensor -> Tensor -> Bool -> Tensor
copy Tensor
_self Tensor
_src Bool
_non_blocking = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.copy_ttb) Tensor
_self Tensor
_src Bool
_non_blocking
cos
:: Tensor
-> Tensor
cos :: Tensor -> Tensor
cos Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.cos_t) Tensor
_self
cosh
:: Tensor
-> Tensor
cosh :: Tensor -> Tensor
cosh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.cosh_t) Tensor
_self
cosine_embedding_loss
:: Tensor
-> Tensor
-> Tensor
-> Double
-> Int
-> Tensor
cosine_embedding_loss :: Tensor -> Tensor -> Tensor -> Double -> Int -> Tensor
cosine_embedding_loss Tensor
_input1 Tensor
_input2 Tensor
_target Double
_margin Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Double -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
ATen.cosine_embedding_loss_tttdl) Tensor
_input1 Tensor
_input2 Tensor
_target Double
_margin Int
_reduction
count_nonzero_tl
:: Tensor
-> Int
-> Tensor
count_nonzero_tl :: Tensor -> Int -> Tensor
count_nonzero_tl Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.count_nonzero_tl) Tensor
_self Int
_dim
cov
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Tensor
cov :: Tensor -> Int -> Tensor -> Tensor -> Tensor
cov Tensor
_self Int
_correction Tensor
_fweights Tensor
_aweights = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.cov_tltt) Tensor
_self Int
_correction Tensor
_fweights Tensor
_aweights
corrcoef
:: Tensor
-> Tensor
corrcoef :: Tensor -> Tensor
corrcoef Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.corrcoef_t) Tensor
_self
cudnn_affine_grid_generator
:: Tensor
-> Int
-> Int
-> Int
-> Int
-> Tensor
cudnn_affine_grid_generator :: Tensor -> Int -> Int -> Int -> Int -> Tensor
cudnn_affine_grid_generator Tensor
_theta Int
_N Int
_C Int
_H Int
_W = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.cudnn_affine_grid_generator_tllll) Tensor
_theta Int
_N Int
_C Int
_H Int
_W
cudnn_batch_norm
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> (Tensor,Tensor,Tensor,Tensor)
cudnn_batch_norm :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> (Tensor, Tensor, Tensor, Tensor)
cudnn_batch_norm Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_exponential_average_factor Double
_epsilon = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.cudnn_batch_norm_tttttbdd) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_exponential_average_factor Double
_epsilon
cudnn_convolution
:: Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Bool
-> Tensor
cudnn_convolution :: Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Bool
-> Tensor
cudnn_convolution Tensor
_self Tensor
_weight [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic Bool
_allow_tf32 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.cudnn_convolution_ttllllbbb) Tensor
_self Tensor
_weight [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic Bool
_allow_tf32
cudnn_convolution_transpose
:: Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Bool
-> Tensor
cudnn_convolution_transpose :: Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Bool
-> Tensor
cudnn_convolution_transpose Tensor
_self Tensor
_weight [Int]
_padding [Int]
_output_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic Bool
_allow_tf32 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
cast10 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.cudnn_convolution_transpose_ttlllllbbb) Tensor
_self Tensor
_weight [Int]
_padding [Int]
_output_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic Bool
_allow_tf32
cudnn_convolution_relu
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
cudnn_convolution_relu :: Tensor
-> Tensor -> Tensor -> [Int] -> [Int] -> [Int] -> Int -> Tensor
cudnn_convolution_relu Tensor
_self Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.cudnn_convolution_relu_tttllll) Tensor
_self Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups
cudnn_convolution_add_relu
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
cudnn_convolution_add_relu :: Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
cudnn_convolution_add_relu Tensor
_self Tensor
_weight Tensor
_z Float
_alpha Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.cudnn_convolution_add_relu_tttstllll) Tensor
_self Tensor
_weight Tensor
_z Float
_alpha Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups
cudnn_grid_sampler
:: Tensor
-> Tensor
-> Tensor
cudnn_grid_sampler :: Tensor -> Tensor -> Tensor
cudnn_grid_sampler Tensor
_self Tensor
_grid = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.cudnn_grid_sampler_tt) Tensor
_self Tensor
_grid
cummax_tl
:: Tensor
-> Int
-> (Tensor,Tensor)
cummax_tl :: Tensor -> Int -> (Tensor, Tensor)
cummax_tl Tensor
_self Int
_dim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.cummax_tl) Tensor
_self Int
_dim
cummax_tn
:: Tensor
-> Dimname
-> (Tensor,Tensor)
cummax_tn :: Tensor -> Dimname -> (Tensor, Tensor)
cummax_tn Tensor
_self Dimname
_dim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.cummax_tn) Tensor
_self Dimname
_dim
cummin_tl
:: Tensor
-> Int
-> (Tensor,Tensor)
cummin_tl :: Tensor -> Int -> (Tensor, Tensor)
cummin_tl Tensor
_self Int
_dim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.cummin_tl) Tensor
_self Int
_dim
cummin_tn
:: Tensor
-> Dimname
-> (Tensor,Tensor)
cummin_tn :: Tensor -> Dimname -> (Tensor, Tensor)
cummin_tn Tensor
_self Dimname
_dim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.cummin_tn) Tensor
_self Dimname
_dim
cumprod
:: Tensor
-> Int
-> DType
-> Tensor
cumprod :: Tensor -> Int -> DType -> Tensor
cumprod Tensor
_self Int
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.cumprod_tls) Tensor
_self Int
_dim DType
_dtype
cumprodWithDimname
:: Tensor
-> Dimname
-> DType
-> Tensor
cumprodWithDimname :: Tensor -> Dimname -> DType -> Tensor
cumprodWithDimname Tensor
_self Dimname
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.cumprod_tns) Tensor
_self Dimname
_dim DType
_dtype
cumsum
:: Tensor
-> Int
-> DType
-> Tensor
cumsum :: Tensor -> Int -> DType -> Tensor
cumsum Tensor
_self Int
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.cumsum_tls) Tensor
_self Int
_dim DType
_dtype
cumsumWithDimname
:: Tensor
-> Dimname
-> DType
-> Tensor
cumsumWithDimname :: Tensor -> Dimname -> DType -> Tensor
cumsumWithDimname Tensor
_self Dimname
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.cumsum_tns) Tensor
_self Dimname
_dim DType
_dtype
cumulative_trapezoid_ttl
:: Tensor
-> Tensor
-> Int
-> Tensor
cumulative_trapezoid_ttl :: Tensor -> Tensor -> Int -> Tensor
cumulative_trapezoid_ttl Tensor
_y Tensor
_x Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.cumulative_trapezoid_ttl) Tensor
_y Tensor
_x Int
_dim
cumulative_trapezoid_tsl
:: Tensor
-> Float
-> Int
-> Tensor
cumulative_trapezoid_tsl :: Tensor -> Float -> Int -> Tensor
cumulative_trapezoid_tsl Tensor
_y Float
_dx Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> Int64 -> IO (ForeignPtr Tensor)
ATen.cumulative_trapezoid_tsl) Tensor
_y Float
_dx Int
_dim
ctcLoss'
:: Tensor
-> Tensor
-> [Int]
-> [Int]
-> Int
-> Int
-> Bool
-> Tensor
ctcLoss' :: Tensor -> Tensor -> [Int] -> [Int] -> Int -> Int -> Bool -> Tensor
ctcLoss' Tensor
_log_probs Tensor
_targets [Int]
_input_lengths [Int]
_target_lengths Int
_blank Int
_reduction Bool
_zero_infinity = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> Int
-> Int
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.ctc_loss_ttllllb) Tensor
_log_probs Tensor
_targets [Int]
_input_lengths [Int]
_target_lengths Int
_blank Int
_reduction Bool
_zero_infinity
ctcLoss
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Bool
-> Tensor
ctcLoss :: Tensor
-> Tensor -> Tensor -> Tensor -> Int -> Int -> Bool -> Tensor
ctcLoss Tensor
_log_probs Tensor
_targets Tensor
_input_lengths Tensor
_target_lengths Int
_blank Int
_reduction Bool
_zero_infinity = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.ctc_loss_ttttllb) Tensor
_log_probs Tensor
_targets Tensor
_input_lengths Tensor
_target_lengths Int
_blank Int
_reduction Bool
_zero_infinity
diag_embed
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
diag_embed :: Tensor -> Int -> Int -> Int -> Tensor
diag_embed Tensor
_self Int
_offset Int
_dim1 Int
_dim2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.diag_embed_tlll) Tensor
_self Int
_offset Int
_dim1 Int
_dim2
diagflat
:: Tensor
-> Int
-> Tensor
diagflat :: Tensor -> Int -> Tensor
diagflat Tensor
_self Int
_offset = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.diagflat_tl) Tensor
_self Int
_offset
diagonal_tlll
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
diagonal_tlll :: Tensor -> Int -> Int -> Int -> Tensor
diagonal_tlll Tensor
_self Int
_offset Int
_dim1 Int
_dim2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.diagonal_tlll) Tensor
_self Int
_offset Int
_dim1 Int
_dim2
linalg_diagonal
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
linalg_diagonal :: Tensor -> Int -> Int -> Int -> Tensor
linalg_diagonal Tensor
_A Int
_offset Int
_dim1 Int
_dim2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.linalg_diagonal_tlll) Tensor
_A Int
_offset Int
_dim1 Int
_dim2
diagonal_tnnnl
:: Tensor
-> Dimname
-> Dimname
-> Dimname
-> Int
-> Tensor
diagonal_tnnnl :: Tensor -> Dimname -> Dimname -> Dimname -> Int -> Tensor
diagonal_tnnnl Tensor
_self Dimname
_outdim Dimname
_dim1 Dimname
_dim2 Int
_offset = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Dimname -> Dimname -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> Int64
-> IO (ForeignPtr Tensor)
ATen.diagonal_tnnnl) Tensor
_self Dimname
_outdim Dimname
_dim1 Dimname
_dim2 Int
_offset
diff
:: Tensor
-> Int
-> Int
-> Tensor
-> Tensor
-> Tensor
diff :: Tensor -> Int -> Int -> Tensor -> Tensor -> Tensor
diff Tensor
_self Int
_n Int
_dim Tensor
_prepend Tensor
_append = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.diff_tlltt) Tensor
_self Int
_n Int
_dim Tensor
_prepend Tensor
_append
gradient_tsll
:: Tensor
-> Float
-> Int
-> Int
-> [Tensor]
gradient_tsll :: Tensor -> Float -> Int -> Int -> [Tensor]
gradient_tsll Tensor
_self Float
_spacing Int
_dim Int
_edge_order = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> Int64
-> Int64
-> IO (ForeignPtr TensorList))
-> Tensor -> Float -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Scalar
-> Int64
-> Int64
-> IO (ForeignPtr TensorList)
ATen.gradient_tsll) Tensor
_self Float
_spacing Int
_dim Int
_edge_order
gradient_tll
:: Tensor
-> [Int]
-> Int
-> [Tensor]
gradient_tll :: Tensor -> [Int] -> Int -> [Tensor]
gradient_tll Tensor
_self [Int]
_dim Int
_edge_order = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> [Int] -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList)
ATen.gradient_tll) Tensor
_self [Int]
_dim Int
_edge_order
div
:: Tensor
-> Tensor
-> Tensor
div :: Tensor -> Tensor -> Tensor
div Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.div_tt) Tensor
_self Tensor
_other
div_tts
:: Tensor
-> Tensor
-> String
-> Tensor
div_tts :: Tensor -> Tensor -> String -> Tensor
div_tts Tensor
_self Tensor
_other String
_rounding_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.div_tts) Tensor
_self Tensor
_other String
_rounding_mode
divScalar
:: Tensor
-> Float
-> Tensor
divScalar :: Tensor -> Float -> Tensor
divScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.div_ts) Tensor
_self Float
_other
div_tss
:: Tensor
-> Float
-> String
-> Tensor
div_tss :: Tensor -> Float -> String -> Tensor
div_tss Tensor
_self Float
_other String
_rounding_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.div_tss) Tensor
_self Float
_other String
_rounding_mode
divide_tt
:: Tensor
-> Tensor
-> Tensor
divide_tt :: Tensor -> Tensor -> Tensor
divide_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.divide_tt) Tensor
_self Tensor
_other
divide_ts
:: Tensor
-> Float
-> Tensor
divide_ts :: Tensor -> Float -> Tensor
divide_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.divide_ts) Tensor
_self Float
_other
divide_tts
:: Tensor
-> Tensor
-> String
-> Tensor
divide_tts :: Tensor -> Tensor -> String -> Tensor
divide_tts Tensor
_self Tensor
_other String
_rounding_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.divide_tts) Tensor
_self Tensor
_other String
_rounding_mode
divide_tss
:: Tensor
-> Float
-> String
-> Tensor
divide_tss :: Tensor -> Float -> String -> Tensor
divide_tss Tensor
_self Float
_other String
_rounding_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.divide_tss) Tensor
_self Float
_other String
_rounding_mode
true_divide_tt
:: Tensor
-> Tensor
-> Tensor
true_divide_tt :: Tensor -> Tensor -> Tensor
true_divide_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.true_divide_tt) Tensor
_self Tensor
_other
true_divide_ts
:: Tensor
-> Float
-> Tensor
true_divide_ts :: Tensor -> Float -> Tensor
true_divide_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.true_divide_ts) Tensor
_self Float
_other
dot
:: Tensor
-> Tensor
-> Tensor
dot :: Tensor -> Tensor -> Tensor
dot Tensor
_self Tensor
_tensor = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.dot_tt) Tensor
_self Tensor
_tensor
vdot
:: Tensor
-> Tensor
-> Tensor
vdot :: Tensor -> Tensor -> Tensor
vdot Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.vdot_tt) Tensor
_self Tensor
_other
einsum
:: String
-> [Tensor]
-> [Int]
-> Tensor
einsum :: String -> [Tensor] -> [Int] -> Tensor
einsum String
_equation [Tensor]
_tensors [Int]
_path = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr StdString
-> ForeignPtr TensorList
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> String -> [Tensor] -> [Int] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr StdString
-> ForeignPtr TensorList
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.einsum_sll) String
_equation [Tensor]
_tensors [Int]
_path
embedding
:: Tensor
-> Tensor
-> Int
-> Bool
-> Bool
-> Tensor
embedding :: Tensor -> Tensor -> Int -> Bool -> Bool -> Tensor
embedding Tensor
_weight Tensor
_indices Int
_padding_idx Bool
_scale_grad_by_freq Bool
_sparse = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.embedding_ttlbb) Tensor
_weight Tensor
_indices Int
_padding_idx Bool
_scale_grad_by_freq Bool
_sparse
row_stack
:: [Tensor]
-> Tensor
row_stack :: [Tensor] -> Tensor
row_stack [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.row_stack_l) [Tensor]
_tensors
embedding_bag_tttblbtb
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Int
-> Bool
-> Tensor
-> Bool
-> (Tensor,Tensor,Tensor,Tensor)
embedding_bag_tttblbtb :: Tensor
-> Tensor
-> Tensor
-> Bool
-> Int
-> Bool
-> Tensor
-> Bool
-> (Tensor, Tensor, Tensor, Tensor)
embedding_bag_tttblbtb Tensor
_weight Tensor
_indices Tensor
_offsets Bool
_scale_grad_by_freq Int
_mode Bool
_sparse Tensor
_per_sample_weights Bool
_include_last_offset = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> Int64
-> CBool
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Int
-> Bool
-> Tensor
-> Bool
-> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> Int64
-> CBool
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.embedding_bag_tttblbtb) Tensor
_weight Tensor
_indices Tensor
_offsets Bool
_scale_grad_by_freq Int
_mode Bool
_sparse Tensor
_per_sample_weights Bool
_include_last_offset
embedding_bag_tttblbtbl
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Int
-> Bool
-> Tensor
-> Bool
-> Int
-> (Tensor,Tensor,Tensor,Tensor)
embedding_bag_tttblbtbl :: Tensor
-> Tensor
-> Tensor
-> Bool
-> Int
-> Bool
-> Tensor
-> Bool
-> Int
-> (Tensor, Tensor, Tensor, Tensor)
embedding_bag_tttblbtbl Tensor
_weight Tensor
_indices Tensor
_offsets Bool
_scale_grad_by_freq Int
_mode Bool
_sparse Tensor
_per_sample_weights Bool
_include_last_offset Int
_padding_idx = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> Int64
-> CBool
-> ForeignPtr Tensor
-> CBool
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Int
-> Bool
-> Tensor
-> Bool
-> Int
-> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> Int64
-> CBool
-> ForeignPtr Tensor
-> CBool
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.embedding_bag_tttblbtbl) Tensor
_weight Tensor
_indices Tensor
_offsets Bool
_scale_grad_by_freq Int
_mode Bool
_sparse Tensor
_per_sample_weights Bool
_include_last_offset Int
_padding_idx
erf
:: Tensor
-> Tensor
erf :: Tensor -> Tensor
erf Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.erf_t) Tensor
_self
erfc
:: Tensor
-> Tensor
erfc :: Tensor -> Tensor
erfc Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.erfc_t) Tensor
_self
exp
:: Tensor
-> Tensor
exp :: Tensor -> Tensor
exp Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.exp_t) Tensor
_self
exp2
:: Tensor
-> Tensor
exp2 :: Tensor -> Tensor
exp2 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.exp2_t) Tensor
_self
expm1
:: Tensor
-> Tensor
expm1 :: Tensor -> Tensor
expm1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.expm1_t) Tensor
_self
flatten
:: Tensor
-> Int
-> Int
-> Tensor
flatten :: Tensor -> Int -> Int -> Tensor
flatten Tensor
_self Int
_start_dim Int
_end_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.flatten_tll) Tensor
_self Int
_start_dim Int
_end_dim
flattenTo
:: Tensor
-> Int
-> Int
-> Dimname
-> Tensor
flattenTo :: Tensor -> Int -> Int -> Dimname -> Tensor
flattenTo Tensor
_self Int
_start_dim Int
_end_dim Dimname
_out_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr Dimname -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Dimname -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
ATen.flatten_tlln) Tensor
_self Int
_start_dim Int
_end_dim Dimname
_out_dim
flattenToWithDimname
:: Tensor
-> Dimname
-> Dimname
-> Dimname
-> Tensor
flattenToWithDimname :: Tensor -> Dimname -> Dimname -> Dimname -> Tensor
flattenToWithDimname Tensor
_self Dimname
_start_dim Dimname
_end_dim Dimname
_out_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Dimname -> Dimname -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
ATen.flatten_tnnn) Tensor
_self Dimname
_start_dim Dimname
_end_dim Dimname
_out_dim
flattenToWithDimnames
:: Tensor
-> [Dimname]
-> Dimname
-> Tensor
flattenToWithDimnames :: Tensor -> [Dimname] -> Dimname -> Tensor
flattenToWithDimnames Tensor
_self [Dimname]
_dims Dimname
_out_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Dimname -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
ATen.flatten_tNn) Tensor
_self [Dimname]
_dims Dimname
_out_dim
unflatten_tll
:: Tensor
-> Int
-> [Int]
-> Tensor
unflatten_tll :: Tensor -> Int -> [Int] -> Tensor
unflatten_tll Tensor
_self Int
_dim [Int]
_sizes = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> [Int] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.unflatten_tll) Tensor
_self Int
_dim [Int]
_sizes
unflatten_tnlN
:: Tensor
-> Dimname
-> [Int]
-> [Dimname]
-> Tensor
unflatten_tnlN :: Tensor -> Dimname -> [Int] -> [Dimname] -> Tensor
unflatten_tnlN Tensor
_self Dimname
_dim [Int]
_sizes [Dimname]
_names = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr IntArray
-> ForeignPtr DimnameList
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> [Int] -> [Dimname] -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr IntArray
-> ForeignPtr DimnameList
-> IO (ForeignPtr Tensor)
ATen.unflatten_tnlN) Tensor
_self Dimname
_dim [Int]
_sizes [Dimname]
_names
fill_ts
:: Tensor
-> Float
-> Tensor
fill_ts :: Tensor -> Float -> Tensor
fill_ts Tensor
_self Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.fill_ts) Tensor
_self Float
_value
fill_tt
:: Tensor
-> Tensor
-> Tensor
fill_tt :: Tensor -> Tensor -> Tensor
fill_tt Tensor
_self Tensor
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fill_tt) Tensor
_self Tensor
_value
floor
:: Tensor
-> Tensor
floor :: Tensor -> Tensor
floor Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.floor_t) Tensor
_self
floor_divide_tt
:: Tensor
-> Tensor
-> Tensor
floor_divide_tt :: Tensor -> Tensor -> Tensor
floor_divide_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.floor_divide_tt) Tensor
_self Tensor
_other
floor_divide_ts
:: Tensor
-> Float
-> Tensor
floor_divide_ts :: Tensor -> Float -> Tensor
floor_divide_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.floor_divide_ts) Tensor
_self Float
_other
frac
:: Tensor
-> Tensor
frac :: Tensor -> Tensor
frac Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.frac_t) Tensor
_self
gcd
:: Tensor
-> Tensor
-> Tensor
gcd :: Tensor -> Tensor -> Tensor
gcd Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.gcd_tt) Tensor
_self Tensor
_other
lcm
:: Tensor
-> Tensor
-> Tensor
lcm :: Tensor -> Tensor -> Tensor
lcm Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lcm_tt) Tensor
_self Tensor
_other
grid_sampler
:: Tensor
-> Tensor
-> Int
-> Int
-> Bool
-> Tensor
grid_sampler :: Tensor -> Tensor -> Int -> Int -> Bool -> Tensor
grid_sampler Tensor
_input Tensor
_grid Int
_interpolation_mode Int
_padding_mode Bool
_align_corners = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.grid_sampler_ttllb) Tensor
_input Tensor
_grid Int
_interpolation_mode Int
_padding_mode Bool
_align_corners
grid_sampler_2d
:: Tensor
-> Tensor
-> Int
-> Int
-> Bool
-> Tensor
grid_sampler_2d :: Tensor -> Tensor -> Int -> Int -> Bool -> Tensor
grid_sampler_2d Tensor
_input Tensor
_grid Int
_interpolation_mode Int
_padding_mode Bool
_align_corners = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.grid_sampler_2d_ttllb) Tensor
_input Tensor
_grid Int
_interpolation_mode Int
_padding_mode Bool
_align_corners
grid_sampler_3d
:: Tensor
-> Tensor
-> Int
-> Int
-> Bool
-> Tensor
grid_sampler_3d :: Tensor -> Tensor -> Int -> Int -> Bool -> Tensor
grid_sampler_3d Tensor
_input Tensor
_grid Int
_interpolation_mode Int
_padding_mode Bool
_align_corners = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.grid_sampler_3d_ttllb) Tensor
_input Tensor
_grid Int
_interpolation_mode Int
_padding_mode Bool
_align_corners
hinge_embedding_loss
:: Tensor
-> Tensor
-> Double
-> Int
-> Tensor
hinge_embedding_loss :: Tensor -> Tensor -> Double -> Int -> Tensor
hinge_embedding_loss Tensor
_self Tensor
_target Double
_margin Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Double -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor)
ATen.hinge_embedding_loss_ttdl) Tensor
_self Tensor
_target Double
_margin Int
_reduction
group_norm
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Double
-> Bool
-> Tensor
group_norm :: Tensor -> Int -> Tensor -> Tensor -> Double -> Bool -> Tensor
group_norm Tensor
_input Int
_num_groups Tensor
_weight Tensor
_bias Double
_eps Bool
_cudnn_enabled = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.group_norm_tlttdb) Tensor
_input Int
_num_groups Tensor
_weight Tensor
_bias Double
_eps Bool
_cudnn_enabled
native_group_norm
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Double
-> (Tensor,Tensor,Tensor)
native_group_norm :: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Double
-> (Tensor, Tensor, Tensor)
native_group_norm Tensor
_input Tensor
_weight Tensor
_bias Int
_N Int
_C Int
_HxW Int
_group Double
_eps = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Double
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.native_group_norm_tttlllld) Tensor
_input Tensor
_weight Tensor
_bias Int
_N Int
_C Int
_HxW Int
_group Double
_eps
index
:: Tensor
-> [Tensor]
-> Tensor
index :: Tensor -> [Tensor] -> Tensor
index Tensor
_self [Tensor]
_indices = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr (C10List (C10Optional Tensor))
-> IO (ForeignPtr Tensor))
-> Tensor -> [Tensor] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr (C10List (C10Optional Tensor))
-> IO (ForeignPtr Tensor)
ATen.index_tl) Tensor
_self [Tensor]
_indices
indexCopy
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Tensor
indexCopy :: Tensor -> Int -> Tensor -> Tensor -> Tensor
indexCopy Tensor
_self Int
_dim Tensor
_index Tensor
_source = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.index_copy_tltt) Tensor
_self Int
_dim Tensor
_index Tensor
_source
indexCopyWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Tensor
-> Tensor
indexCopyWithDimname :: Tensor -> Dimname -> Tensor -> Tensor -> Tensor
indexCopyWithDimname Tensor
_self Dimname
_dim Tensor
_index Tensor
_source = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.index_copy_tntt) Tensor
_self Dimname
_dim Tensor
_index Tensor
_source
index_put
:: Tensor
-> [Tensor]
-> Tensor
-> Bool
-> Tensor
index_put :: Tensor -> [Tensor] -> Tensor -> Bool -> Tensor
index_put Tensor
_self [Tensor]
_indices Tensor
_values Bool
_accumulate = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr (C10List (C10Optional Tensor))
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> [Tensor] -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr (C10List (C10Optional Tensor))
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
ATen.index_put_tltb) Tensor
_self [Tensor]
_indices Tensor
_values Bool
_accumulate
instance_norm
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> Bool
-> Tensor
instance_norm :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> Bool
-> Tensor
instance_norm Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_use_input_stats Double
_momentum Double
_eps Bool
_cudnn_enabled = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.instance_norm_tttttbddb) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_use_input_stats Double
_momentum Double
_eps Bool
_cudnn_enabled
isclose
:: Tensor
-> Tensor
-> Double
-> Double
-> Bool
-> Tensor
isclose :: Tensor -> Tensor -> Double -> Double -> Bool -> Tensor
isclose Tensor
_self Tensor
_other Double
_rtol Double
_atol Bool
_equal_nan = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Double -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.isclose_ttddb) Tensor
_self Tensor
_other Double
_rtol Double
_atol Bool
_equal_nan
isin_ttbb
:: Tensor
-> Tensor
-> Bool
-> Bool
-> Tensor
isin_ttbb :: Tensor -> Tensor -> Bool -> Bool -> Tensor
isin_ttbb Tensor
_elements Tensor
_test_elements Bool
_assume_unique Bool
_invert = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.isin_ttbb) Tensor
_elements Tensor
_test_elements Bool
_assume_unique Bool
_invert
isin_tsbb
:: Tensor
-> Float
-> Bool
-> Bool
-> Tensor
isin_tsbb :: Tensor -> Float -> Bool -> Bool -> Tensor
isin_tsbb Tensor
_elements Float
_test_element Bool
_assume_unique Bool
_invert = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Scalar -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.isin_tsbb) Tensor
_elements Float
_test_element Bool
_assume_unique Bool
_invert
isin_stbb
:: Float
-> Tensor
-> Bool
-> Bool
-> Tensor
isin_stbb :: Float -> Tensor -> Bool -> Bool -> Tensor
isin_stbb Float
_element Tensor
_test_elements Bool
_assume_unique Bool
_invert = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Scalar
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.isin_stbb) Float
_element Tensor
_test_elements Bool
_assume_unique Bool
_invert
isnan
:: Tensor
-> Tensor
isnan :: Tensor -> Tensor
isnan Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.isnan_t) Tensor
_self
is_distributed
:: Tensor
-> Bool
is_distributed :: Tensor -> Bool
is_distributed Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_distributed_t) Tensor
_self
is_floating_point
:: Tensor
-> Bool
is_floating_point :: Tensor -> Bool
is_floating_point Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_floating_point_t) Tensor
_self
is_complex
:: Tensor
-> Bool
is_complex :: Tensor -> Bool
is_complex Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_complex_t) Tensor
_self
is_conj
:: Tensor
-> Bool
is_conj :: Tensor -> Bool
is_conj Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_conj_t) Tensor
_self
is_neg
:: Tensor
-> Bool
is_neg :: Tensor -> Bool
is_neg Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_neg_t) Tensor
_self
isreal
:: Tensor
-> Tensor
isreal :: Tensor -> Tensor
isreal Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.isreal_t) Tensor
_self
is_nonzero
:: Tensor
-> Bool
is_nonzero :: Tensor -> Bool
is_nonzero Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_nonzero_t) Tensor
_self
is_same_size
:: Tensor
-> Tensor
-> Bool
is_same_size :: Tensor -> Tensor -> Bool
is_same_size Tensor
_self Tensor
_other = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool)
-> Tensor -> Tensor -> IO Bool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool
ATen.is_same_size_tt) Tensor
_self Tensor
_other
is_signed
:: Tensor
-> Bool
is_signed :: Tensor -> Bool
is_signed Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_signed_t) Tensor
_self
is_inference
:: Tensor
-> Bool
is_inference :: Tensor -> Bool
is_inference Tensor
_self = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CBool) -> Tensor -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CBool
ATen.is_inference_t) Tensor
_self
kl_div
:: Tensor
-> Tensor
-> Int
-> Bool
-> Tensor
kl_div :: Tensor -> Tensor -> Int -> Bool -> Tensor
kl_div Tensor
_self Tensor
_target Int
_reduction Bool
_log_target = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.kl_div_ttlb) Tensor
_self Tensor
_target Int
_reduction Bool
_log_target
kron
:: Tensor
-> Tensor
-> Tensor
kron :: Tensor -> Tensor -> Tensor
kron Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.kron_tt) Tensor
_self Tensor
_other
kthvalue
:: Tensor
-> Int
-> Int
-> Bool
-> (Tensor,Tensor)
kthvalue :: Tensor -> Int -> Int -> Bool -> (Tensor, Tensor)
kthvalue Tensor
_self Int
_k Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.kthvalue_tllb) Tensor
_self Int
_k Int
_dim Bool
_keepdim
kthvalueWithDimname
:: Tensor
-> Int
-> Dimname
-> Bool
-> (Tensor,Tensor)
kthvalueWithDimname :: Tensor -> Int -> Dimname -> Bool -> (Tensor, Tensor)
kthvalueWithDimname Tensor
_self Int
_k Dimname
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.kthvalue_tlnb) Tensor
_self Int
_k Dimname
_dim Bool
_keepdim
layer_norm
:: Tensor
-> [Int]
-> Tensor
-> Tensor
-> Double
-> Bool
-> Tensor
layer_norm :: Tensor -> [Int] -> Tensor -> Tensor -> Double -> Bool -> Tensor
layer_norm Tensor
_input [Int]
_normalized_shape Tensor
_weight Tensor
_bias Double
_eps Bool
_cudnn_enable = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> [Int]
-> Tensor
-> Tensor
-> Double
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.layer_norm_tlttdb) Tensor
_input [Int]
_normalized_shape Tensor
_weight Tensor
_bias Double
_eps Bool
_cudnn_enable
native_layer_norm
:: Tensor
-> [Int]
-> Tensor
-> Tensor
-> Double
-> (Tensor,Tensor,Tensor)
native_layer_norm :: Tensor
-> [Int] -> Tensor -> Tensor -> Double -> (Tensor, Tensor, Tensor)
native_layer_norm Tensor
_input [Int]
_normalized_shape Tensor
_weight Tensor
_bias Double
_eps = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> [Int]
-> Tensor
-> Tensor
-> Double
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.native_layer_norm_tlttd) Tensor
_input [Int]
_normalized_shape Tensor
_weight Tensor
_bias Double
_eps
nan_to_num
:: Tensor
-> Double
-> Double
-> Double
-> Tensor
nan_to_num :: Tensor -> Double -> Double -> Double -> Tensor
nan_to_num Tensor
_self Double
_nan Double
_posinf Double
_neginf = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> CDouble -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Double -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CDouble -> CDouble -> CDouble -> IO (ForeignPtr Tensor)
ATen.nan_to_num_tddd) Tensor
_self Double
_nan Double
_posinf Double
_neginf
linear
:: Tensor
-> Tensor
-> Tensor
-> Tensor
linear :: Tensor -> Tensor -> Tensor -> Tensor
linear Tensor
_input Tensor
_weight Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linear_ttt) Tensor
_input Tensor
_weight Tensor
_bias
mkldnn_linear
:: Tensor
-> Tensor
-> Tensor
-> Tensor
mkldnn_linear :: Tensor -> Tensor -> Tensor -> Tensor
mkldnn_linear Tensor
_self Tensor
_weight Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.mkldnn_linear_ttt) Tensor
_self Tensor
_weight Tensor
_bias
mkldnn_linear_backward_input
:: [Int]
-> Tensor
-> Tensor
-> Tensor
mkldnn_linear_backward_input :: [Int] -> Tensor -> Tensor -> Tensor
mkldnn_linear_backward_input [Int]
_input_size Tensor
_grad_output Tensor
_weight = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> [Int] -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr IntArray
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.mkldnn_linear_backward_input_ltt) [Int]
_input_size Tensor
_grad_output Tensor
_weight
mkldnn_linear_backward_weights
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> (Tensor,Tensor)
mkldnn_linear_backward_weights :: Tensor -> Tensor -> Tensor -> Bool -> (Tensor, Tensor)
mkldnn_linear_backward_weights Tensor
_grad_output Tensor
_input Tensor
_weight Bool
_bias_defined = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.mkldnn_linear_backward_weights_tttb) Tensor
_grad_output Tensor
_input Tensor
_weight Bool
_bias_defined
fbgemm_linear_int8_weight_fp32_activation
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
-> Tensor
fbgemm_linear_int8_weight_fp32_activation :: Tensor
-> Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor -> Tensor
fbgemm_linear_int8_weight_fp32_activation Tensor
_input Tensor
_weight Tensor
_packed Tensor
_col_offsets Float
_weight_scale Float
_weight_zero_point Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.fbgemm_linear_int8_weight_fp32_activation_ttttsst) Tensor
_input Tensor
_weight Tensor
_packed Tensor
_col_offsets Float
_weight_scale Float
_weight_zero_point Tensor
_bias
fbgemm_linear_int8_weight
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
-> Tensor
fbgemm_linear_int8_weight :: Tensor
-> Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor -> Tensor
fbgemm_linear_int8_weight Tensor
_input Tensor
_weight Tensor
_packed Tensor
_col_offsets Float
_weight_scale Float
_weight_zero_point Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.fbgemm_linear_int8_weight_ttttsst) Tensor
_input Tensor
_weight Tensor
_packed Tensor
_col_offsets Float
_weight_scale Float
_weight_zero_point Tensor
_bias
fbgemm_linear_quantize_weight
:: Tensor
-> (Tensor,Tensor,Double,Int)
fbgemm_linear_quantize_weight :: Tensor -> (Tensor, Tensor, Double, Int)
fbgemm_linear_quantize_weight Tensor
_input = IO (Tensor, Tensor, Double, Int) -> (Tensor, Tensor, Double, Int)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Double, Int) -> (Tensor, Tensor, Double, Int))
-> IO (Tensor, Tensor, Double, Int)
-> (Tensor, Tensor, Double, Int)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))))
-> Tensor -> IO (Tensor, Tensor, Double, Int)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64)))
ATen.fbgemm_linear_quantize_weight_t) Tensor
_input
fbgemm_pack_gemm_matrix_fp16
:: Tensor
-> Tensor
fbgemm_pack_gemm_matrix_fp16 :: Tensor -> Tensor
fbgemm_pack_gemm_matrix_fp16 Tensor
_input = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fbgemm_pack_gemm_matrix_fp16_t) Tensor
_input
fbgemm_linear_fp16_weight_fp32_activation
:: Tensor
-> Tensor
-> Tensor
-> Tensor
fbgemm_linear_fp16_weight_fp32_activation :: Tensor -> Tensor -> Tensor -> Tensor
fbgemm_linear_fp16_weight_fp32_activation Tensor
_input Tensor
_packed_weight Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fbgemm_linear_fp16_weight_fp32_activation_ttt) Tensor
_input Tensor
_packed_weight Tensor
_bias
fbgemm_linear_fp16_weight
:: Tensor
-> Tensor
-> Tensor
-> Tensor
fbgemm_linear_fp16_weight :: Tensor -> Tensor -> Tensor -> Tensor
fbgemm_linear_fp16_weight Tensor
_input Tensor
_packed_weight Tensor
_bias = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fbgemm_linear_fp16_weight_ttt) Tensor
_input Tensor
_packed_weight Tensor
_bias
quantizeFbgemm'
:: Tensor
-> Tensor
quantizeFbgemm' :: Tensor -> Tensor
quantizeFbgemm' Tensor
_input = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fbgemm_pack_quantized_matrix_t) Tensor
_input
quantizeFbgemm
:: Tensor
-> Int
-> Int
-> Tensor
quantizeFbgemm :: Tensor -> Int -> Int -> Tensor
quantizeFbgemm Tensor
_input Int
_K Int
_N = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.fbgemm_pack_quantized_matrix_tll) Tensor
_input Int
_K Int
_N
ldexp
:: Tensor
-> Tensor
-> Tensor
ldexp :: Tensor -> Tensor -> Tensor
ldexp Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ldexp_tt) Tensor
_self Tensor
_other
log
:: Tensor
-> Tensor
log :: Tensor -> Tensor
log Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.log_t) Tensor
_self
log10
:: Tensor
-> Tensor
log10 :: Tensor -> Tensor
log10 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.log10_t) Tensor
_self
log1p
:: Tensor
-> Tensor
log1p :: Tensor -> Tensor
log1p Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.log1p_t) Tensor
_self
log2
:: Tensor
-> Tensor
log2 :: Tensor -> Tensor
log2 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.log2_t) Tensor
_self
logaddexp
:: Tensor
-> Tensor
-> Tensor
logaddexp :: Tensor -> Tensor -> Tensor
logaddexp Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logaddexp_tt) Tensor
_self Tensor
_other
logaddexp2
:: Tensor
-> Tensor
-> Tensor
logaddexp2 :: Tensor -> Tensor -> Tensor
logaddexp2 Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logaddexp2_tt) Tensor
_self Tensor
_other
xlogy_tt
:: Tensor
-> Tensor
-> Tensor
xlogy_tt :: Tensor -> Tensor -> Tensor
xlogy_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.xlogy_tt) Tensor
_self Tensor
_other
xlogy_st
:: Float
-> Tensor
-> Tensor
xlogy_st :: Float -> Tensor -> Tensor
xlogy_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.xlogy_st) Float
_self Tensor
_other
xlogy_ts
:: Tensor
-> Float
-> Tensor
xlogy_ts :: Tensor -> Float -> Tensor
xlogy_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.xlogy_ts) Tensor
_self Float
_other
logSoftmax
:: Tensor
-> Int
-> DType
-> Tensor
logSoftmax :: Tensor -> Int -> DType -> Tensor
logSoftmax Tensor
_self Int
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.log_softmax_tls) Tensor
_self Int
_dim DType
_dtype
logSoftmaxWithDimname
:: Tensor
-> Dimname
-> DType
-> Tensor
logSoftmaxWithDimname :: Tensor -> Dimname -> DType -> Tensor
logSoftmaxWithDimname Tensor
_self Dimname
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.log_softmax_tns) Tensor
_self Dimname
_dim DType
_dtype
logcumsumexp_tl
:: Tensor
-> Int
-> Tensor
logcumsumexp_tl :: Tensor -> Int -> Tensor
logcumsumexp_tl Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.logcumsumexp_tl) Tensor
_self Int
_dim
logcumsumexp_tn
:: Tensor
-> Dimname
-> Tensor
logcumsumexp_tn :: Tensor -> Dimname -> Tensor
logcumsumexp_tn Tensor
_self Dimname
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Dimname -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
ATen.logcumsumexp_tn) Tensor
_self Dimname
_dim
logsumexp
:: Tensor
-> Int
-> Bool
-> Tensor
logsumexp :: Tensor -> Int -> Bool -> Tensor
logsumexp Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.logsumexp_tlb) Tensor
_self Int
_dim Bool
_keepdim
logsumexpWithDimnameList
:: Tensor
-> [Dimname]
-> Bool
-> Tensor
logsumexpWithDimnameList :: Tensor -> [Dimname] -> Bool -> Tensor
logsumexpWithDimnameList Tensor
_self [Dimname]
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr DimnameList -> CBool -> IO (ForeignPtr Tensor)
ATen.logsumexp_tNb) Tensor
_self [Dimname]
_dim Bool
_keepdim
margin_ranking_loss
:: Tensor
-> Tensor
-> Tensor
-> Double
-> Int
-> Tensor
margin_ranking_loss :: Tensor -> Tensor -> Tensor -> Double -> Int -> Tensor
margin_ranking_loss Tensor
_input1 Tensor
_input2 Tensor
_target Double
_margin Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Double -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
ATen.margin_ranking_loss_tttdl) Tensor
_input1 Tensor
_input2 Tensor
_target Double
_margin Int
_reduction
matmul
:: Tensor
-> Tensor
-> Tensor
matmul :: Tensor -> Tensor -> Tensor
matmul Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.matmul_tt) Tensor
_self Tensor
_other
matrix_power
:: Tensor
-> Int
-> Tensor
matrix_power :: Tensor -> Int -> Tensor
matrix_power Tensor
_self Int
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.matrix_power_tl) Tensor
_self Int
_n
matrix_exp
:: Tensor
-> Tensor
matrix_exp :: Tensor -> Tensor
matrix_exp Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.matrix_exp_t) Tensor
_self
aminmax
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
aminmax :: Tensor -> Int -> Bool -> (Tensor, Tensor)
aminmax Tensor
_self Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.aminmax_tlb) Tensor
_self Int
_dim Bool
_keepdim
maxDim
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
maxDim :: Tensor -> Int -> Bool -> (Tensor, Tensor)
maxDim Tensor
_self Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.max_tlb) Tensor
_self Int
_dim Bool
_keepdim
maxWithDimname
:: Tensor
-> Dimname
-> Bool
-> (Tensor,Tensor)
maxWithDimname :: Tensor -> Dimname -> Bool -> (Tensor, Tensor)
maxWithDimname Tensor
_self Dimname
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.max_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
amax
:: Tensor
-> Int
-> Bool
-> Tensor
amax :: Tensor -> Int -> Bool -> Tensor
amax Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.amax_tlb) Tensor
_self Int
_dim Bool
_keepdim
max_pool1d_with_indices
:: Tensor
-> Int
-> Int
-> Int
-> Int
-> Bool
-> (Tensor,Tensor)
max_pool1d_with_indices :: Tensor -> Int -> Int -> Int -> Int -> Bool -> (Tensor, Tensor)
max_pool1d_with_indices Tensor
_self Int
_kernel_size Int
_stride Int
_padding Int
_dilation Bool
_ceil_mode = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.max_pool1d_with_indices_tllllb) Tensor
_self Int
_kernel_size Int
_stride Int
_padding Int
_dilation Bool
_ceil_mode
max_pool1d
:: Tensor
-> Int
-> Int
-> Int
-> Int
-> Bool
-> Tensor
max_pool1d :: Tensor -> Int -> Int -> Int -> Int -> Bool -> Tensor
max_pool1d Tensor
_self Int
_kernel_size Int
_stride Int
_padding Int
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.max_pool1d_tllllb) Tensor
_self Int
_kernel_size Int
_stride Int
_padding Int
_dilation Bool
_ceil_mode
max_pool2d
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Bool
-> Tensor
max_pool2d :: Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> Tensor
max_pool2d Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.max_pool2d_tllllb) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode
mkldnn_max_pool2d
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Bool
-> Tensor
mkldnn_max_pool2d :: Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> Tensor
mkldnn_max_pool2d Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.mkldnn_max_pool2d_tllllb) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode
mkldnn_max_pool3d
:: Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Bool
-> Tensor
mkldnn_max_pool3d :: Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> Tensor
mkldnn_max_pool3d Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.mkldnn_max_pool3d_tllllb) Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Bool
_ceil_mode
quantized_max_pool1d
:: Tensor
-> Int
-> Int
-> Int
-> Int
-> Bool
-> Tensor
quantized_max_pool1d :: Tensor -> Int -> Int -> Int -> Int -> Bool -> Tensor
quantized_max_pool1d Tensor
_self Int
_kernel_size Int
_stride Int
_padding Int
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.quantized_max_pool1d_tllllb) Tensor
_self Int
_kernel_size Int
_stride Int
_padding Int
_dilation Bool
_ceil_mode
quantized_max_pool2d
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Bool
-> Tensor
quantized_max_pool2d :: Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> Tensor
quantized_max_pool2d Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.quantized_max_pool2d_tllllb) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode
max_pool3d
:: Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Bool
-> Tensor
max_pool3d :: Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> Tensor
max_pool3d Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Bool
_ceil_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.max_pool3d_tllllb) Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Bool
_ceil_mode
meanAll
:: Tensor
-> DType
-> Tensor
meanAll :: Tensor -> DType -> Tensor
meanAll Tensor
_self DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> DType -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.mean_ts) Tensor
_self DType
_dtype
meanDim
:: Tensor
-> Int
-> Bool
-> DType
-> Tensor
meanDim :: Tensor -> Int -> Bool -> DType -> Tensor
meanDim Tensor
_self Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.mean_tlbs) Tensor
_self Int
_dim Bool
_keepdim DType
_dtype
meanWithDimnames
:: Tensor
-> [Dimname]
-> Bool
-> DType
-> Tensor
meanWithDimnames :: Tensor -> [Dimname] -> Bool -> DType -> Tensor
meanWithDimnames Tensor
_self [Dimname]
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.mean_tNbs) Tensor
_self [Dimname]
_dim Bool
_keepdim DType
_dtype
nanmean
:: Tensor
-> Int
-> Bool
-> DType
-> Tensor
nanmean :: Tensor -> Int -> Bool -> DType -> Tensor
nanmean Tensor
_self Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.nanmean_tlbs) Tensor
_self Int
_dim Bool
_keepdim DType
_dtype
medianAll
:: Tensor
-> Tensor
medianAll :: Tensor -> Tensor
medianAll Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.median_t) Tensor
_self
medianDim
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
medianDim :: Tensor -> Int -> Bool -> (Tensor, Tensor)
medianDim Tensor
_self Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.median_tlb) Tensor
_self Int
_dim Bool
_keepdim
medianWithDimname
:: Tensor
-> Dimname
-> Bool
-> (Tensor,Tensor)
medianWithDimname :: Tensor -> Dimname -> Bool -> (Tensor, Tensor)
medianWithDimname Tensor
_self Dimname
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.median_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
nanmedian_t
:: Tensor
-> Tensor
nanmedian_t :: Tensor -> Tensor
nanmedian_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.nanmedian_t) Tensor
_self
nanmedian_tlb
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
nanmedian_tlb :: Tensor -> Int -> Bool -> (Tensor, Tensor)
nanmedian_tlb Tensor
_self Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.nanmedian_tlb) Tensor
_self Int
_dim Bool
_keepdim
nanmedian_tnb
:: Tensor
-> Dimname
-> Bool
-> (Tensor,Tensor)
nanmedian_tnb :: Tensor -> Dimname -> Bool -> (Tensor, Tensor)
nanmedian_tnb Tensor
_self Dimname
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.nanmedian_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
minDim
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
minDim :: Tensor -> Int -> Bool -> (Tensor, Tensor)
minDim Tensor
_self Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.min_tlb) Tensor
_self Int
_dim Bool
_keepdim
minWithDimname
:: Tensor
-> Dimname
-> Bool
-> (Tensor,Tensor)
minWithDimname :: Tensor -> Dimname -> Bool -> (Tensor, Tensor)
minWithDimname Tensor
_self Dimname
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.min_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
amin
:: Tensor
-> Int
-> Bool
-> Tensor
amin :: Tensor -> Int -> Bool -> Tensor
amin Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.amin_tlb) Tensor
_self Int
_dim Bool
_keepdim
mkldnn_convolution
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
mkldnn_convolution :: Tensor
-> Tensor -> Tensor -> [Int] -> [Int] -> [Int] -> Int -> Tensor
mkldnn_convolution Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.mkldnn_convolution_tttllll) Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups
mkldnn_rnn_layer
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> [Int]
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor,Tensor)
mkldnn_rnn_layer :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> [Int]
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Bool
-> Bool
-> (Tensor, Tensor, Tensor, Tensor)
mkldnn_rnn_layer Tensor
_input Tensor
_weight0 Tensor
_weight1 Tensor
_weight2 Tensor
_weight3 Tensor
_hx_ Tensor
_cx_ Bool
_reverse [Int]
_batch_sizes Int
_mode Int
_hidden_size Int
_num_layers Bool
_has_biases Bool
_bidirectional Bool
_batch_first Bool
_train = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr IntArray
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> [Int]
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 x14 cx14 x15 cx15 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
Castable x14 cx14, Castable x15 cx15, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> cx13
-> cx14
-> cx15
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> x15
-> IO y
cast16 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr IntArray
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.mkldnn_rnn_layer_tttttttbllllbbbb) Tensor
_input Tensor
_weight0 Tensor
_weight1 Tensor
_weight2 Tensor
_weight3 Tensor
_hx_ Tensor
_cx_ Bool
_reverse [Int]
_batch_sizes Int
_mode Int
_hidden_size Int
_num_layers Bool
_has_biases Bool
_bidirectional Bool
_batch_first Bool
_train
miopen_batch_norm
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> (Tensor,Tensor,Tensor)
miopen_batch_norm :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> (Tensor, Tensor, Tensor)
miopen_batch_norm Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_exponential_average_factor Double
_epsilon = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.miopen_batch_norm_tttttbdd) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_exponential_average_factor Double
_epsilon
miopen_convolution
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Tensor
miopen_convolution :: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Tensor
miopen_convolution Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.miopen_convolution_tttllllbb) Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic
miopen_convolution_transpose
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Tensor
miopen_convolution_transpose :: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Tensor
miopen_convolution_transpose Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_output_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
cast10 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.miopen_convolution_transpose_tttlllllbb) Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_output_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic
miopen_depthwise_convolution
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Tensor
miopen_depthwise_convolution :: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> Tensor
miopen_depthwise_convolution Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.miopen_depthwise_convolution_tttllllbb) Tensor
_self Tensor
_weight Tensor
_bias [Int]
_padding [Int]
_stride [Int]
_dilation Int
_groups Bool
_benchmark Bool
_deterministic
miopen_convolution_relu
:: Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
miopen_convolution_relu :: Tensor
-> Tensor -> Tensor -> [Int] -> [Int] -> [Int] -> Int -> Tensor
miopen_convolution_relu Tensor
_self Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.miopen_convolution_relu_tttllll) Tensor
_self Tensor
_weight Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups
miopen_convolution_add_relu
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
miopen_convolution_add_relu :: Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> Tensor
miopen_convolution_add_relu Tensor
_self Tensor
_weight Tensor
_z Float
_alpha Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
-> [Int]
-> [Int]
-> [Int]
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.miopen_convolution_add_relu_tttstllll) Tensor
_self Tensor
_weight Tensor
_z Float
_alpha Tensor
_bias [Int]
_stride [Int]
_padding [Int]
_dilation Int
_groups
miopen_rnn
:: Tensor
-> [Tensor]
-> Int
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Bool
-> Double
-> Bool
-> Bool
-> [Int]
-> Tensor
-> (Tensor,Tensor,Tensor,Tensor,Tensor)
miopen_rnn :: Tensor
-> [Tensor]
-> Int
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Bool
-> Double
-> Bool
-> Bool
-> [Int]
-> Tensor
-> (Tensor, Tensor, Tensor, Tensor, Tensor)
miopen_rnn Tensor
_input [Tensor]
_weight Int
_weight_stride0 Tensor
_hx Tensor
_cx Int
_mode Int
_hidden_size Int
_num_layers Bool
_batch_first Double
_dropout Bool
_train Bool
_bidirectional [Int]
_batch_sizes Tensor
_dropout_state = IO (Tensor, Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr TensorList
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO
(ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> [Tensor]
-> Int
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Bool
-> Double
-> Bool
-> Bool
-> [Int]
-> Tensor
-> IO (Tensor, Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> cx13
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> IO y
cast14 ForeignPtr Tensor
-> ForeignPtr TensorList
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO
(ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
ATen.miopen_rnn_tllttlllbdbblt) Tensor
_input [Tensor]
_weight Int
_weight_stride0 Tensor
_hx Tensor
_cx Int
_mode Int
_hidden_size Int
_num_layers Bool
_batch_first Double
_dropout Bool
_train Bool
_bidirectional [Int]
_batch_sizes Tensor
_dropout_state
mm
:: Tensor
-> Tensor
-> Tensor
mm :: Tensor -> Tensor -> Tensor
mm Tensor
_self Tensor
_mat2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.mm_tt) Tensor
_self Tensor
_mat2
mode
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
mode :: Tensor -> Int -> Bool -> (Tensor, Tensor)
mode Tensor
_self Int
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.mode_tlb) Tensor
_self Int
_dim Bool
_keepdim
modeWithDimname
:: Tensor
-> Dimname
-> Bool
-> (Tensor,Tensor)
modeWithDimname :: Tensor -> Dimname -> Bool -> (Tensor, Tensor)
modeWithDimname Tensor
_self Dimname
_dim Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.mode_tnb) Tensor
_self Dimname
_dim Bool
_keepdim
mul
:: Tensor
-> Tensor
-> Tensor
mul :: Tensor -> Tensor -> Tensor
mul Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.mul_tt) Tensor
_self Tensor
_other
mulScalar
:: Tensor
-> Float
-> Tensor
mulScalar :: Tensor -> Float -> Tensor
mulScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.mul_ts) Tensor
_self Float
_other
multiply_tt
:: Tensor
-> Tensor
-> Tensor
multiply_tt :: Tensor -> Tensor -> Tensor
multiply_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.multiply_tt) Tensor
_self Tensor
_other
multiply_ts
:: Tensor
-> Float
-> Tensor
multiply_ts :: Tensor -> Float -> Tensor
multiply_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.multiply_ts) Tensor
_self Float
_other
mv
:: Tensor
-> Tensor
-> Tensor
mv :: Tensor -> Tensor -> Tensor
mv Tensor
_self Tensor
_vec = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.mv_tt) Tensor
_self Tensor
_vec
mvlgamma
:: Tensor
-> Int
-> Tensor
mvlgamma :: Tensor -> Int -> Tensor
mvlgamma Tensor
_self Int
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.mvlgamma_tl) Tensor
_self Int
_p
narrow_copy
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
narrow_copy :: Tensor -> Int -> Int -> Int -> Tensor
narrow_copy Tensor
_self Int
_dim Int
_start Int
_length = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.narrow_copy_tlll) Tensor
_self Int
_dim Int
_start Int
_length
narrow_tlll
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
narrow_tlll :: Tensor -> Int -> Int -> Int -> Tensor
narrow_tlll Tensor
_self Int
_dim Int
_start Int
_length = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.narrow_tlll) Tensor
_self Int
_dim Int
_start Int
_length
narrow_tltl
:: Tensor
-> Int
-> Tensor
-> Int
-> Tensor
narrow_tltl :: Tensor -> Int -> Tensor -> Int -> Tensor
narrow_tltl Tensor
_self Int
_dim Tensor
_start Int
_length = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.narrow_tltl) Tensor
_self Int
_dim Tensor
_start Int
_length
native_batch_norm
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> (Tensor,Tensor,Tensor)
native_batch_norm :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> (Tensor, Tensor, Tensor)
native_batch_norm Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_momentum Double
_eps = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Double
-> Double
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.native_batch_norm_tttttbdd) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_running_mean Tensor
_running_var Bool
_training Double
_momentum Double
_eps
batch_norm_stats
:: Tensor
-> Double
-> (Tensor,Tensor)
batch_norm_stats :: Tensor -> Double -> (Tensor, Tensor)
batch_norm_stats Tensor
_input Double
_eps = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Double -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CDouble -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.batch_norm_stats_td) Tensor
_input Double
_eps
batch_norm_elemt
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Tensor
batch_norm_elemt :: Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Double -> Tensor
batch_norm_elemt Tensor
_input Tensor
_weight Tensor
_bias Tensor
_mean Tensor
_invstd Double
_eps = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.batch_norm_elemt_tttttd) Tensor
_input Tensor
_weight Tensor
_bias Tensor
_mean Tensor
_invstd Double
_eps
batch_norm_gather_stats
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Int
-> (Tensor,Tensor)
batch_norm_gather_stats :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Int
-> (Tensor, Tensor)
batch_norm_gather_stats Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_running_mean Tensor
_running_var Double
_momentum Double
_eps Int
_count = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Int
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.batch_norm_gather_stats_tttttddl) Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_running_mean Tensor
_running_var Double
_momentum Double
_eps Int
_count
batch_norm_gather_stats_with_counts
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Tensor
-> (Tensor,Tensor)
batch_norm_gather_stats_with_counts :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Tensor
-> (Tensor, Tensor)
batch_norm_gather_stats_with_counts Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_running_mean Tensor
_running_var Double
_momentum Double
_eps Tensor
_counts = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Tensor
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.batch_norm_gather_stats_with_counts_tttttddt) Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_running_mean Tensor
_running_var Double
_momentum Double
_eps Tensor
_counts
batch_norm_backward_reduce
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor,Tensor)
batch_norm_backward_reduce :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Bool
-> Bool
-> (Tensor, Tensor, Tensor, Tensor)
batch_norm_backward_reduce Tensor
_grad_out Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_weight Bool
_input_g Bool
_weight_g Bool
_bias_g = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.batch_norm_backward_reduce_tttttbbb) Tensor
_grad_out Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_weight Bool
_input_g Bool
_weight_g Bool
_bias_g
batch_norm_backward_elemt
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
batch_norm_backward_elemt :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
batch_norm_backward_elemt Tensor
_grad_out Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_weight Tensor
_mean_dy Tensor
_mean_dy_xmu Tensor
_count = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.batch_norm_backward_elemt_tttttttt) Tensor
_grad_out Tensor
_input Tensor
_mean Tensor
_invstd Tensor
_weight Tensor
_mean_dy Tensor
_mean_dy_xmu Tensor
_count
batch_norm_update_stats
:: Tensor
-> Tensor
-> Tensor
-> Double
-> (Tensor,Tensor)
batch_norm_update_stats :: Tensor -> Tensor -> Tensor -> Double -> (Tensor, Tensor)
batch_norm_update_stats Tensor
_input Tensor
_running_mean Tensor
_running_var Double
_momentum = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Tensor -> Double -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.batch_norm_update_stats_tttd) Tensor
_input Tensor
_running_mean Tensor
_running_var Double
_momentum
is_vulkan_available
:: Bool
is_vulkan_available :: Bool
is_vulkan_available = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (IO CBool -> IO Bool
forall a ca. Castable a ca => IO ca -> IO a
cast0 IO CBool
ATen.is_vulkan_available)
pairwise_distance
:: Tensor
-> Tensor
-> Double
-> Double
-> Bool
-> Tensor
pairwise_distance :: Tensor -> Tensor -> Double -> Double -> Bool -> Tensor
pairwise_distance Tensor
_x1 Tensor
_x2 Double
_p Double
_eps Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Double -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.pairwise_distance_ttddb) Tensor
_x1 Tensor
_x2 Double
_p Double
_eps Bool
_keepdim
cdist
:: Tensor
-> Tensor
-> Double
-> Int
-> Tensor
cdist :: Tensor -> Tensor -> Double -> Int -> Tensor
cdist Tensor
_x1 Tensor
_x2 Double
_p Int
_compute_mode = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Double -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor)
ATen.cdist_ttdl) Tensor
_x1 Tensor
_x2 Double
_p Int
_compute_mode
pdist
:: Tensor
-> Double
-> Tensor
pdist :: Tensor -> Double -> Tensor
pdist Tensor
_self Double
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
ATen.pdist_td) Tensor
_self Double
_p
cosine_similarity
:: Tensor
-> Tensor
-> Int
-> Double
-> Tensor
cosine_similarity :: Tensor -> Tensor -> Int -> Double -> Tensor
cosine_similarity Tensor
_x1 Tensor
_x2 Int
_dim Double
_eps = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor)
ATen.cosine_similarity_ttld) Tensor
_x1 Tensor
_x2 Int
_dim Double
_eps
permute
:: Tensor
-> [Int]
-> Tensor
permute :: Tensor -> [Int] -> Tensor
permute Tensor
_self [Int]
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.permute_tl) Tensor
_self [Int]
_dims
movedim_tll
:: Tensor
-> Int
-> Int
-> Tensor
movedim_tll :: Tensor -> Int -> Int -> Tensor
movedim_tll Tensor
_self Int
_source Int
_destination = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.movedim_tll) Tensor
_self Int
_source Int
_destination
moveaxis_tll
:: Tensor
-> Int
-> Int
-> Tensor
moveaxis_tll :: Tensor -> Int -> Int -> Tensor
moveaxis_tll Tensor
_self Int
_source Int
_destination = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.moveaxis_tll) Tensor
_self Int
_source Int
_destination
adjoint
:: Tensor
-> Tensor
adjoint :: Tensor -> Tensor
adjoint Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.adjoint_t) Tensor
_self
pixel_shuffle
:: Tensor
-> Int
-> Tensor
pixel_shuffle :: Tensor -> Int -> Tensor
pixel_shuffle Tensor
_self Int
_upscale_factor = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.pixel_shuffle_tl) Tensor
_self Int
_upscale_factor
pixel_unshuffle
:: Tensor
-> Int
-> Tensor
pixel_unshuffle :: Tensor -> Int -> Tensor
pixel_unshuffle Tensor
_self Int
_downscale_factor = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.pixel_unshuffle_tl) Tensor
_self Int
_downscale_factor
channel_shuffle
:: Tensor
-> Int
-> Tensor
channel_shuffle :: Tensor -> Int -> Tensor
channel_shuffle Tensor
_self Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.channel_shuffle_tl) Tensor
_self Int
_groups
native_channel_shuffle
:: Tensor
-> Int
-> Tensor
native_channel_shuffle :: Tensor -> Int -> Tensor
native_channel_shuffle Tensor
_self Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.native_channel_shuffle_tl) Tensor
_self Int
_groups
pinverse
:: Tensor
-> Double
-> Tensor
pinverse :: Tensor -> Double -> Tensor
pinverse Tensor
_self Double
_rcond = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
ATen.pinverse_td) Tensor
_self Double
_rcond
poisson_nll_loss
:: Tensor
-> Tensor
-> Bool
-> Bool
-> Double
-> Int
-> Tensor
poisson_nll_loss :: Tensor -> Tensor -> Bool -> Bool -> Double -> Int -> Tensor
poisson_nll_loss Tensor
_input Tensor
_target Bool
_log_input Bool
_full Double
_eps Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> Bool -> Double -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
ATen.poisson_nll_loss_ttbbdl) Tensor
_input Tensor
_target Bool
_log_input Bool
_full Double
_eps Int
_reduction
rad2deg
:: Tensor
-> Tensor
rad2deg :: Tensor -> Tensor
rad2deg Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.rad2deg_t) Tensor
_self
deg2rad
:: Tensor
-> Tensor
deg2rad :: Tensor -> Tensor
deg2rad Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.deg2rad_t) Tensor
_self
ravel
:: Tensor
-> Tensor
ravel :: Tensor -> Tensor
ravel Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ravel_t) Tensor
_self
reciprocal
:: Tensor
-> Tensor
reciprocal :: Tensor -> Tensor
reciprocal Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.reciprocal_t) Tensor
_self
neg
:: Tensor
-> Tensor
neg :: Tensor -> Tensor
neg Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.neg_t) Tensor
_self
negative
:: Tensor
-> Tensor
negative :: Tensor -> Tensor
negative Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.negative_t) Tensor
_self
repeat_interleave_tl
:: Tensor
-> Int
-> Tensor
repeat_interleave_tl :: Tensor -> Int -> Tensor
repeat_interleave_tl Tensor
_repeats Int
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.repeat_interleave_tl) Tensor
_repeats Int
_output_size
repeat_interleave_ttll
:: Tensor
-> Tensor
-> Int
-> Int
-> Tensor
repeat_interleave_ttll :: Tensor -> Tensor -> Int -> Int -> Tensor
repeat_interleave_ttll Tensor
_self Tensor
_repeats Int
_dim Int
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.repeat_interleave_ttll) Tensor
_self Tensor
_repeats Int
_dim Int
_output_size
repeat_interleave_tlll
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
repeat_interleave_tlll :: Tensor -> Int -> Int -> Int -> Tensor
repeat_interleave_tlll Tensor
_self Int
_repeats Int
_dim Int
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.repeat_interleave_tlll) Tensor
_self Int
_repeats Int
_dim Int
_output_size
reshape
:: Tensor
-> [Int]
-> Tensor
reshape :: Tensor -> [Int] -> Tensor
reshape Tensor
_self [Int]
_shape = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.reshape_tl) Tensor
_self [Int]
_shape
round_t
:: Tensor
-> Tensor
round_t :: Tensor -> Tensor
round_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.round_t) Tensor
_self
round_tl
:: Tensor
-> Int
-> Tensor
round_tl :: Tensor -> Int -> Tensor
round_tl Tensor
_self Int
_decimals = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.round_tl) Tensor
_self Int
_decimals
relu
:: Tensor
-> Tensor
relu :: Tensor -> Tensor
relu Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.relu_t) Tensor
_self
relu6
:: Tensor
-> Tensor
relu6 :: Tensor -> Tensor
relu6 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.relu6_t) Tensor
_self
prelu
:: Tensor
-> Tensor
-> Tensor
prelu :: Tensor -> Tensor -> Tensor
prelu Tensor
_self Tensor
_weight = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.prelu_tt) Tensor
_self Tensor
_weight
gelu
:: Tensor
-> String
-> Tensor
gelu :: Tensor -> String -> Tensor
gelu Tensor
_self String
_approximate = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr StdString -> IO (ForeignPtr Tensor))
-> Tensor -> String -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.gelu_ts) Tensor
_self String
_approximate
hardshrink
:: Tensor
-> Float
-> Tensor
hardshrink :: Tensor -> Float -> Tensor
hardshrink Tensor
_self Float
_lambd = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.hardshrink_ts) Tensor
_self Float
_lambd
rsqrt
:: Tensor
-> Tensor
rsqrt :: Tensor -> Tensor
rsqrt Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.rsqrt_t) Tensor
_self
selectWithDimname
:: Tensor
-> Dimname
-> Int
-> Tensor
selectWithDimname :: Tensor -> Dimname -> Int -> Tensor
selectWithDimname Tensor
_self Dimname
_dim Int
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> Int64 -> IO (ForeignPtr Tensor)
ATen.select_tnl) Tensor
_self Dimname
_dim Int
_index
select
:: Tensor
-> Int
-> Int
-> Tensor
select :: Tensor -> Int -> Int -> Tensor
select Tensor
_self Int
_dim Int
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.select_tll) Tensor
_self Int
_dim Int
_index
selu
:: Tensor
-> Tensor
selu :: Tensor -> Tensor
selu Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.selu_t) Tensor
_self
celu
:: Tensor
-> Float
-> Tensor
celu :: Tensor -> Float -> Tensor
celu Tensor
_self Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.celu_ts) Tensor
_self Float
_alpha
silu
:: Tensor
-> Tensor
silu :: Tensor -> Tensor
silu Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.silu_t) Tensor
_self
mish
:: Tensor
-> Tensor
mish :: Tensor -> Tensor
mish Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.mish_t) Tensor
_self
sigmoid
:: Tensor
-> Tensor
sigmoid :: Tensor -> Tensor
sigmoid Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sigmoid_t) Tensor
_self
logit
:: Tensor
-> Double
-> Tensor
logit :: Tensor -> Double -> Tensor
logit Tensor
_self Double
_eps = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
ATen.logit_td) Tensor
_self Double
_eps
sin
:: Tensor
-> Tensor
sin :: Tensor -> Tensor
sin Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sin_t) Tensor
_self
sinc
:: Tensor
-> Tensor
sinc :: Tensor -> Tensor
sinc Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sinc_t) Tensor
_self
sinh
:: Tensor
-> Tensor
sinh :: Tensor -> Tensor
sinh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sinh_t) Tensor
_self
size
:: Tensor
-> Int
-> Int
size :: Tensor -> Int -> Int
size Tensor
_self Int
_dim = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO Int64) -> Tensor -> Int -> IO Int
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO Int64
ATen.size_tl) Tensor
_self Int
_dim
sizeWithDimname
:: Tensor
-> Dimname
-> Int
sizeWithDimname :: Tensor -> Dimname -> Int
sizeWithDimname Tensor
_self Dimname
_dim = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64)
-> Tensor -> Dimname -> IO Int
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64
ATen.size_tn) Tensor
_self Dimname
_dim
slice
:: Tensor
-> Int
-> Int
-> Int
-> Int
-> Tensor
slice :: Tensor -> Int -> Int -> Int -> Int -> Tensor
slice Tensor
_self Int
_dim Int
_start Int
_end Int
_step = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.slice_tllll) Tensor
_self Int
_dim Int
_start Int
_end Int
_step
slice_scatter
:: Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Int
-> Tensor
slice_scatter :: Tensor -> Tensor -> Int -> Int -> Int -> Int -> Tensor
slice_scatter Tensor
_self Tensor
_src Int
_dim Int
_start Int
_end Int
_step = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.slice_scatter_ttllll) Tensor
_self Tensor
_src Int
_dim Int
_start Int
_end Int
_step
select_scatter
:: Tensor
-> Tensor
-> Int
-> Int
-> Tensor
select_scatter :: Tensor -> Tensor -> Int -> Int -> Tensor
select_scatter Tensor
_self Tensor
_src Int
_dim Int
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.select_scatter_ttll) Tensor
_self Tensor
_src Int
_dim Int
_index
diagonal_scatter
:: Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Tensor
diagonal_scatter :: Tensor -> Tensor -> Int -> Int -> Int -> Tensor
diagonal_scatter Tensor
_self Tensor
_src Int
_offset Int
_dim1 Int
_dim2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.diagonal_scatter_ttlll) Tensor
_self Tensor
_src Int
_offset Int
_dim1 Int
_dim2
as_strided_scatter
:: Tensor
-> Tensor
-> [Int]
-> [Int]
-> Int
-> Tensor
as_strided_scatter :: Tensor -> Tensor -> [Int] -> [Int] -> Int -> Tensor
as_strided_scatter Tensor
_self Tensor
_src [Int]
_size [Int]
_stride Int
_storage_offset = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> [Int] -> [Int] -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.as_strided_scatter_ttlll) Tensor
_self Tensor
_src [Int]
_size [Int]
_stride Int
_storage_offset
smm
:: Tensor
-> Tensor
-> Tensor
smm :: Tensor -> Tensor -> Tensor
smm Tensor
_self Tensor
_mat2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.smm_tt) Tensor
_self Tensor
_mat2
softmax
:: Tensor
-> Int
-> DType
-> Tensor
softmax :: Tensor -> Int -> DType -> Tensor
softmax Tensor
_self Int
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.softmax_tls) Tensor
_self Int
_dim DType
_dtype
softmaxWithDimname
:: Tensor
-> Dimname
-> DType
-> Tensor
softmaxWithDimname :: Tensor -> Dimname -> DType -> Tensor
softmaxWithDimname Tensor
_self Dimname
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.softmax_tns) Tensor
_self Dimname
_dim DType
_dtype
unsafe_split
:: Tensor
-> Int
-> Int
-> [Tensor]
unsafe_split :: Tensor -> Int -> Int -> [Tensor]
unsafe_split Tensor
_self Int
_split_size Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
ATen.unsafe_split_tll) Tensor
_self Int
_split_size Int
_dim
split_tll
:: Tensor
-> Int
-> Int
-> [Tensor]
split_tll :: Tensor -> Int -> Int -> [Tensor]
split_tll Tensor
_self Int
_split_size Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
ATen.split_tll) Tensor
_self Int
_split_size Int
_dim
unsafe_split_with_sizes
:: Tensor
-> [Int]
-> Int
-> [Tensor]
unsafe_split_with_sizes :: Tensor -> [Int] -> Int -> [Tensor]
unsafe_split_with_sizes Tensor
_self [Int]
_split_sizes Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> [Int] -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList)
ATen.unsafe_split_with_sizes_tll) Tensor
_self [Int]
_split_sizes Int
_dim
split_with_sizes
:: Tensor
-> [Int]
-> Int
-> [Tensor]
split_with_sizes :: Tensor -> [Int] -> Int -> [Tensor]
split_with_sizes Tensor
_self [Int]
_split_sizes Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> [Int] -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList)
ATen.split_with_sizes_tll) Tensor
_self [Int]
_split_sizes Int
_dim
hsplit_tl
:: Tensor
-> Int
-> [Tensor]
hsplit_tl :: Tensor -> Int -> [Tensor]
hsplit_tl Tensor
_self Int
_sections = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
ATen.hsplit_tl) Tensor
_self Int
_sections
vsplit_tl
:: Tensor
-> Int
-> [Tensor]
vsplit_tl :: Tensor -> Int -> [Tensor]
vsplit_tl Tensor
_self Int
_sections = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
ATen.vsplit_tl) Tensor
_self Int
_sections
dsplit_tl
:: Tensor
-> Int
-> [Tensor]
dsplit_tl :: Tensor -> Int -> [Tensor]
dsplit_tl Tensor
_self Int
_sections = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
ATen.dsplit_tl) Tensor
_self Int
_sections
squeezeAll
:: Tensor
-> Tensor
squeezeAll :: Tensor -> Tensor
squeezeAll Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.squeeze_t) Tensor
_self
squeezeDim
:: Tensor
-> Int
-> Tensor
squeezeDim :: Tensor -> Int -> Tensor
squeezeDim Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.squeeze_tl) Tensor
_self Int
_dim
squeezeWithDimname
:: Tensor
-> Dimname
-> Tensor
squeezeWithDimname :: Tensor -> Dimname -> Tensor
squeezeWithDimname Tensor
_self Dimname
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Dimname -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
ATen.squeeze_tn) Tensor
_self Dimname
_dim
sspaddmm
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
sspaddmm :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
sspaddmm Tensor
_self Tensor
_mat1 Tensor
_mat2 Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.sspaddmm_tttss) Tensor
_self Tensor
_mat1 Tensor
_mat2 Float
_beta Float
_alpha
stack
:: [Tensor]
-> Int
-> Tensor
stack :: [Tensor] -> Int -> Tensor
stack [Tensor]
_tensors Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor))
-> [Tensor] -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList -> Int64 -> IO (ForeignPtr Tensor)
ATen.stack_ll) [Tensor]
_tensors Int
_dim
hstack
:: [Tensor]
-> Tensor
hstack :: [Tensor] -> Tensor
hstack [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.hstack_l) [Tensor]
_tensors
vstack
:: [Tensor]
-> Tensor
vstack :: [Tensor] -> Tensor
vstack [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.vstack_l) [Tensor]
_tensors
dstack
:: [Tensor]
-> Tensor
dstack :: [Tensor] -> Tensor
dstack [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.dstack_l) [Tensor]
_tensors
stft_tllltbbb
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> Bool
-> Bool
-> Tensor
stft_tllltbbb :: Tensor
-> Int -> Int -> Int -> Tensor -> Bool -> Bool -> Bool -> Tensor
stft_tllltbbb Tensor
_self Int
_n_fft Int
_hop_length Int
_win_length Tensor
_window Bool
_normalized Bool
_onesided Bool
_return_complex = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.stft_tllltbbb) Tensor
_self Int
_n_fft Int
_hop_length Int
_win_length Tensor
_window Bool
_normalized Bool
_onesided Bool
_return_complex
stft_tllltbsbbb
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> String
-> Bool
-> Bool
-> Bool
-> Tensor
stft_tllltbsbbb :: Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> String
-> Bool
-> Bool
-> Bool
-> Tensor
stft_tllltbsbbb Tensor
_self Int
_n_fft Int
_hop_length Int
_win_length Tensor
_window Bool
_center String
_pad_mode Bool
_normalized Bool
_onesided Bool
_return_complex = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr StdString
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> String
-> Bool
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
cast10 ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr StdString
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.stft_tllltbsbbb) Tensor
_self Int
_n_fft Int
_hop_length Int
_win_length Tensor
_window Bool
_center String
_pad_mode Bool
_normalized Bool
_onesided Bool
_return_complex
istft
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> Bool
-> Bool
-> Int
-> Bool
-> Tensor
istft :: Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> Bool
-> Bool
-> Int
-> Bool
-> Tensor
istft Tensor
_self Int
_n_fft Int
_hop_length Int
_win_length Tensor
_window Bool
_center Bool
_normalized Bool
_onesided Int
_length Bool
_return_complex = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Int
-> Int
-> Int
-> Tensor
-> Bool
-> Bool
-> Bool
-> Int
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
cast10 ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.istft_tllltbbblb) Tensor
_self Int
_n_fft Int
_hop_length Int
_win_length Tensor
_window Bool
_center Bool
_normalized Bool
_onesided Int
_length Bool
_return_complex
stride
:: Tensor
-> Int
-> Int
stride :: Tensor -> Int -> Int
stride Tensor
_self Int
_dim = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO Int64) -> Tensor -> Int -> IO Int
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO Int64
ATen.stride_tl) Tensor
_self Int
_dim
strideWithDimname
:: Tensor
-> Dimname
-> Int
strideWithDimname :: Tensor -> Dimname -> Int
strideWithDimname Tensor
_self Dimname
_dim = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64)
-> Tensor -> Dimname -> IO Int
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64
ATen.stride_tn) Tensor
_self Dimname
_dim
sumAll
:: Tensor
-> DType
-> Tensor
sumAll :: Tensor -> DType -> Tensor
sumAll Tensor
_self DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> DType -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.sum_ts) Tensor
_self DType
_dtype
sumDim
:: Tensor
-> Int
-> Bool
-> DType
-> Tensor
sumDim :: Tensor -> Int -> Bool -> DType -> Tensor
sumDim Tensor
_self Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.sum_tlbs) Tensor
_self Int
_dim Bool
_keepdim DType
_dtype
sumWithDimnames
:: Tensor
-> [Dimname]
-> Bool
-> DType
-> Tensor
sumWithDimnames :: Tensor -> [Dimname] -> Bool -> DType -> Tensor
sumWithDimnames Tensor
_self [Dimname]
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.sum_tNbs) Tensor
_self [Dimname]
_dim Bool
_keepdim DType
_dtype
nansum
:: Tensor
-> Int
-> Bool
-> DType
-> Tensor
nansum :: Tensor -> Int -> Bool -> DType -> Tensor
nansum Tensor
_self Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.nansum_tlbs) Tensor
_self Int
_dim Bool
_keepdim DType
_dtype
sqrt
:: Tensor
-> Tensor
sqrt :: Tensor -> Tensor
sqrt Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sqrt_t) Tensor
_self
square
:: Tensor
-> Tensor
square :: Tensor -> Tensor
square Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.square_t) Tensor
_self
stdAll
:: Tensor
-> Bool
-> Tensor
stdAll :: Tensor -> Bool -> Tensor
stdAll Tensor
_self Bool
_unbiased = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.std_tb) Tensor
_self Bool
_unbiased
stdDim
:: Tensor
-> Int
-> Bool
-> Bool
-> Tensor
stdDim :: Tensor -> Int -> Bool -> Bool -> Tensor
stdDim Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.std_tlbb) Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim
std_tllb
:: Tensor
-> Int
-> Int
-> Bool
-> Tensor
std_tllb :: Tensor -> Int -> Int -> Bool -> Tensor
std_tllb Tensor
_self Int
_dim Int
_correction Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.std_tllb) Tensor
_self Int
_dim Int
_correction Bool
_keepdim
stdMeanAll
:: Tensor
-> Bool
-> (Tensor,Tensor)
stdMeanAll :: Tensor -> Bool -> (Tensor, Tensor)
stdMeanAll Tensor
_self Bool
_unbiased = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.std_mean_tb) Tensor
_self Bool
_unbiased
stdMeanDim
:: Tensor
-> Int
-> Bool
-> Bool
-> (Tensor,Tensor)
stdMeanDim :: Tensor -> Int -> Bool -> Bool -> (Tensor, Tensor)
stdMeanDim Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.std_mean_tlbb) Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim
std_mean_tllb
:: Tensor
-> Int
-> Int
-> Bool
-> (Tensor,Tensor)
std_mean_tllb :: Tensor -> Int -> Int -> Bool -> (Tensor, Tensor)
std_mean_tllb Tensor
_self Int
_dim Int
_correction Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.std_mean_tllb) Tensor
_self Int
_dim Int
_correction Bool
_keepdim
stdMeanWithDimnames
:: Tensor
-> [Dimname]
-> Bool
-> Bool
-> (Tensor,Tensor)
stdMeanWithDimnames :: Tensor -> [Dimname] -> Bool -> Bool -> (Tensor, Tensor)
stdMeanWithDimnames Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> [Dimname] -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.std_mean_tNbb) Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim
std_mean_tNlb
:: Tensor
-> [Dimname]
-> Int
-> Bool
-> (Tensor,Tensor)
std_mean_tNlb :: Tensor -> [Dimname] -> Int -> Bool -> (Tensor, Tensor)
std_mean_tNlb Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> [Dimname] -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.std_mean_tNlb) Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim
stdWithDimnames
:: Tensor
-> [Dimname]
-> Bool
-> Bool
-> Tensor
stdWithDimnames :: Tensor -> [Dimname] -> Bool -> Bool -> Tensor
stdWithDimnames Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.std_tNbb) Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim
std_tNlb
:: Tensor
-> [Dimname]
-> Int
-> Bool
-> Tensor
std_tNlb :: Tensor -> [Dimname] -> Int -> Bool -> Tensor
std_tNlb Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.std_tNlb) Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim
prodAll
:: Tensor
-> DType
-> Tensor
prodAll :: Tensor -> DType -> Tensor
prodAll Tensor
_self DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> DType -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.prod_ts) Tensor
_self DType
_dtype
prodDim
:: Tensor
-> Int
-> Bool
-> DType
-> Tensor
prodDim :: Tensor -> Int -> Bool -> DType -> Tensor
prodDim Tensor
_self Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> CBool -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.prod_tlbs) Tensor
_self Int
_dim Bool
_keepdim DType
_dtype
prodWithDimnames
:: Tensor
-> Dimname
-> Bool
-> DType
-> Tensor
prodWithDimnames :: Tensor -> Dimname -> Bool -> DType -> Tensor
prodWithDimnames Tensor
_self Dimname
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.prod_tnbs) Tensor
_self Dimname
_dim Bool
_keepdim DType
_dtype
t
:: Tensor
-> Tensor
t :: Tensor -> Tensor
t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.t_t) Tensor
_self
tan
:: Tensor
-> Tensor
tan :: Tensor -> Tensor
tan Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.tan_t) Tensor
_self
tanh
:: Tensor
-> Tensor
tanh :: Tensor -> Tensor
tanh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.tanh_t) Tensor
_self
tensordot
:: Tensor
-> Tensor
-> [Int]
-> [Int]
-> Tensor
tensordot :: Tensor -> Tensor -> [Int] -> [Int] -> Tensor
tensordot Tensor
_self Tensor
_other [Int]
_dims_self [Int]
_dims_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> [Int] -> [Int] -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.tensordot_ttll) Tensor
_self Tensor
_other [Int]
_dims_self [Int]
_dims_other
threshold
:: Tensor
-> Float
-> Float
-> Tensor
threshold :: Tensor -> Float -> Float -> Tensor
threshold Tensor
_self Float
_threshold Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.threshold_tss) Tensor
_self Float
_threshold Float
_value
tile
:: Tensor
-> [Int]
-> Tensor
tile :: Tensor -> [Int] -> Tensor
tile Tensor
_self [Int]
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.tile_tl) Tensor
_self [Int]
_dims
transpose
:: Tensor
-> Int
-> Int
-> Tensor
transpose :: Tensor -> Int -> Int -> Tensor
transpose Tensor
_self Int
_dim0 Int
_dim1 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.transpose_tll) Tensor
_self Int
_dim0 Int
_dim1
transposeWithDimname
:: Tensor
-> Dimname
-> Dimname
-> Tensor
transposeWithDimname :: Tensor -> Dimname -> Dimname -> Tensor
transposeWithDimname Tensor
_self Dimname
_dim0 Dimname
_dim1 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Dimname -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
ATen.transpose_tnn) Tensor
_self Dimname
_dim0 Dimname
_dim1
one_hot
:: Tensor
-> Int
-> Tensor
one_hot :: Tensor -> Int -> Tensor
one_hot Tensor
_self Int
_num_classes = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.one_hot_tl) Tensor
_self Int
_num_classes
flip
:: Tensor
-> [Int]
-> Tensor
flip :: Tensor -> [Int] -> Tensor
flip Tensor
_self [Int]
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.flip_tl) Tensor
_self [Int]
_dims
fliplr
:: Tensor
-> Tensor
fliplr :: Tensor -> Tensor
fliplr Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fliplr_t) Tensor
_self
flipud
:: Tensor
-> Tensor
flipud :: Tensor -> Tensor
flipud Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.flipud_t) Tensor
_self
roll
:: Tensor
-> Int
-> Int
-> Tensor
roll :: Tensor -> Int -> Int -> Tensor
roll Tensor
_self Int
_shifts Int
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.roll_tll) Tensor
_self Int
_shifts Int
_dims
rot90
:: Tensor
-> Int
-> [Int]
-> Tensor
rot90 :: Tensor -> Int -> [Int] -> Tensor
rot90 Tensor
_self Int
_k [Int]
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> [Int] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.rot90_tll) Tensor
_self Int
_k [Int]
_dims
trapezoid_ttl
:: Tensor
-> Tensor
-> Int
-> Tensor
trapezoid_ttl :: Tensor -> Tensor -> Int -> Tensor
trapezoid_ttl Tensor
_y Tensor
_x Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.trapezoid_ttl) Tensor
_y Tensor
_x Int
_dim
trapezoid_tsl
:: Tensor
-> Float
-> Int
-> Tensor
trapezoid_tsl :: Tensor -> Float -> Int -> Tensor
trapezoid_tsl Tensor
_y Float
_dx Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> Int64 -> IO (ForeignPtr Tensor)
ATen.trapezoid_tsl) Tensor
_y Float
_dx Int
_dim
trapz
:: Tensor
-> Tensor
-> Int
-> Tensor
trapz :: Tensor -> Tensor -> Int -> Tensor
trapz Tensor
_y Tensor
_x Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.trapz_ttl) Tensor
_y Tensor
_x Int
_dim
trapzScalar
:: Tensor
-> Double
-> Int
-> Tensor
trapzScalar :: Tensor -> Double -> Int -> Tensor
trapzScalar Tensor
_y Double
_dx Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor)
ATen.trapz_tdl) Tensor
_y Double
_dx Int
_dim
triplet_margin_loss
:: Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Double
-> Bool
-> Int
-> Tensor
triplet_margin_loss :: Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Double
-> Bool
-> Int
-> Tensor
triplet_margin_loss Tensor
_anchor Tensor
_positive Tensor
_negative Double
_margin Double
_p Double
_eps Bool
_swap Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Double
-> Double
-> Bool
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> Int64
-> IO (ForeignPtr Tensor)
ATen.triplet_margin_loss_tttdddbl) Tensor
_anchor Tensor
_positive Tensor
_negative Double
_margin Double
_p Double
_eps Bool
_swap Int
_reduction
trunc
:: Tensor
-> Tensor
trunc :: Tensor -> Tensor
trunc Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.trunc_t) Tensor
_self
fix
:: Tensor
-> Tensor
fix :: Tensor -> Tensor
fix Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fix_t) Tensor
_self
unique_dim
:: Tensor
-> Int
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
unique_dim :: Tensor -> Int -> Bool -> Bool -> Bool -> (Tensor, Tensor, Tensor)
unique_dim Tensor
_self Int
_dim Bool
_sorted Bool
_return_inverse Bool
_return_counts = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> Int
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.unique_dim_tlbbb) Tensor
_self Int
_dim Bool
_sorted Bool
_return_inverse Bool
_return_counts
unique_consecutive
:: Tensor
-> Bool
-> Bool
-> Int
-> (Tensor,Tensor,Tensor)
unique_consecutive :: Tensor -> Bool -> Bool -> Int -> (Tensor, Tensor, Tensor)
unique_consecutive Tensor
_self Bool
_return_inverse Bool
_return_counts Int
_dim = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Bool -> Bool -> Int -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.unique_consecutive_tbbl) Tensor
_self Bool
_return_inverse Bool
_return_counts Int
_dim
unique_dim_consecutive
:: Tensor
-> Int
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
unique_dim_consecutive :: Tensor -> Int -> Bool -> Bool -> (Tensor, Tensor, Tensor)
unique_dim_consecutive Tensor
_self Int
_dim Bool
_return_inverse Bool
_return_counts = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Int -> Bool -> Bool -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.unique_dim_consecutive_tlbb) Tensor
_self Int
_dim Bool
_return_inverse Bool
_return_counts
unsqueeze
:: Tensor
-> Int
-> Tensor
unsqueeze :: Tensor -> Int -> Tensor
unsqueeze Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.unsqueeze_tl) Tensor
_self Int
_dim
vander
:: Tensor
-> Int
-> Bool
-> Tensor
vander :: Tensor -> Int -> Bool -> Tensor
vander Tensor
_x Int
_N Bool
_increasing = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.vander_tlb) Tensor
_x Int
_N Bool
_increasing
var
:: Tensor
-> Bool
-> Tensor
var :: Tensor -> Bool -> Tensor
var Tensor
_self Bool
_unbiased = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.var_tb) Tensor
_self Bool
_unbiased
varDim
:: Tensor
-> Int
-> Bool
-> Bool
-> Tensor
varDim :: Tensor -> Int -> Bool -> Bool -> Tensor
varDim Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.var_tlbb) Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim
var_tllb
:: Tensor
-> Int
-> Int
-> Bool
-> Tensor
var_tllb :: Tensor -> Int -> Int -> Bool -> Tensor
var_tllb Tensor
_self Int
_dim Int
_correction Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.var_tllb) Tensor
_self Int
_dim Int
_correction Bool
_keepdim
varWithDimnames
:: Tensor
-> [Dimname]
-> Bool
-> Bool
-> Tensor
varWithDimnames :: Tensor -> [Dimname] -> Bool -> Bool -> Tensor
varWithDimnames Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.var_tNbb) Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim
var_tNlb
:: Tensor
-> [Dimname]
-> Int
-> Bool
-> Tensor
var_tNlb :: Tensor -> [Dimname] -> Int -> Bool -> Tensor
var_tNlb Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> [Dimname] -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
ATen.var_tNlb) Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim
varMean
:: Tensor
-> Bool
-> (Tensor,Tensor)
varMean :: Tensor -> Bool -> (Tensor, Tensor)
varMean Tensor
_self Bool
_unbiased = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.var_mean_tb) Tensor
_self Bool
_unbiased
varMeanDim
:: Tensor
-> Int
-> Bool
-> Bool
-> (Tensor,Tensor)
varMeanDim :: Tensor -> Int -> Bool -> Bool -> (Tensor, Tensor)
varMeanDim Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.var_mean_tlbb) Tensor
_self Int
_dim Bool
_unbiased Bool
_keepdim
var_mean_tllb
:: Tensor
-> Int
-> Int
-> Bool
-> (Tensor,Tensor)
var_mean_tllb :: Tensor -> Int -> Int -> Bool -> (Tensor, Tensor)
var_mean_tllb Tensor
_self Int
_dim Int
_correction Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.var_mean_tllb) Tensor
_self Int
_dim Int
_correction Bool
_keepdim
varMeanWithDimnames
:: Tensor
-> [Dimname]
-> Bool
-> Bool
-> (Tensor,Tensor)
varMeanWithDimnames :: Tensor -> [Dimname] -> Bool -> Bool -> (Tensor, Tensor)
varMeanWithDimnames Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> [Dimname] -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.var_mean_tNbb) Tensor
_self [Dimname]
_dim Bool
_unbiased Bool
_keepdim
var_mean_tNlb
:: Tensor
-> [Dimname]
-> Int
-> Bool
-> (Tensor,Tensor)
var_mean_tNlb :: Tensor -> [Dimname] -> Int -> Bool -> (Tensor, Tensor)
var_mean_tNlb Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> [Dimname] -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.var_mean_tNlb) Tensor
_self [Dimname]
_dim Int
_correction Bool
_keepdim
where'
:: Tensor
-> Tensor
-> Tensor
-> Tensor
where' :: Tensor -> Tensor -> Tensor -> Tensor
where' Tensor
_condition Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.where_ttt) Tensor
_condition Tensor
_self Tensor
_other
where_tst
:: Tensor
-> Float
-> Tensor
-> Tensor
where_tst :: Tensor -> Float -> Tensor -> Tensor
where_tst Tensor
_condition Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.where_tst) Tensor
_condition Float
_self Tensor
_other
where_tts
:: Tensor
-> Tensor
-> Float
-> Tensor
where_tts :: Tensor -> Tensor -> Float -> Tensor
where_tts Tensor
_condition Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.where_tts) Tensor
_condition Tensor
_self Float
_other
where_tss
:: Tensor
-> Float
-> Float
-> Tensor
where_tss :: Tensor -> Float -> Float -> Tensor
where_tss Tensor
_condition Float
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.where_tss) Tensor
_condition Float
_self Float
_other
isNonZero
:: Tensor
-> [Tensor]
isNonZero :: Tensor -> [Tensor]
isNonZero Tensor
_condition = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr TensorList))
-> Tensor -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr TensorList)
ATen.where_t) Tensor
_condition
norm_except_dim
:: Tensor
-> Int
-> Int
-> Tensor
norm_except_dim :: Tensor -> Int -> Int -> Tensor
norm_except_dim Tensor
_v Int
_pow Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.norm_except_dim_tll) Tensor
_v Int
_pow Int
_dim
native_norm_ts
:: Tensor
-> Float
-> Tensor
native_norm_ts :: Tensor -> Float -> Tensor
native_norm_ts Tensor
_self Float
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.native_norm_ts) Tensor
_self Float
_p
native_norm_tslbs
:: Tensor
-> Float
-> Int
-> Bool
-> DType
-> Tensor
native_norm_tslbs :: Tensor -> Float -> Int -> Bool -> DType -> Tensor
native_norm_tslbs Tensor
_self Float
_p Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.native_norm_tslbs) Tensor
_self Float
_p Int
_dim Bool
_keepdim DType
_dtype
normCastAll
:: Tensor
-> Float
-> DType
-> Tensor
normCastAll :: Tensor -> Float -> DType -> Tensor
normCastAll Tensor
_self Float
_p DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.norm_tss) Tensor
_self Float
_p DType
_dtype
normAll
:: Tensor
-> Float
-> Tensor
normAll :: Tensor -> Float -> Tensor
normAll Tensor
_self Float
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.norm_ts) Tensor
_self Float
_p
normCastDim
:: Tensor
-> Float
-> Int
-> Bool
-> DType
-> Tensor
normCastDim :: Tensor -> Float -> Int -> Bool -> DType -> Tensor
normCastDim Tensor
_self Float
_p Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.norm_tslbs) Tensor
_self Float
_p Int
_dim Bool
_keepdim DType
_dtype
normDim
:: Tensor
-> Float
-> Int
-> Bool
-> Tensor
normDim :: Tensor -> Float -> Int -> Bool -> Tensor
normDim Tensor
_self Float
_p Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
ATen.norm_tslb) Tensor
_self Float
_p Int
_dim Bool
_keepdim
norm_tsNbs
:: Tensor
-> Float
-> [Dimname]
-> Bool
-> DType
-> Tensor
norm_tsNbs :: Tensor -> Float -> [Dimname] -> Bool -> DType -> Tensor
norm_tsNbs Tensor
_self Float
_p [Dimname]
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> [Dimname] -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.norm_tsNbs) Tensor
_self Float
_p [Dimname]
_dim Bool
_keepdim DType
_dtype
norm_tsNb
:: Tensor
-> Float
-> [Dimname]
-> Bool
-> Tensor
norm_tsNb :: Tensor -> Float -> [Dimname] -> Bool -> Tensor
norm_tsNb Tensor
_self Float
_p [Dimname]
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> [Dimname] -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor)
ATen.norm_tsNb) Tensor
_self Float
_p [Dimname]
_dim Bool
_keepdim
frexp
:: Tensor
-> (Tensor,Tensor)
frexp :: Tensor -> (Tensor, Tensor)
frexp Tensor
_self = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> IO (Tensor, Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.frexp_t) Tensor
_self
frobenius_norm
:: Tensor
-> Int
-> Bool
-> Tensor
frobenius_norm :: Tensor -> Int -> Bool -> Tensor
frobenius_norm Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.frobenius_norm_tlb) Tensor
_self Int
_dim Bool
_keepdim
nuclearNormAll
:: Tensor
-> Bool
-> Tensor
nuclearNormAll :: Tensor -> Bool -> Tensor
nuclearNormAll Tensor
_self Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.nuclear_norm_tb) Tensor
_self Bool
_keepdim
nuclearNormDim
:: Tensor
-> (Int,Int)
-> Bool
-> Tensor
nuclearNormDim :: Tensor -> (Int, Int) -> Bool -> Tensor
nuclearNormDim Tensor
_self (Int, Int)
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.nuclear_norm_tlb) Tensor
_self (Int, Int)
_dim Bool
_keepdim
clone
:: Tensor
-> ATen.MemoryFormat
-> Tensor
clone :: Tensor -> MemoryFormat -> Tensor
clone Tensor
_self MemoryFormat
_memory_format = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> MemoryFormat -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.clone_tM) Tensor
_self MemoryFormat
_memory_format
positive
:: Tensor
-> Tensor
positive :: Tensor -> Tensor
positive Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.positive_t) Tensor
_self
sub
:: Tensor
-> Tensor
-> Float
-> Tensor
sub :: Tensor -> Tensor -> Float -> Tensor
sub Tensor
_self Tensor
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.sub_tts) Tensor
_self Tensor
_other Float
_alpha
subScalar
:: Tensor
-> Float
-> Float
-> Tensor
subScalar :: Tensor -> Float -> Float -> Tensor
subScalar Tensor
_self Float
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.sub_tss) Tensor
_self Float
_other Float
_alpha
subtract_tts
:: Tensor
-> Tensor
-> Float
-> Tensor
subtract_tts :: Tensor -> Tensor -> Float -> Tensor
subtract_tts Tensor
_self Tensor
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.subtract_tts) Tensor
_self Tensor
_other Float
_alpha
subtract_tss
:: Tensor
-> Float
-> Float
-> Tensor
subtract_tss :: Tensor -> Float -> Float -> Tensor
subtract_tss Tensor
_self Float
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.subtract_tss) Tensor
_self Float
_other Float
_alpha
rsub
:: Tensor
-> Tensor
-> Float
-> Tensor
rsub :: Tensor -> Tensor -> Float -> Tensor
rsub Tensor
_self Tensor
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.rsub_tts) Tensor
_self Tensor
_other Float
_alpha
heaviside
:: Tensor
-> Tensor
-> Tensor
heaviside :: Tensor -> Tensor -> Tensor
heaviside Tensor
_self Tensor
_values = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.heaviside_tt) Tensor
_self Tensor
_values
rsubScalar
:: Tensor
-> Float
-> Float
-> Tensor
rsubScalar :: Tensor -> Float -> Float -> Tensor
rsubScalar Tensor
_self Float
_other Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.rsub_tss) Tensor
_self Float
_other Float
_alpha
sparse_sampled_addmm
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
sparse_sampled_addmm :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
sparse_sampled_addmm Tensor
_self Tensor
_mat1 Tensor
_mat2 Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.sparse_sampled_addmm_tttss) Tensor
_self Tensor
_mat1 Tensor
_mat2 Float
_beta Float
_alpha
addmm
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
addmm :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
addmm Tensor
_self Tensor
_mat1 Tensor
_mat2 Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.addmm_tttss) Tensor
_self Tensor
_mat1 Tensor
_mat2 Float
_beta Float
_alpha
hspmm
:: Tensor
-> Tensor
-> Tensor
hspmm :: Tensor -> Tensor -> Tensor
hspmm Tensor
_mat1 Tensor
_mat2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.hspmm_tt) Tensor
_mat1 Tensor
_mat2
unbind
:: Tensor
-> Int
-> [Tensor]
unbind :: Tensor -> Int -> [Tensor]
unbind Tensor
_self Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
ATen.unbind_tl) Tensor
_self Int
_dim
unbindWithDimname
:: Tensor
-> Dimname
-> [Tensor]
unbindWithDimname :: Tensor -> Dimname -> [Tensor]
unbindWithDimname Tensor
_self Dimname
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> IO (ForeignPtr TensorList))
-> Tensor -> Dimname -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr Dimname -> IO (ForeignPtr TensorList)
ATen.unbind_tn) Tensor
_self Dimname
_dim
mkldnn_reorder_conv2d_weight
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Int
-> [Int]
-> Tensor
mkldnn_reorder_conv2d_weight :: Tensor
-> (Int, Int) -> (Int, Int) -> (Int, Int) -> Int -> [Int] -> Tensor
mkldnn_reorder_conv2d_weight Tensor
_self (Int, Int)
_padding (Int, Int)
_stride (Int, Int)
_dilation Int
_groups [Int]
_input_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Int
-> [Int]
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.mkldnn_reorder_conv2d_weight_tlllll) Tensor
_self (Int, Int)
_padding (Int, Int)
_stride (Int, Int)
_dilation Int
_groups [Int]
_input_size
mkldnn_reorder_conv3d_weight
:: Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Int
-> Tensor
mkldnn_reorder_conv3d_weight :: Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Int
-> Tensor
mkldnn_reorder_conv3d_weight Tensor
_self (Int, Int, Int)
_padding (Int, Int, Int)
_stride (Int, Int, Int)
_dilation Int
_groups = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.mkldnn_reorder_conv3d_weight_tllll) Tensor
_self (Int, Int, Int)
_padding (Int, Int, Int)
_stride (Int, Int, Int)
_dilation Int
_groups
quantize_per_tensor_dynamic
:: Tensor
-> DType
-> Bool
-> Tensor
quantize_per_tensor_dynamic :: Tensor -> DType -> Bool -> Tensor
quantize_per_tensor_dynamic Tensor
_self DType
_dtype Bool
_reduce_range = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> MemoryFormat -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> DType -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> MemoryFormat -> CBool -> IO (ForeignPtr Tensor)
ATen.quantize_per_tensor_dynamic_tsb) Tensor
_self DType
_dtype Bool
_reduce_range
quantize_per_tensor_tdls
:: Tensor
-> Double
-> Int
-> DType
-> Tensor
quantize_per_tensor_tdls :: Tensor -> Double -> Int -> DType -> Tensor
quantize_per_tensor_tdls Tensor
_self Double
_scale Int
_zero_point DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CDouble -> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.quantize_per_tensor_tdls) Tensor
_self Double
_scale Int
_zero_point DType
_dtype
quantize_per_tensor_ttts
:: Tensor
-> Tensor
-> Tensor
-> DType
-> Tensor
quantize_per_tensor_ttts :: Tensor -> Tensor -> Tensor -> DType -> Tensor
quantize_per_tensor_ttts Tensor
_self Tensor
_scale Tensor
_zero_point DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.quantize_per_tensor_ttts) Tensor
_self Tensor
_scale Tensor
_zero_point DType
_dtype
quantize_per_tensor_ltts
:: [Tensor]
-> Tensor
-> Tensor
-> DType
-> [Tensor]
quantize_per_tensor_ltts :: [Tensor] -> Tensor -> Tensor -> DType -> [Tensor]
quantize_per_tensor_ltts [Tensor]
_tensors Tensor
_scales Tensor
_zero_points DType
_dtype = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> MemoryFormat
-> IO (ForeignPtr TensorList))
-> [Tensor] -> Tensor -> Tensor -> DType -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> MemoryFormat
-> IO (ForeignPtr TensorList)
ATen.quantize_per_tensor_ltts) [Tensor]
_tensors Tensor
_scales Tensor
_zero_points DType
_dtype
quantize_per_channel
:: Tensor
-> Tensor
-> Tensor
-> Int
-> DType
-> Tensor
quantize_per_channel :: Tensor -> Tensor -> Tensor -> Int -> DType -> Tensor
quantize_per_channel Tensor
_self Tensor
_scales Tensor
_zero_points Int
_axis DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.quantize_per_channel_tttls) Tensor
_self Tensor
_scales Tensor
_zero_points Int
_axis DType
_dtype
dequantize_t
:: Tensor
-> Tensor
dequantize_t :: Tensor -> Tensor
dequantize_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.dequantize_t) Tensor
_self
dequantize_l
:: [Tensor]
-> [Tensor]
dequantize_l :: [Tensor] -> [Tensor]
dequantize_l [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.dequantize_l) [Tensor]
_tensors
q_scale
:: Tensor
-> Double
q_scale :: Tensor -> Double
q_scale Tensor
_self = IO Double -> Double
forall a. IO a -> a
unsafePerformIO (IO Double -> Double) -> IO Double -> Double
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO CDouble) -> Tensor -> IO Double
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO CDouble
ATen.q_scale_t) Tensor
_self
q_zero_point
:: Tensor
-> Int
q_zero_point :: Tensor -> Int
q_zero_point Tensor
_self = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO Int64) -> Tensor -> IO Int
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO Int64
ATen.q_zero_point_t) Tensor
_self
q_per_channel_scales
:: Tensor
-> Tensor
q_per_channel_scales :: Tensor -> Tensor
q_per_channel_scales Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.q_per_channel_scales_t) Tensor
_self
q_per_channel_zero_points
:: Tensor
-> Tensor
q_per_channel_zero_points :: Tensor -> Tensor
q_per_channel_zero_points Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.q_per_channel_zero_points_t) Tensor
_self
q_per_channel_axis
:: Tensor
-> Int
q_per_channel_axis :: Tensor -> Int
q_per_channel_axis Tensor
_self = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO Int64) -> Tensor -> IO Int
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO Int64
ATen.q_per_channel_axis_t) Tensor
_self
int_repr
:: Tensor
-> Tensor
int_repr :: Tensor -> Tensor
int_repr Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.int_repr_t) Tensor
_self
fake_quantize_per_tensor_affine_tdlll
:: Tensor
-> Double
-> Int
-> Int
-> Int
-> Tensor
fake_quantize_per_tensor_affine_tdlll :: Tensor -> Double -> Int -> Int -> Int -> Tensor
fake_quantize_per_tensor_affine_tdlll Tensor
_self Double
_scale Int
_zero_point Int
_quant_min Int
_quant_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> CDouble -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.fake_quantize_per_tensor_affine_tdlll) Tensor
_self Double
_scale Int
_zero_point Int
_quant_min Int
_quant_max
fake_quantize_per_tensor_affine_tttll
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Tensor
fake_quantize_per_tensor_affine_tttll :: Tensor -> Tensor -> Tensor -> Int -> Int -> Tensor
fake_quantize_per_tensor_affine_tttll Tensor
_self Tensor
_scale Tensor
_zero_point Int
_quant_min Int
_quant_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.fake_quantize_per_tensor_affine_tttll) Tensor
_self Tensor
_scale Tensor
_zero_point Int
_quant_min Int
_quant_max
fake_quantize_per_tensor_affine_cachemask
:: Tensor
-> Double
-> Int
-> Int
-> Int
-> (Tensor,Tensor)
fake_quantize_per_tensor_affine_cachemask :: Tensor -> Double -> Int -> Int -> Int -> (Tensor, Tensor)
fake_quantize_per_tensor_affine_cachemask Tensor
_self Double
_scale Int
_zero_point Int
_quant_min Int
_quant_max = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Double -> Int -> Int -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.fake_quantize_per_tensor_affine_cachemask_tdlll) Tensor
_self Double
_scale Int
_zero_point Int
_quant_min Int
_quant_max
fake_quantize_per_channel_affine
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> Tensor
fake_quantize_per_channel_affine :: Tensor -> Tensor -> Tensor -> Int -> Int -> Int -> Tensor
fake_quantize_per_channel_affine Tensor
_self Tensor
_scale Tensor
_zero_point Int
_axis Int
_quant_min Int
_quant_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.fake_quantize_per_channel_affine_tttlll) Tensor
_self Tensor
_scale Tensor
_zero_point Int
_axis Int
_quant_min Int
_quant_max
fake_quantize_per_channel_affine_cachemask
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> (Tensor,Tensor)
fake_quantize_per_channel_affine_cachemask :: Tensor -> Tensor -> Tensor -> Int -> Int -> Int -> (Tensor, Tensor)
fake_quantize_per_channel_affine_cachemask Tensor
_self Tensor
_scale Tensor
_zero_point Int
_axis Int
_quant_min Int
_quant_max = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Int
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.fake_quantize_per_channel_affine_cachemask_tttlll) Tensor
_self Tensor
_scale Tensor
_zero_point Int
_axis Int
_quant_min Int
_quant_max
fused_moving_avg_obs_fake_quant
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Tensor
fused_moving_avg_obs_fake_quant :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Tensor
fused_moving_avg_obs_fake_quant Tensor
_self Tensor
_observer_on Tensor
_fake_quant_on Tensor
_running_min Tensor
_running_max Tensor
_scale Tensor
_zero_point Double
_averaging_const Int
_quant_min Int
_quant_max Int
_ch_axis Bool
_per_row_fake_quant Bool
_symmetric_quant = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> IO y
cast13 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.fused_moving_avg_obs_fake_quant_tttttttdlllbb) Tensor
_self Tensor
_observer_on Tensor
_fake_quant_on Tensor
_running_min Tensor
_running_max Tensor
_scale Tensor
_zero_point Double
_averaging_const Int
_quant_min Int
_quant_max Int
_ch_axis Bool
_per_row_fake_quant Bool
_symmetric_quant
choose_qparams_optimized
:: Tensor
-> Int
-> Int
-> Double
-> Int
-> (Tensor,Tensor)
choose_qparams_optimized :: Tensor -> Int -> Int -> Double -> Int -> (Tensor, Tensor)
choose_qparams_optimized Tensor
_input Int
_numel Int
_n_bins Double
_ratio Int
_bit_width = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> CDouble
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Int -> Double -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> Int64
-> CDouble
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.choose_qparams_optimized_tlldl) Tensor
_input Int
_numel Int
_n_bins Double
_ratio Int
_bit_width
meshgrid_l
:: [Tensor]
-> [Tensor]
meshgrid_l :: [Tensor] -> [Tensor]
meshgrid_l [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> [Tensor] -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.meshgrid_l) [Tensor]
_tensors
meshgrid_ls
:: [Tensor]
-> String
-> [Tensor]
meshgrid_ls :: [Tensor] -> String -> [Tensor]
meshgrid_ls [Tensor]
_tensors String
_indexing = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList
-> ForeignPtr StdString -> IO (ForeignPtr TensorList))
-> [Tensor] -> String -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr TensorList
-> ForeignPtr StdString -> IO (ForeignPtr TensorList)
ATen.meshgrid_ls) [Tensor]
_tensors String
_indexing
cartesian_prod
:: [Tensor]
-> Tensor
cartesian_prod :: [Tensor] -> Tensor
cartesian_prod [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.cartesian_prod_l) [Tensor]
_tensors
combinations
:: Tensor
-> Int
-> Bool
-> Tensor
combinations :: Tensor -> Int -> Bool -> Tensor
combinations Tensor
_self Int
_r Bool
_with_replacement = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.combinations_tlb) Tensor
_self Int
_r Bool
_with_replacement
resultType
:: Tensor
-> Tensor
-> DType
resultType :: Tensor -> Tensor -> DType
resultType Tensor
_tensor Tensor
_other = IO DType -> DType
forall a. IO a -> a
unsafePerformIO (IO DType -> DType) -> IO DType -> DType
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO MemoryFormat)
-> Tensor -> Tensor -> IO DType
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO MemoryFormat
ATen.result_type_tt) Tensor
_tensor Tensor
_other
resultTypeScalar
:: Tensor
-> Float
-> DType
resultTypeScalar :: Tensor -> Float -> DType
resultTypeScalar Tensor
_tensor Float
_other = IO DType -> DType
forall a. IO a -> a
unsafePerformIO (IO DType -> DType) -> IO DType -> DType
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO MemoryFormat)
-> Tensor -> Float -> IO DType
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO MemoryFormat
ATen.result_type_ts) Tensor
_tensor Float
_other
resultTypeScalar'
:: Float
-> Tensor
-> DType
resultTypeScalar' :: Float -> Tensor -> DType
resultTypeScalar' Float
_scalar Tensor
_tensor = IO DType -> DType
forall a. IO a -> a
unsafePerformIO (IO DType -> DType) -> IO DType -> DType
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO MemoryFormat)
-> Float -> Tensor -> IO DType
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO MemoryFormat
ATen.result_type_st) Float
_scalar Tensor
_tensor
resultTypeScalars
:: Float
-> Float
-> DType
resultTypeScalars :: Float -> Float -> DType
resultTypeScalars Float
_scalar1 Float
_scalar2 = IO DType -> DType
forall a. IO a -> a
unsafePerformIO (IO DType -> DType) -> IO DType -> DType
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Scalar -> IO MemoryFormat)
-> Float -> Float -> IO DType
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Scalar -> IO MemoryFormat
ATen.result_type_ss) Float
_scalar1 Float
_scalar2
can_cast
:: DType
-> DType
-> Bool
can_cast :: DType -> DType -> Bool
can_cast DType
_from DType
_to = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((MemoryFormat -> MemoryFormat -> IO CBool)
-> DType -> DType -> IO Bool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 MemoryFormat -> MemoryFormat -> IO CBool
ATen.can_cast_ss) DType
_from DType
_to
promote_types
:: DType
-> DType
-> DType
promote_types :: DType -> DType -> DType
promote_types DType
_type1 DType
_type2 = IO DType -> DType
forall a. IO a -> a
unsafePerformIO (IO DType -> DType) -> IO DType -> DType
forall a b. (a -> b) -> a -> b
$ ((MemoryFormat -> MemoryFormat -> IO MemoryFormat)
-> DType -> DType -> IO DType
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 MemoryFormat -> MemoryFormat -> IO MemoryFormat
ATen.promote_types_ss) DType
_type1 DType
_type2
lstm
:: Tensor
-> [Tensor]
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
lstm :: Tensor
-> [Tensor]
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor, Tensor, Tensor)
lstm Tensor
_input [Tensor]
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> [Tensor]
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.lstm_tllbldbbb) Tensor
_input [Tensor]
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first
lstm'
:: Tensor
-> Tensor
-> [Tensor]
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
lstm' :: Tensor
-> Tensor
-> [Tensor]
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor, Tensor, Tensor)
lstm' Tensor
_data Tensor
_batch_sizes [Tensor]
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> [Tensor]
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.lstm_ttllbldbb) Tensor
_data Tensor
_batch_sizes [Tensor]
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional
gru
:: Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor)
gru :: Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor, Tensor)
gru Tensor
_input Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.gru_ttlbldbbb) Tensor
_input Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first
gru'
:: Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor,Tensor)
gru' :: Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor, Tensor)
gru' Tensor
_data Tensor
_batch_sizes Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.gru_tttlbldbb) Tensor
_data Tensor
_batch_sizes Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional
rnnTanh
:: Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor)
rnnTanh :: Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor, Tensor)
rnnTanh Tensor
_input Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.rnn_tanh_ttlbldbbb) Tensor
_input Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first
rnnTanh'
:: Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor,Tensor)
rnnTanh' :: Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor, Tensor)
rnnTanh' Tensor
_data Tensor
_batch_sizes Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.rnn_tanh_tttlbldbb) Tensor
_data Tensor
_batch_sizes Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional
rnnRelu
:: Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor)
rnnRelu :: Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> (Tensor, Tensor)
rnnRelu Tensor
_input Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.rnn_relu_ttlbldbbb) Tensor
_input Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional Bool
_batch_first
rnnRelu'
:: Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor,Tensor)
rnnRelu' :: Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> (Tensor, Tensor)
rnnRelu' Tensor
_data Tensor
_batch_sizes Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Tensor
-> Tensor
-> [Tensor]
-> Bool
-> Int
-> Double
-> Bool
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable y cy) =>
(ca
-> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
cast9 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.rnn_relu_tttlbldbb) Tensor
_data Tensor
_batch_sizes Tensor
_hx [Tensor]
_params Bool
_has_biases Int
_num_layers Double
_dropout Bool
_train Bool
_bidirectional
lstm_cell
:: Tensor
-> [Tensor]
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> (Tensor,Tensor)
lstm_cell :: Tensor
-> [Tensor]
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> (Tensor, Tensor)
lstm_cell Tensor
_input [Tensor]
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> [Tensor]
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.lstm_cell_tltttt) Tensor
_input [Tensor]
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh
gru_cell
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
gru_cell :: Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Tensor
gru_cell Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.gru_cell_tttttt) Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh
rnn_tanh_cell
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
rnn_tanh_cell :: Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Tensor
rnn_tanh_cell Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.rnn_tanh_cell_tttttt) Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh
rnn_relu_cell
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
rnn_relu_cell :: Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Tensor
rnn_relu_cell Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.rnn_relu_cell_tttttt) Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh
quantized_lstm_cell
:: Tensor
-> [Tensor]
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> (Tensor,Tensor)
quantized_lstm_cell :: Tensor
-> [Tensor]
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> (Tensor, Tensor)
quantized_lstm_cell Tensor
_input [Tensor]
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> [Tensor]
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> cx13
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> IO y
cast14 ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.quantized_lstm_cell_tlttttttttssss) Tensor
_input [Tensor]
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh
quantized_gru_cell
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> Tensor
quantized_gru_cell :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> Tensor
quantized_gru_cell Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> cx13
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> IO y
cast14 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.quantized_gru_cell_ttttttttttssss) Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh
quantized_rnn_relu_cell
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> Tensor
quantized_rnn_relu_cell :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> Tensor
quantized_rnn_relu_cell Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> cx13
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> IO y
cast14 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.quantized_rnn_relu_cell_ttttttttttssss) Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh
quantized_rnn_tanh_cell
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> Tensor
quantized_rnn_tanh_cell :: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> Tensor
quantized_rnn_tanh_cell Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Float
-> Float
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
Castable y cy) =>
(ca
-> cx1
-> cx2
-> cx3
-> cx4
-> cx5
-> cx6
-> cx7
-> cx8
-> cx9
-> cx10
-> cx11
-> cx12
-> cx13
-> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> IO y
cast14 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.quantized_rnn_tanh_cell_ttttttttttssss) Tensor
_input Tensor
_hx Tensor
_w_ih Tensor
_w_hh Tensor
_b_ih Tensor
_b_hh Tensor
_packed_ih Tensor
_packed_hh Tensor
_col_offsets_ih Tensor
_col_offsets_hh Float
_scale_ih Float
_scale_hh Float
_zero_point_ih Float
_zero_point_hh
lift
:: Tensor
-> Tensor
lift :: Tensor -> Tensor
lift Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lift_t) Tensor
_self
lift_fresh
:: Tensor
-> Tensor
lift_fresh :: Tensor -> Tensor
lift_fresh Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lift_fresh_t) Tensor
_self
lift_fresh_copy
:: Tensor
-> Tensor
lift_fresh_copy :: Tensor -> Tensor
lift_fresh_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lift_fresh_copy_t) Tensor
_self
maskedFillScalar
:: Tensor
-> Tensor
-> Float
-> Tensor
maskedFillScalar :: Tensor -> Tensor -> Float -> Tensor
maskedFillScalar Tensor
_self Tensor
_mask Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.masked_fill_tts) Tensor
_self Tensor
_mask Float
_value
maskedFill
:: Tensor
-> Tensor
-> Tensor
-> Tensor
maskedFill :: Tensor -> Tensor -> Tensor -> Tensor
maskedFill Tensor
_self Tensor
_mask Tensor
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.masked_fill_ttt) Tensor
_self Tensor
_mask Tensor
_value
masked_scatter
:: Tensor
-> Tensor
-> Tensor
-> Tensor
masked_scatter :: Tensor -> Tensor -> Tensor -> Tensor
masked_scatter Tensor
_self Tensor
_mask Tensor
_source = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.masked_scatter_ttt) Tensor
_self Tensor
_mask Tensor
_source
put
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Tensor
put :: Tensor -> Tensor -> Tensor -> Bool -> Tensor
put Tensor
_self Tensor
_index Tensor
_source Bool
_accumulate = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
ATen.put_tttb) Tensor
_self Tensor
_index Tensor
_source Bool
_accumulate
index_add_tltts
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Float
-> Tensor
index_add_tltts :: Tensor -> Int -> Tensor -> Tensor -> Float -> Tensor
index_add_tltts Tensor
_self Int
_dim Tensor
_index Tensor
_source Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.index_add_tltts) Tensor
_self Int
_dim Tensor
_index Tensor
_source Float
_alpha
index_add_tntts
:: Tensor
-> Dimname
-> Tensor
-> Tensor
-> Float
-> Tensor
index_add_tntts :: Tensor -> Dimname -> Tensor -> Tensor -> Float -> Tensor
index_add_tntts Tensor
_self Dimname
_dim Tensor
_index Tensor
_source Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.index_add_tntts) Tensor
_self Dimname
_dim Tensor
_index Tensor
_source Float
_alpha
index_reduce
:: Tensor
-> Int
-> Tensor
-> Tensor
-> String
-> Bool
-> Tensor
index_reduce :: Tensor -> Int -> Tensor -> Tensor -> String -> Bool -> Tensor
index_reduce Tensor
_self Int
_dim Tensor
_index Tensor
_source String
_reduce Bool
_include_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> String -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
ATen.index_reduce_tlttsb) Tensor
_self Int
_dim Tensor
_index Tensor
_source String
_reduce Bool
_include_self
indexFillScalar
:: Tensor
-> Int
-> Tensor
-> Float
-> Tensor
indexFillScalar :: Tensor -> Int -> Tensor -> Float -> Tensor
indexFillScalar Tensor
_self Int
_dim Tensor
_index Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.index_fill_tlts) Tensor
_self Int
_dim Tensor
_index Float
_value
indexFill
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Tensor
indexFill :: Tensor -> Int -> Tensor -> Tensor -> Tensor
indexFill Tensor
_self Int
_dim Tensor
_index Tensor
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.index_fill_tltt) Tensor
_self Int
_dim Tensor
_index Tensor
_value
indexFillScalarWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Float
-> Tensor
indexFillScalarWithDimname :: Tensor -> Dimname -> Tensor -> Float -> Tensor
indexFillScalarWithDimname Tensor
_self Dimname
_dim Tensor
_index Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.index_fill_tnts) Tensor
_self Dimname
_dim Tensor
_index Float
_value
indexFillWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Tensor
-> Tensor
indexFillWithDimname :: Tensor -> Dimname -> Tensor -> Tensor -> Tensor
indexFillWithDimname Tensor
_self Dimname
_dim Tensor
_index Tensor
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.index_fill_tntt) Tensor
_self Dimname
_dim Tensor
_index Tensor
_value
scatter
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Tensor
scatter :: Tensor -> Int -> Tensor -> Tensor -> Tensor
scatter Tensor
_self Int
_dim Tensor
_index Tensor
_src = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.scatter_tltt) Tensor
_self Int
_dim Tensor
_index Tensor
_src
scatterScalar
:: Tensor
-> Int
-> Tensor
-> Float
-> Tensor
scatterScalar :: Tensor -> Int -> Tensor -> Float -> Tensor
scatterScalar Tensor
_self Int
_dim Tensor
_index Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.scatter_tlts) Tensor
_self Int
_dim Tensor
_index Float
_value
scatter_tltts
:: Tensor
-> Int
-> Tensor
-> Tensor
-> String
-> Tensor
scatter_tltts :: Tensor -> Int -> Tensor -> Tensor -> String -> Tensor
scatter_tltts Tensor
_self Int
_dim Tensor
_index Tensor
_src String
_reduce = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.scatter_tltts) Tensor
_self Int
_dim Tensor
_index Tensor
_src String
_reduce
scatter_tltss
:: Tensor
-> Int
-> Tensor
-> Float
-> String
-> Tensor
scatter_tltss :: Tensor -> Int -> Tensor -> Float -> String -> Tensor
scatter_tltss Tensor
_self Int
_dim Tensor
_index Float
_value String
_reduce = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Float -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.scatter_tltss) Tensor
_self Int
_dim Tensor
_index Float
_value String
_reduce
scatterWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Tensor
-> Tensor
scatterWithDimname :: Tensor -> Dimname -> Tensor -> Tensor -> Tensor
scatterWithDimname Tensor
_self Dimname
_dim Tensor
_index Tensor
_src = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.scatter_tntt) Tensor
_self Dimname
_dim Tensor
_index Tensor
_src
scatterScalarWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Float
-> Tensor
scatterScalarWithDimname :: Tensor -> Dimname -> Tensor -> Float -> Tensor
scatterScalarWithDimname Tensor
_self Dimname
_dim Tensor
_index Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.scatter_tnts) Tensor
_self Dimname
_dim Tensor
_index Float
_value
scatterAdd
:: Tensor
-> Int
-> Tensor
-> Tensor
-> Tensor
scatterAdd :: Tensor -> Int -> Tensor -> Tensor -> Tensor
scatterAdd Tensor
_self Int
_dim Tensor
_index Tensor
_src = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.scatter_add_tltt) Tensor
_self Int
_dim Tensor
_index Tensor
_src
scatterAddWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Tensor
-> Tensor
scatterAddWithDimname :: Tensor -> Dimname -> Tensor -> Tensor -> Tensor
scatterAddWithDimname Tensor
_self Dimname
_dim Tensor
_index Tensor
_src = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.scatter_add_tntt) Tensor
_self Dimname
_dim Tensor
_index Tensor
_src
scatter_reduce
:: Tensor
-> Int
-> Tensor
-> Tensor
-> String
-> Bool
-> Tensor
scatter_reduce :: Tensor -> Int -> Tensor -> Tensor -> String -> Bool -> Tensor
scatter_reduce Tensor
_self Int
_dim Tensor
_index Tensor
_src String
_reduce Bool
_include_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Tensor -> String -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
ATen.scatter_reduce_tlttsb) Tensor
_self Int
_dim Tensor
_index Tensor
_src String
_reduce Bool
_include_self
bitwise_and_ts
:: Tensor
-> Float
-> Tensor
bitwise_and_ts :: Tensor -> Float -> Tensor
bitwise_and_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.bitwise_and_ts) Tensor
_self Float
_other
bitwise_and_st
:: Float
-> Tensor
-> Tensor
bitwise_and_st :: Float -> Tensor -> Tensor
bitwise_and_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_and_st) Float
_self Tensor
_other
bitwise_and_tt
:: Tensor
-> Tensor
-> Tensor
bitwise_and_tt :: Tensor -> Tensor -> Tensor
bitwise_and_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_and_tt) Tensor
_self Tensor
_other
bitwise_or_ts
:: Tensor
-> Float
-> Tensor
bitwise_or_ts :: Tensor -> Float -> Tensor
bitwise_or_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.bitwise_or_ts) Tensor
_self Float
_other
bitwise_or_st
:: Float
-> Tensor
-> Tensor
bitwise_or_st :: Float -> Tensor -> Tensor
bitwise_or_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_or_st) Float
_self Tensor
_other
bitwise_or_tt
:: Tensor
-> Tensor
-> Tensor
bitwise_or_tt :: Tensor -> Tensor -> Tensor
bitwise_or_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_or_tt) Tensor
_self Tensor
_other
bitwiseXorScalar
:: Tensor
-> Float
-> Tensor
bitwiseXorScalar :: Tensor -> Float -> Tensor
bitwiseXorScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.bitwise_xor_ts) Tensor
_self Float
_other
bitwise_xor_st
:: Float
-> Tensor
-> Tensor
bitwise_xor_st :: Float -> Tensor -> Tensor
bitwise_xor_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_xor_st) Float
_self Tensor
_other
bitwiseXor
:: Tensor
-> Tensor
-> Tensor
bitwiseXor :: Tensor -> Tensor -> Tensor
bitwiseXor Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_xor_tt) Tensor
_self Tensor
_other
bitwise_left_shift_tt
:: Tensor
-> Tensor
-> Tensor
bitwise_left_shift_tt :: Tensor -> Tensor -> Tensor
bitwise_left_shift_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_left_shift_tt) Tensor
_self Tensor
_other
bitwise_left_shift_ts
:: Tensor
-> Float
-> Tensor
bitwise_left_shift_ts :: Tensor -> Float -> Tensor
bitwise_left_shift_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.bitwise_left_shift_ts) Tensor
_self Float
_other
bitwise_left_shift_st
:: Float
-> Tensor
-> Tensor
bitwise_left_shift_st :: Float -> Tensor -> Tensor
bitwise_left_shift_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_left_shift_st) Float
_self Tensor
_other
bitwise_right_shift_tt
:: Tensor
-> Tensor
-> Tensor
bitwise_right_shift_tt :: Tensor -> Tensor -> Tensor
bitwise_right_shift_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_right_shift_tt) Tensor
_self Tensor
_other
bitwise_right_shift_ts
:: Tensor
-> Float
-> Tensor
bitwise_right_shift_ts :: Tensor -> Float -> Tensor
bitwise_right_shift_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.bitwise_right_shift_ts) Tensor
_self Float
_other
bitwise_right_shift_st
:: Float
-> Tensor
-> Tensor
bitwise_right_shift_st :: Float -> Tensor -> Tensor
bitwise_right_shift_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.bitwise_right_shift_st) Float
_self Tensor
_other
addbmm
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Float
-> Tensor
addbmm :: Tensor -> Tensor -> Tensor -> Float -> Float -> Tensor
addbmm Tensor
_self Tensor
_batch1 Tensor
_batch2 Float
_beta Float
_alpha = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.addbmm_tttss) Tensor
_self Tensor
_batch1 Tensor
_batch2 Float
_beta Float
_alpha
diag
:: Tensor
-> Int
-> Tensor
diag :: Tensor -> Int -> Tensor
diag Tensor
_self Int
_diagonal = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.diag_tl) Tensor
_self Int
_diagonal
cross
:: Tensor
-> Tensor
-> Int
-> Tensor
cross :: Tensor -> Tensor -> Int -> Tensor
cross Tensor
_self Tensor
_other Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.cross_ttl) Tensor
_self Tensor
_other Int
_dim
triu
:: Tensor
-> Int
-> Tensor
triu :: Tensor -> Int -> Tensor
triu Tensor
_self Int
_diagonal = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.triu_tl) Tensor
_self Int
_diagonal
tril
:: Tensor
-> Int
-> Tensor
tril :: Tensor -> Int -> Tensor
tril Tensor
_self Int
_diagonal = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.tril_tl) Tensor
_self Int
_diagonal
trace
:: Tensor
-> Tensor
trace :: Tensor -> Tensor
trace Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.trace_t) Tensor
_self
neScalar
:: Tensor
-> Float
-> Tensor
neScalar :: Tensor -> Float -> Tensor
neScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.ne_ts) Tensor
_self Float
_other
ne
:: Tensor
-> Tensor
-> Tensor
ne :: Tensor -> Tensor -> Tensor
ne Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ne_tt) Tensor
_self Tensor
_other
not_equal_ts
:: Tensor
-> Float
-> Tensor
not_equal_ts :: Tensor -> Float -> Tensor
not_equal_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.not_equal_ts) Tensor
_self Float
_other
not_equal_tt
:: Tensor
-> Tensor
-> Tensor
not_equal_tt :: Tensor -> Tensor -> Tensor
not_equal_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.not_equal_tt) Tensor
_self Tensor
_other
eqScalar
:: Tensor
-> Float
-> Tensor
eqScalar :: Tensor -> Float -> Tensor
eqScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.eq_ts) Tensor
_self Float
_other
eq
:: Tensor
-> Tensor
-> Tensor
eq :: Tensor -> Tensor -> Tensor
eq Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.eq_tt) Tensor
_self Tensor
_other
geScalar
:: Tensor
-> Float
-> Tensor
geScalar :: Tensor -> Float -> Tensor
geScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.ge_ts) Tensor
_self Float
_other
ge
:: Tensor
-> Tensor
-> Tensor
ge :: Tensor -> Tensor -> Tensor
ge Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ge_tt) Tensor
_self Tensor
_other
greater_equal_ts
:: Tensor
-> Float
-> Tensor
greater_equal_ts :: Tensor -> Float -> Tensor
greater_equal_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.greater_equal_ts) Tensor
_self Float
_other
greater_equal_tt
:: Tensor
-> Tensor
-> Tensor
greater_equal_tt :: Tensor -> Tensor -> Tensor
greater_equal_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.greater_equal_tt) Tensor
_self Tensor
_other
leScalar
:: Tensor
-> Float
-> Tensor
leScalar :: Tensor -> Float -> Tensor
leScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.le_ts) Tensor
_self Float
_other
le
:: Tensor
-> Tensor
-> Tensor
le :: Tensor -> Tensor -> Tensor
le Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.le_tt) Tensor
_self Tensor
_other
less_equal_ts
:: Tensor
-> Float
-> Tensor
less_equal_ts :: Tensor -> Float -> Tensor
less_equal_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.less_equal_ts) Tensor
_self Float
_other
less_equal_tt
:: Tensor
-> Tensor
-> Tensor
less_equal_tt :: Tensor -> Tensor -> Tensor
less_equal_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.less_equal_tt) Tensor
_self Tensor
_other
gtScalar
:: Tensor
-> Float
-> Tensor
gtScalar :: Tensor -> Float -> Tensor
gtScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.gt_ts) Tensor
_self Float
_other
gt
:: Tensor
-> Tensor
-> Tensor
gt :: Tensor -> Tensor -> Tensor
gt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.gt_tt) Tensor
_self Tensor
_other
greater_ts
:: Tensor
-> Float
-> Tensor
greater_ts :: Tensor -> Float -> Tensor
greater_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.greater_ts) Tensor
_self Float
_other
greater_tt
:: Tensor
-> Tensor
-> Tensor
greater_tt :: Tensor -> Tensor -> Tensor
greater_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.greater_tt) Tensor
_self Tensor
_other
ltScalar
:: Tensor
-> Float
-> Tensor
ltScalar :: Tensor -> Float -> Tensor
ltScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.lt_ts) Tensor
_self Float
_other
lt
:: Tensor
-> Tensor
-> Tensor
lt :: Tensor -> Tensor -> Tensor
lt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lt_tt) Tensor
_self Tensor
_other
less_ts
:: Tensor
-> Float
-> Tensor
less_ts :: Tensor -> Float -> Tensor
less_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.less_ts) Tensor
_self Float
_other
less_tt
:: Tensor
-> Tensor
-> Tensor
less_tt :: Tensor -> Tensor -> Tensor
less_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.less_tt) Tensor
_self Tensor
_other
take
:: Tensor
-> Tensor
-> Tensor
take :: Tensor -> Tensor -> Tensor
take Tensor
_self Tensor
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.take_tt) Tensor
_self Tensor
_index
take_along_dim
:: Tensor
-> Tensor
-> Int
-> Tensor
take_along_dim :: Tensor -> Tensor -> Int -> Tensor
take_along_dim Tensor
_self Tensor
_indices Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.take_along_dim_ttl) Tensor
_self Tensor
_indices Int
_dim
indexSelect
:: Tensor
-> Int
-> Tensor
-> Tensor
indexSelect :: Tensor -> Int -> Tensor -> Tensor
indexSelect Tensor
_self Int
_dim Tensor
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.index_select_tlt) Tensor
_self Int
_dim Tensor
_index
indexSelectWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Tensor
indexSelectWithDimname :: Tensor -> Dimname -> Tensor -> Tensor
indexSelectWithDimname Tensor
_self Dimname
_dim Tensor
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.index_select_tnt) Tensor
_self Dimname
_dim Tensor
_index
masked_select
:: Tensor
-> Tensor
-> Tensor
masked_select :: Tensor -> Tensor -> Tensor
masked_select Tensor
_self Tensor
_mask = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.masked_select_tt) Tensor
_self Tensor
_mask
nonzero
:: Tensor
-> Tensor
nonzero :: Tensor -> Tensor
nonzero Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.nonzero_t) Tensor
_self
nonzero_numpy
:: Tensor
-> [Tensor]
nonzero_numpy :: Tensor -> [Tensor]
nonzero_numpy Tensor
_self = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr TensorList))
-> Tensor -> IO [Tensor]
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr TensorList)
ATen.nonzero_numpy_t) Tensor
_self
argwhere
:: Tensor
-> Tensor
argwhere :: Tensor -> Tensor
argwhere Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.argwhere_t) Tensor
_self
gather
:: Tensor
-> Int
-> Tensor
-> Bool
-> Tensor
gather :: Tensor -> Int -> Tensor -> Bool -> Tensor
gather Tensor
_self Int
_dim Tensor
_index Bool
_sparse_grad = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.gather_tltb) Tensor
_self Int
_dim Tensor
_index Bool
_sparse_grad
gatherWithDimname
:: Tensor
-> Dimname
-> Tensor
-> Bool
-> Tensor
gatherWithDimname :: Tensor -> Dimname -> Tensor -> Bool -> Tensor
gatherWithDimname Tensor
_self Dimname
_dim Tensor
_index Bool
_sparse_grad = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
ATen.gather_tntb) Tensor
_self Dimname
_dim Tensor
_index Bool
_sparse_grad
addcmul
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
addcmul :: Tensor -> Tensor -> Tensor -> Float -> Tensor
addcmul Tensor
_self Tensor
_tensor1 Tensor
_tensor2 Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.addcmul_ttts) Tensor
_self Tensor
_tensor1 Tensor
_tensor2 Float
_value
addcdiv
:: Tensor
-> Tensor
-> Tensor
-> Float
-> Tensor
addcdiv :: Tensor -> Tensor -> Tensor -> Float -> Tensor
addcdiv Tensor
_self Tensor
_tensor1 Tensor
_tensor2 Float
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.addcdiv_ttts) Tensor
_self Tensor
_tensor1 Tensor
_tensor2 Float
_value
cross_entropy_loss
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Double
-> Tensor
cross_entropy_loss :: Tensor -> Tensor -> Tensor -> Int -> Int -> Double -> Tensor
cross_entropy_loss Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index Double
_label_smoothing = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.cross_entropy_loss_tttlld) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index Double
_label_smoothing
triangular_solve
:: Tensor
-> Tensor
-> Bool
-> Bool
-> Bool
-> (Tensor,Tensor)
triangular_solve :: Tensor -> Tensor -> Bool -> Bool -> Bool -> (Tensor, Tensor)
triangular_solve Tensor
_self Tensor
_A Bool
_upper Bool
_transpose Bool
_unitriangular = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Bool -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.triangular_solve_ttbbb) Tensor
_self Tensor
_A Bool
_upper Bool
_transpose Bool
_unitriangular
linalg_solve_triangular
:: Tensor
-> Tensor
-> Bool
-> Bool
-> Bool
-> Tensor
linalg_solve_triangular :: Tensor -> Tensor -> Bool -> Bool -> Bool -> Tensor
linalg_solve_triangular Tensor
_self Tensor
_B Bool
_upper Bool
_left Bool
_unitriangular = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.linalg_solve_triangular_ttbbb) Tensor
_self Tensor
_B Bool
_upper Bool
_left Bool
_unitriangular
linalg_vander
:: Tensor
-> Int
-> Tensor
linalg_vander :: Tensor -> Int -> Tensor
linalg_vander Tensor
_x Int
_N = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.linalg_vander_tl) Tensor
_x Int
_N
svd
:: Tensor
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
svd :: Tensor -> Bool -> Bool -> (Tensor, Tensor, Tensor)
svd Tensor
_self Bool
_some Bool
_compute_uv = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Bool -> Bool -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.svd_tbb) Tensor
_self Bool
_some Bool
_compute_uv
swapaxes
:: Tensor
-> Int
-> Int
-> Tensor
swapaxes :: Tensor -> Int -> Int -> Tensor
swapaxes Tensor
_self Int
_axis0 Int
_axis1 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.swapaxes_tll) Tensor
_self Int
_axis0 Int
_axis1
swapdims
:: Tensor
-> Int
-> Int
-> Tensor
swapdims :: Tensor -> Int -> Int -> Tensor
swapdims Tensor
_self Int
_dim0 Int
_dim1 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.swapdims_tll) Tensor
_self Int
_dim0 Int
_dim1
cholesky
:: Tensor
-> Bool
-> Tensor
cholesky :: Tensor -> Bool -> Tensor
cholesky Tensor
_self Bool
_upper = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.cholesky_tb) Tensor
_self Bool
_upper
cholesky_solve
:: Tensor
-> Tensor
-> Bool
-> Tensor
cholesky_solve :: Tensor -> Tensor -> Bool -> Tensor
cholesky_solve Tensor
_self Tensor
_input2 Bool
_upper = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.cholesky_solve_ttb) Tensor
_self Tensor
_input2 Bool
_upper
cholesky_inverse
:: Tensor
-> Bool
-> Tensor
cholesky_inverse :: Tensor -> Bool -> Tensor
cholesky_inverse Tensor
_self Bool
_upper = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.cholesky_inverse_tb) Tensor
_self Bool
_upper
qr
:: Tensor
-> Bool
-> (Tensor,Tensor)
qr :: Tensor -> Bool -> (Tensor, Tensor)
qr Tensor
_self Bool
_some = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.qr_tb) Tensor
_self Bool
_some
geqrf
:: Tensor
-> (Tensor,Tensor)
geqrf :: Tensor -> (Tensor, Tensor)
geqrf Tensor
_self = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> IO (Tensor, Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.geqrf_t) Tensor
_self
orgqr
:: Tensor
-> Tensor
-> Tensor
orgqr :: Tensor -> Tensor -> Tensor
orgqr Tensor
_self Tensor
_input2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.orgqr_tt) Tensor
_self Tensor
_input2
ormqr
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Bool
-> Tensor
ormqr :: Tensor -> Tensor -> Tensor -> Bool -> Bool -> Tensor
ormqr Tensor
_self Tensor
_input2 Tensor
_input3 Bool
_left Bool
_transpose = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.ormqr_tttbb) Tensor
_self Tensor
_input2 Tensor
_input3 Bool
_left Bool
_transpose
lu_solve
:: Tensor
-> Tensor
-> Tensor
-> Tensor
lu_solve :: Tensor -> Tensor -> Tensor -> Tensor
lu_solve Tensor
_self Tensor
_LU_data Tensor
_LU_pivots = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lu_solve_ttt) Tensor
_self Tensor
_LU_data Tensor
_LU_pivots
lu_unpack
:: Tensor
-> Tensor
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
lu_unpack :: Tensor -> Tensor -> Bool -> Bool -> (Tensor, Tensor, Tensor)
lu_unpack Tensor
_LU_data Tensor
_LU_pivots Bool
_unpack_data Bool
_unpack_pivots = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Tensor -> Bool -> Bool -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.lu_unpack_ttbb) Tensor
_LU_data Tensor
_LU_pivots Bool
_unpack_data Bool
_unpack_pivots
lgamma
:: Tensor
-> Tensor
lgamma :: Tensor -> Tensor
lgamma Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lgamma_t) Tensor
_self
digamma
:: Tensor
-> Tensor
digamma :: Tensor -> Tensor
digamma Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.digamma_t) Tensor
_self
polygamma
:: Int
-> Tensor
-> Tensor
polygamma :: Int -> Tensor -> Tensor
polygamma Int
_n Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((Int64 -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Int -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Int64 -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.polygamma_lt) Int
_n Tensor
_self
erfinv
:: Tensor
-> Tensor
erfinv :: Tensor -> Tensor
erfinv Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.erfinv_t) Tensor
_self
i0
:: Tensor
-> Tensor
i0 :: Tensor -> Tensor
i0 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.i0_t) Tensor
_self
sign
:: Tensor
-> Tensor
sign :: Tensor -> Tensor
sign Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.sign_t) Tensor
_self
signbit
:: Tensor
-> Tensor
signbit :: Tensor -> Tensor
signbit Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.signbit_t) Tensor
_self
dist
:: Tensor
-> Tensor
-> Float
-> Tensor
dist :: Tensor -> Tensor -> Float -> Tensor
dist Tensor
_self Tensor
_other Float
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.dist_tts) Tensor
_self Tensor
_other Float
_p
atan2
:: Tensor
-> Tensor
-> Tensor
atan2 :: Tensor -> Tensor -> Tensor
atan2 Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.atan2_tt) Tensor
_self Tensor
_other
arctan2
:: Tensor
-> Tensor
-> Tensor
arctan2 :: Tensor -> Tensor -> Tensor
arctan2 Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.arctan2_tt) Tensor
_self Tensor
_other
lerpScalar
:: Tensor
-> Tensor
-> Float
-> Tensor
lerpScalar :: Tensor -> Tensor -> Float -> Tensor
lerpScalar Tensor
_self Tensor
_end Float
_weight = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.lerp_tts) Tensor
_self Tensor
_end Float
_weight
lerp
:: Tensor
-> Tensor
-> Tensor
-> Tensor
lerp :: Tensor -> Tensor -> Tensor -> Tensor
lerp Tensor
_self Tensor
_end Tensor
_weight = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.lerp_ttt) Tensor
_self Tensor
_end Tensor
_weight
histc
:: Tensor
-> Int
-> Float
-> Float
-> Tensor
histc :: Tensor -> Int -> Float -> Float -> Tensor
histc Tensor
_self Int
_bins Float
_min Float
_max = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.histc_tlss) Tensor
_self Int
_bins Float
_min Float
_max
histogram_tttb
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> (Tensor,Tensor)
histogram_tttb :: Tensor -> Tensor -> Tensor -> Bool -> (Tensor, Tensor)
histogram_tttb Tensor
_self Tensor
_bins Tensor
_weight Bool
_density = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.histogram_tttb) Tensor
_self Tensor
_bins Tensor
_weight Bool
_density
histogram_tlatb
:: Tensor
-> Int
-> ([Double])
-> Tensor
-> Bool
-> (Tensor,Tensor)
histogram_tlatb :: Tensor -> Int -> [Double] -> Tensor -> Bool -> (Tensor, Tensor)
histogram_tlatb Tensor
_self Int
_bins [Double]
_range Tensor
_weight Bool
_density = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> ForeignPtr (StdVector CDouble)
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> Int
-> [Double]
-> Tensor
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> ForeignPtr (StdVector CDouble)
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.histogram_tlatb) Tensor
_self Int
_bins [Double]
_range Tensor
_weight Bool
_density
histogramdd_tlatb
:: Tensor
-> Int
-> ([Double])
-> Tensor
-> Bool
-> (Tensor,[Tensor])
histogramdd_tlatb :: Tensor -> Int -> [Double] -> Tensor -> Bool -> (Tensor, [Tensor])
histogramdd_tlatb Tensor
_self Int
_bins [Double]
_range Tensor
_weight Bool
_density = IO (Tensor, [Tensor]) -> (Tensor, [Tensor])
forall a. IO a -> a
unsafePerformIO (IO (Tensor, [Tensor]) -> (Tensor, [Tensor]))
-> IO (Tensor, [Tensor]) -> (Tensor, [Tensor])
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, TensorList))))
-> Tensor
-> Int
-> [Double]
-> Tensor
-> Bool
-> IO (Tensor, [Tensor])
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, TensorList)))
ATen.histogramdd_tlatb) Tensor
_self Int
_bins [Double]
_range Tensor
_weight Bool
_density
fmodScalar
:: Tensor
-> Float
-> Tensor
fmodScalar :: Tensor -> Float -> Tensor
fmodScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.fmod_ts) Tensor
_self Float
_other
fmod
:: Tensor
-> Tensor
-> Tensor
fmod :: Tensor -> Tensor -> Tensor
fmod Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fmod_tt) Tensor
_self Tensor
_other
hypot
:: Tensor
-> Tensor
-> Tensor
hypot :: Tensor -> Tensor -> Tensor
hypot Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.hypot_tt) Tensor
_self Tensor
_other
igamma
:: Tensor
-> Tensor
-> Tensor
igamma :: Tensor -> Tensor -> Tensor
igamma Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.igamma_tt) Tensor
_self Tensor
_other
igammac
:: Tensor
-> Tensor
-> Tensor
igammac :: Tensor -> Tensor -> Tensor
igammac Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.igammac_tt) Tensor
_self Tensor
_other
nextafter
:: Tensor
-> Tensor
-> Tensor
nextafter :: Tensor -> Tensor -> Tensor
nextafter Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.nextafter_tt) Tensor
_self Tensor
_other
remainderScalar
:: Tensor
-> Float
-> Tensor
remainderScalar :: Tensor -> Float -> Tensor
remainderScalar Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.remainder_ts) Tensor
_self Float
_other
remainder
:: Tensor
-> Tensor
-> Tensor
remainder :: Tensor -> Tensor -> Tensor
remainder Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.remainder_tt) Tensor
_self Tensor
_other
remainder_st
:: Float
-> Tensor
-> Tensor
remainder_st :: Float -> Tensor -> Tensor
remainder_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.remainder_st) Float
_self Tensor
_other
minAll
:: Tensor
-> Tensor
minAll :: Tensor -> Tensor
minAll Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.min_t) Tensor
_self
fmin
:: Tensor
-> Tensor
-> Tensor
fmin :: Tensor -> Tensor -> Tensor
fmin Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fmin_tt) Tensor
_self Tensor
_other
maxAll
:: Tensor
-> Tensor
maxAll :: Tensor -> Tensor
maxAll Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.max_t) Tensor
_self
fmax
:: Tensor
-> Tensor
-> Tensor
fmax :: Tensor -> Tensor -> Tensor
fmax Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.fmax_tt) Tensor
_self Tensor
_other
maximum
:: Tensor
-> Tensor
-> Tensor
maximum :: Tensor -> Tensor -> Tensor
maximum Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.maximum_tt) Tensor
_self Tensor
_other
max
:: Tensor
-> Tensor
-> Tensor
max :: Tensor -> Tensor -> Tensor
max Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.max_tt) Tensor
_self Tensor
_other
minimum
:: Tensor
-> Tensor
-> Tensor
minimum :: Tensor -> Tensor -> Tensor
minimum Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.minimum_tt) Tensor
_self Tensor
_other
min
:: Tensor
-> Tensor
-> Tensor
min :: Tensor -> Tensor -> Tensor
min Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.min_tt) Tensor
_self Tensor
_other
quantile_ttlbs
:: Tensor
-> Tensor
-> Int
-> Bool
-> String
-> Tensor
quantile_ttlbs :: Tensor -> Tensor -> Int -> Bool -> String -> Tensor
quantile_ttlbs Tensor
_self Tensor
_q Int
_dim Bool
_keepdim String
_interpolation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Bool -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.quantile_ttlbs) Tensor
_self Tensor
_q Int
_dim Bool
_keepdim String
_interpolation
quantile_tdlbs
:: Tensor
-> Double
-> Int
-> Bool
-> String
-> Tensor
quantile_tdlbs :: Tensor -> Double -> Int -> Bool -> String -> Tensor
quantile_tdlbs Tensor
_self Double
_q Int
_dim Bool
_keepdim String
_interpolation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Int -> Bool -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> CDouble
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.quantile_tdlbs) Tensor
_self Double
_q Int
_dim Bool
_keepdim String
_interpolation
nanquantile_ttlbs
:: Tensor
-> Tensor
-> Int
-> Bool
-> String
-> Tensor
nanquantile_ttlbs :: Tensor -> Tensor -> Int -> Bool -> String -> Tensor
nanquantile_ttlbs Tensor
_self Tensor
_q Int
_dim Bool
_keepdim String
_interpolation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Bool -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.nanquantile_ttlbs) Tensor
_self Tensor
_q Int
_dim Bool
_keepdim String
_interpolation
nanquantile_tdlbs
:: Tensor
-> Double
-> Int
-> Bool
-> String
-> Tensor
nanquantile_tdlbs :: Tensor -> Double -> Int -> Bool -> String -> Tensor
nanquantile_tdlbs Tensor
_self Double
_q Int
_dim Bool
_keepdim String
_interpolation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Int -> Bool -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> CDouble
-> Int64
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.nanquantile_tdlbs) Tensor
_self Double
_q Int
_dim Bool
_keepdim String
_interpolation
sort
:: Tensor
-> Int
-> Bool
-> (Tensor,Tensor)
sort :: Tensor -> Int -> Bool -> (Tensor, Tensor)
sort Tensor
_self Int
_dim Bool
_descending = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.sort_tlb) Tensor
_self Int
_dim Bool
_descending
sort_tblb
:: Tensor
-> Bool
-> Int
-> Bool
-> (Tensor,Tensor)
sort_tblb :: Tensor -> Bool -> Int -> Bool -> (Tensor, Tensor)
sort_tblb Tensor
_self Bool
_stable Int
_dim Bool
_descending = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> Int -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CBool
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.sort_tblb) Tensor
_self Bool
_stable Int
_dim Bool
_descending
sortWithDimname
:: Tensor
-> Dimname
-> Bool
-> (Tensor,Tensor)
sortWithDimname :: Tensor -> Dimname -> Bool -> (Tensor, Tensor)
sortWithDimname Tensor
_self Dimname
_dim Bool
_descending = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.sort_tnb) Tensor
_self Dimname
_dim Bool
_descending
sort_tbnb
:: Tensor
-> Bool
-> Dimname
-> Bool
-> (Tensor,Tensor)
sort_tbnb :: Tensor -> Bool -> Dimname -> Bool -> (Tensor, Tensor)
sort_tbnb Tensor
_self Bool
_stable Dimname
_dim Bool
_descending = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> Dimname -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CBool
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.sort_tbnb) Tensor
_self Bool
_stable Dimname
_dim Bool
_descending
msort
:: Tensor
-> Tensor
msort :: Tensor -> Tensor
msort Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.msort_t) Tensor
_self
argsort
:: Tensor
-> Int
-> Bool
-> Tensor
argsort :: Tensor -> Int -> Bool -> Tensor
argsort Tensor
_self Int
_dim Bool
_descending = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.argsort_tlb) Tensor
_self Int
_dim Bool
_descending
argsort_tblb
:: Tensor
-> Bool
-> Int
-> Bool
-> Tensor
argsort_tblb :: Tensor -> Bool -> Int -> Bool -> Tensor
argsort_tblb Tensor
_self Bool
_stable Int
_dim Bool
_descending = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> Int64 -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CBool -> Int64 -> CBool -> IO (ForeignPtr Tensor)
ATen.argsort_tblb) Tensor
_self Bool
_stable Int
_dim Bool
_descending
argsortWithDimname
:: Tensor
-> Dimname
-> Bool
-> Tensor
argsortWithDimname :: Tensor -> Dimname -> Bool -> Tensor
argsortWithDimname Tensor
_self Dimname
_dim Bool
_descending = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Dimname -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Dimname -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Dimname -> CBool -> IO (ForeignPtr Tensor)
ATen.argsort_tnb) Tensor
_self Dimname
_dim Bool
_descending
topk
:: Tensor
-> Int
-> Int
-> Bool
-> Bool
-> (Tensor,Tensor)
topk :: Tensor -> Int -> Int -> Bool -> Bool -> (Tensor, Tensor)
topk Tensor
_self Int
_k Int
_dim Bool
_largest Bool
_sorted = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Int -> Int -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.topk_tllbb) Tensor
_self Int
_k Int
_dim Bool
_largest Bool
_sorted
all
:: Tensor
-> Tensor
all :: Tensor -> Tensor
all Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.all_t) Tensor
_self
any
:: Tensor
-> Tensor
any :: Tensor -> Tensor
any Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.any_t) Tensor
_self
renorm
:: Tensor
-> Float
-> Int
-> Float
-> Tensor
renorm :: Tensor -> Float -> Int -> Float -> Tensor
renorm Tensor
_self Float
_p Int
_dim Float
_maxnorm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> Int64
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Scalar
-> Int64
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.renorm_tsls) Tensor
_self Float
_p Int
_dim Float
_maxnorm
equal
:: Tensor
-> Tensor
-> Bool
equal :: Tensor -> Tensor -> Bool
equal Tensor
_self Tensor
_other = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool)
-> Tensor -> Tensor -> IO Bool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool
ATen.equal_tt) Tensor
_self Tensor
_other
pow
:: Tensor
-> Tensor
-> Tensor
pow :: Tensor -> Tensor -> Tensor
pow Tensor
_self Tensor
_exponent = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.pow_tt) Tensor
_self Tensor
_exponent
powScalar'
:: Float
-> Tensor
-> Tensor
powScalar' :: Float -> Tensor -> Tensor
powScalar' Float
_self Tensor
_exponent = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.pow_st) Float
_self Tensor
_exponent
powScalar
:: Tensor
-> Float
-> Tensor
powScalar :: Tensor -> Float -> Tensor
powScalar Tensor
_self Float
_exponent = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.pow_ts) Tensor
_self Float
_exponent
float_power_tt
:: Tensor
-> Tensor
-> Tensor
float_power_tt :: Tensor -> Tensor -> Tensor
float_power_tt Tensor
_self Tensor
_exponent = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.float_power_tt) Tensor
_self Tensor
_exponent
float_power_st
:: Float
-> Tensor
-> Tensor
float_power_st :: Float -> Tensor -> Tensor
float_power_st Float
_self Tensor
_exponent = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.float_power_st) Float
_self Tensor
_exponent
float_power_ts
:: Tensor
-> Float
-> Tensor
float_power_ts :: Tensor -> Float -> Tensor
float_power_ts Tensor
_self Float
_exponent = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.float_power_ts) Tensor
_self Float
_exponent
alias
:: Tensor
-> Tensor
alias :: Tensor -> Tensor
alias Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.alias_t) Tensor
_self
bucketize_ttbb
:: Tensor
-> Tensor
-> Bool
-> Bool
-> Tensor
bucketize_ttbb :: Tensor -> Tensor -> Bool -> Bool -> Tensor
bucketize_ttbb Tensor
_self Tensor
_boundaries Bool
_out_int32 Bool
_right = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.bucketize_ttbb) Tensor
_self Tensor
_boundaries Bool
_out_int32 Bool
_right
bucketize_stbb
:: Float
-> Tensor
-> Bool
-> Bool
-> Tensor
bucketize_stbb :: Float -> Tensor -> Bool -> Bool -> Tensor
bucketize_stbb Float
_self Tensor
_boundaries Bool
_out_int32 Bool
_right = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Scalar
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor)
ATen.bucketize_stbb) Float
_self Tensor
_boundaries Bool
_out_int32 Bool
_right
searchsorted_ttbbst
:: Tensor
-> Tensor
-> Bool
-> Bool
-> String
-> Tensor
-> Tensor
searchsorted_ttbbst :: Tensor -> Tensor -> Bool -> Bool -> String -> Tensor -> Tensor
searchsorted_ttbbst Tensor
_sorted_sequence Tensor
_self Bool
_out_int32 Bool
_right String
_side Tensor
_sorter = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Bool
-> Bool
-> String
-> Tensor
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.searchsorted_ttbbst) Tensor
_sorted_sequence Tensor
_self Bool
_out_int32 Bool
_right String
_side Tensor
_sorter
searchsorted_tsbbst
:: Tensor
-> Float
-> Bool
-> Bool
-> String
-> Tensor
-> Tensor
searchsorted_tsbbst :: Tensor -> Float -> Bool -> Bool -> String -> Tensor -> Tensor
searchsorted_tsbbst Tensor
_sorted_sequence Float
_self Bool
_out_int32 Bool
_right String
_side Tensor
_sorter = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> CBool
-> CBool
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Bool -> Bool -> String -> Tensor -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Scalar
-> CBool
-> CBool
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
ATen.searchsorted_tsbbst) Tensor
_sorted_sequence Float
_self Bool
_out_int32 Bool
_right String
_side Tensor
_sorter
mse_loss
:: Tensor
-> Tensor
-> Int
-> Tensor
mse_loss :: Tensor -> Tensor -> Int -> Tensor
mse_loss Tensor
_self Tensor
_target Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.mse_loss_ttl) Tensor
_self Tensor
_target Int
_reduction
l1_loss
:: Tensor
-> Tensor
-> Int
-> Tensor
l1_loss :: Tensor -> Tensor -> Int -> Tensor
l1_loss Tensor
_self Tensor
_target Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.l1_loss_ttl) Tensor
_self Tensor
_target Int
_reduction
multi_margin_loss
:: Tensor
-> Tensor
-> Float
-> Float
-> Tensor
-> Int
-> Tensor
multi_margin_loss :: Tensor -> Tensor -> Float -> Float -> Tensor -> Int -> Tensor
multi_margin_loss Tensor
_self Tensor
_target Float
_p Float
_margin Tensor
_weight Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Float -> Float -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
ATen.multi_margin_loss_ttsstl) Tensor
_self Tensor
_target Float
_p Float
_margin Tensor
_weight Int
_reduction
multilabel_margin_loss
:: Tensor
-> Tensor
-> Int
-> Tensor
multilabel_margin_loss :: Tensor -> Tensor -> Int -> Tensor
multilabel_margin_loss Tensor
_self Tensor
_target Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.multilabel_margin_loss_ttl) Tensor
_self Tensor
_target Int
_reduction
multilabel_margin_loss_forward
:: Tensor
-> Tensor
-> Int
-> (Tensor,Tensor)
multilabel_margin_loss_forward :: Tensor -> Tensor -> Int -> (Tensor, Tensor)
multilabel_margin_loss_forward Tensor
_self Tensor
_target Int
_reduction = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.multilabel_margin_loss_forward_ttl) Tensor
_self Tensor
_target Int
_reduction
nll_loss_nd
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Tensor
nll_loss_nd :: Tensor -> Tensor -> Tensor -> Int -> Int -> Tensor
nll_loss_nd Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.nll_loss_nd_tttll) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index
nll_loss
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Tensor
nll_loss :: Tensor -> Tensor -> Tensor -> Int -> Int -> Tensor
nll_loss Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.nll_loss_tttll) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index
nll_loss_forward
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> (Tensor,Tensor)
nll_loss_forward :: Tensor -> Tensor -> Tensor -> Int -> Int -> (Tensor, Tensor)
nll_loss_forward Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.nll_loss_forward_tttll) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index
nll_loss2d
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> Tensor
nll_loss2d :: Tensor -> Tensor -> Tensor -> Int -> Int -> Tensor
nll_loss2d Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
ATen.nll_loss2d_tttll) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index
nll_loss2d_forward
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Int
-> (Tensor,Tensor)
nll_loss2d_forward :: Tensor -> Tensor -> Tensor -> Int -> Int -> (Tensor, Tensor)
nll_loss2d_forward Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Tensor -> Int -> Int -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.nll_loss2d_forward_tttll) Tensor
_self Tensor
_target Tensor
_weight Int
_reduction Int
_ignore_index
smooth_l1_loss
:: Tensor
-> Tensor
-> Int
-> Double
-> Tensor
smooth_l1_loss :: Tensor -> Tensor -> Int -> Double -> Tensor
smooth_l1_loss Tensor
_self Tensor
_target Int
_reduction Double
_beta = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor)
ATen.smooth_l1_loss_ttld) Tensor
_self Tensor
_target Int
_reduction Double
_beta
huber_loss
:: Tensor
-> Tensor
-> Int
-> Double
-> Tensor
huber_loss :: Tensor -> Tensor -> Int -> Double -> Tensor
huber_loss Tensor
_self Tensor
_target Int
_reduction Double
_delta = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor)
ATen.huber_loss_ttld) Tensor
_self Tensor
_target Int
_reduction Double
_delta
soft_margin_loss
:: Tensor
-> Tensor
-> Int
-> Tensor
soft_margin_loss :: Tensor -> Tensor -> Int -> Tensor
soft_margin_loss Tensor
_self Tensor
_target Int
_reduction = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.soft_margin_loss_ttl) Tensor
_self Tensor
_target Int
_reduction
elu
:: Tensor
-> Float
-> Float
-> Float
-> Tensor
elu :: Tensor -> Float -> Float -> Float -> Tensor
elu Tensor
_self Float
_alpha Float
_scale Float
_input_scale = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.elu_tsss) Tensor
_self Float
_alpha Float
_scale Float
_input_scale
glu
:: Tensor
-> Int
-> Tensor
glu :: Tensor -> Int -> Tensor
glu Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.glu_tl) Tensor
_self Int
_dim
glu_jvp
:: Tensor
-> Tensor
-> Tensor
-> Int
-> Tensor
glu_jvp :: Tensor -> Tensor -> Tensor -> Int -> Tensor
glu_jvp Tensor
_glu Tensor
_x Tensor
_dx Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
ATen.glu_jvp_tttl) Tensor
_glu Tensor
_x Tensor
_dx Int
_dim
glu_backward_jvp
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Tensor
glu_backward_jvp :: Tensor -> Tensor -> Tensor -> Tensor -> Tensor -> Int -> Tensor
glu_backward_jvp Tensor
_grad_x Tensor
_grad_glu Tensor
_x Tensor
_dgrad_glu Tensor
_dx Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
ATen.glu_backward_jvp_tttttl) Tensor
_grad_x Tensor
_grad_glu Tensor
_x Tensor
_dgrad_glu Tensor
_dx Int
_dim
hardsigmoid
:: Tensor
-> Tensor
hardsigmoid :: Tensor -> Tensor
hardsigmoid Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.hardsigmoid_t) Tensor
_self
hardtanh
:: Tensor
-> Float
-> Float
-> Tensor
hardtanh :: Tensor -> Float -> Float -> Tensor
hardtanh Tensor
_self Float
_min_val Float
_max_val = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.hardtanh_tss) Tensor
_self Float
_min_val Float
_max_val
hardswish
:: Tensor
-> Tensor
hardswish :: Tensor -> Tensor
hardswish Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.hardswish_t) Tensor
_self
leaky_relu
:: Tensor
-> Float
-> Tensor
leaky_relu :: Tensor -> Float -> Tensor
leaky_relu Tensor
_self Float
_negative_slope = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.leaky_relu_ts) Tensor
_self Float
_negative_slope
log_sigmoid
:: Tensor
-> Tensor
log_sigmoid :: Tensor -> Tensor
log_sigmoid Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.log_sigmoid_t) Tensor
_self
log_sigmoid_forward
:: Tensor
-> (Tensor,Tensor)
log_sigmoid_forward :: Tensor -> (Tensor, Tensor)
log_sigmoid_forward Tensor
_self = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> IO (Tensor, Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.log_sigmoid_forward_t) Tensor
_self
softplus
:: Tensor
-> Float
-> Float
-> Tensor
softplus :: Tensor -> Float -> Float -> Tensor
softplus Tensor
_self Float
_beta Float
_threshold = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Float -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.softplus_tss) Tensor
_self Float
_beta Float
_threshold
softshrink
:: Tensor
-> Float
-> Tensor
softshrink :: Tensor -> Float -> Tensor
softshrink Tensor
_self Float
_lambd = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.softshrink_ts) Tensor
_self Float
_lambd
adaptive_avg_pool2d
:: Tensor
-> (Int,Int)
-> Tensor
adaptive_avg_pool2d :: Tensor -> (Int, Int) -> Tensor
adaptive_avg_pool2d Tensor
_self (Int, Int)
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.adaptive_avg_pool2d_tl) Tensor
_self (Int, Int)
_output_size
mkldnn_adaptive_avg_pool2d
:: Tensor
-> (Int,Int)
-> Tensor
mkldnn_adaptive_avg_pool2d :: Tensor -> (Int, Int) -> Tensor
mkldnn_adaptive_avg_pool2d Tensor
_self (Int, Int)
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.mkldnn_adaptive_avg_pool2d_tl) Tensor
_self (Int, Int)
_output_size
adaptive_avg_pool3d
:: Tensor
-> (Int,Int,Int)
-> Tensor
adaptive_avg_pool3d :: Tensor -> (Int, Int, Int) -> Tensor
adaptive_avg_pool3d Tensor
_self (Int, Int, Int)
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.adaptive_avg_pool3d_tl) Tensor
_self (Int, Int, Int)
_output_size
adaptive_max_pool2d
:: Tensor
-> (Int,Int)
-> (Tensor,Tensor)
adaptive_max_pool2d :: Tensor -> (Int, Int) -> (Tensor, Tensor)
adaptive_max_pool2d Tensor
_self (Int, Int)
_output_size = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> (Int, Int) -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.adaptive_max_pool2d_tl) Tensor
_self (Int, Int)
_output_size
adaptive_max_pool3d
:: Tensor
-> (Int,Int,Int)
-> (Tensor,Tensor)
adaptive_max_pool3d :: Tensor -> (Int, Int, Int) -> (Tensor, Tensor)
adaptive_max_pool3d Tensor
_self (Int, Int, Int)
_output_size = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> (Int, Int, Int) -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.adaptive_max_pool3d_tl) Tensor
_self (Int, Int, Int)
_output_size
avg_pool2d
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Bool
-> Bool
-> Int
-> Tensor
avg_pool2d :: Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> Bool
-> Int
-> Tensor
avg_pool2d Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding Bool
_ceil_mode Bool
_count_include_pad Int
_divisor_override = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> Bool
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr Tensor)
ATen.avg_pool2d_tlllbbl) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding Bool
_ceil_mode Bool
_count_include_pad Int
_divisor_override
avg_pool3d
:: Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Bool
-> Bool
-> Int
-> Tensor
avg_pool3d :: Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> Bool
-> Int
-> Tensor
avg_pool3d Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding Bool
_ceil_mode Bool
_count_include_pad Int
_divisor_override = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> Bool
-> Int
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr Tensor)
ATen.avg_pool3d_tlllbbl) Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding Bool
_ceil_mode Bool
_count_include_pad Int
_divisor_override
fractional_max_pool2d
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> Tensor
-> (Tensor,Tensor)
fractional_max_pool2d :: Tensor -> (Int, Int) -> (Int, Int) -> Tensor -> (Tensor, Tensor)
fractional_max_pool2d Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_output_size Tensor
_random_samples = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> Tensor
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.fractional_max_pool2d_tllt) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_output_size Tensor
_random_samples
fractional_max_pool3d
:: Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
-> (Tensor,Tensor)
fractional_max_pool3d :: Tensor
-> (Int, Int, Int) -> (Int, Int, Int) -> Tensor -> (Tensor, Tensor)
fractional_max_pool3d Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_output_size Tensor
_random_samples = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.fractional_max_pool3d_tllt) Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_output_size Tensor
_random_samples
max_pool2d_with_indices
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Bool
-> (Tensor,Tensor)
max_pool2d_with_indices :: Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> (Tensor, Tensor)
max_pool2d_with_indices Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.max_pool2d_with_indices_tllllb) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation Bool
_ceil_mode
max_pool3d_with_indices
:: Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Bool
-> (Tensor,Tensor)
max_pool3d_with_indices :: Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> (Tensor, Tensor)
max_pool3d_with_indices Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Bool
_ceil_mode = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Bool
-> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.max_pool3d_with_indices_tllllb) Tensor
_self (Int, Int, Int)
_kernel_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation Bool
_ceil_mode
max_unpool2d
:: Tensor
-> Tensor
-> (Int,Int)
-> Tensor
max_unpool2d :: Tensor -> Tensor -> (Int, Int) -> Tensor
max_unpool2d Tensor
_self Tensor
_indices (Int, Int)
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> (Int, Int) -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.max_unpool2d_ttl) Tensor
_self Tensor
_indices (Int, Int)
_output_size
max_unpool3d
:: Tensor
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
max_unpool3d :: Tensor
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
max_unpool3d Tensor
_self Tensor
_indices (Int, Int, Int)
_output_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.max_unpool3d_ttlll) Tensor
_self Tensor
_indices (Int, Int, Int)
_output_size (Int, Int, Int)
_stride (Int, Int, Int)
_padding
reflection_pad1d
:: Tensor
-> (Int,Int)
-> Tensor
reflection_pad1d :: Tensor -> (Int, Int) -> Tensor
reflection_pad1d Tensor
_self (Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.reflection_pad1d_tl) Tensor
_self (Int, Int)
_padding
reflection_pad2d
:: Tensor
-> (Int,Int,Int,Int)
-> Tensor
reflection_pad2d :: Tensor -> (Int, Int, Int, Int) -> Tensor
reflection_pad2d Tensor
_self (Int, Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int, Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.reflection_pad2d_tl) Tensor
_self (Int, Int, Int, Int)
_padding
reflection_pad3d
:: Tensor
-> (Int,Int,Int,Int,Int,Int)
-> Tensor
reflection_pad3d :: Tensor -> (Int, Int, Int, Int, Int, Int) -> Tensor
reflection_pad3d Tensor
_self (Int, Int, Int, Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int, Int, Int, Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.reflection_pad3d_tl) Tensor
_self (Int, Int, Int, Int, Int, Int)
_padding
replication_pad1d
:: Tensor
-> (Int,Int)
-> Tensor
replication_pad1d :: Tensor -> (Int, Int) -> Tensor
replication_pad1d Tensor
_self (Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.replication_pad1d_tl) Tensor
_self (Int, Int)
_padding
replication_pad2d
:: Tensor
-> (Int,Int,Int,Int)
-> Tensor
replication_pad2d :: Tensor -> (Int, Int, Int, Int) -> Tensor
replication_pad2d Tensor
_self (Int, Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int, Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.replication_pad2d_tl) Tensor
_self (Int, Int, Int, Int)
_padding
replication_pad3d
:: Tensor
-> (Int,Int,Int,Int,Int,Int)
-> Tensor
replication_pad3d :: Tensor -> (Int, Int, Int, Int, Int, Int) -> Tensor
replication_pad3d Tensor
_self (Int, Int, Int, Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int, Int, Int, Int, Int) -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.replication_pad3d_tl) Tensor
_self (Int, Int, Int, Int, Int, Int)
_padding
pad
:: Tensor
-> [Int]
-> String
-> Double
-> Tensor
pad :: Tensor -> [Int] -> String -> Double -> Tensor
pad Tensor
_self [Int]
_pad String
_mode Double
_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> String -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.pad_tlsd) Tensor
_self [Int]
_pad String
_mode Double
_value
upsample_linear1d_tlba
:: Tensor
-> [Int]
-> Bool
-> ([Double])
-> Tensor
upsample_linear1d_tlba :: Tensor -> [Int] -> Bool -> [Double] -> Tensor
upsample_linear1d_tlba Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Bool -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_linear1d_tlba) Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors
upsample_bilinear2d_tlba
:: Tensor
-> [Int]
-> Bool
-> ([Double])
-> Tensor
upsample_bilinear2d_tlba :: Tensor -> [Int] -> Bool -> [Double] -> Tensor
upsample_bilinear2d_tlba Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Bool -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_bilinear2d_tlba) Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors
upsample_trilinear3d_tlba
:: Tensor
-> [Int]
-> Bool
-> ([Double])
-> Tensor
upsample_trilinear3d_tlba :: Tensor -> [Int] -> Bool -> [Double] -> Tensor
upsample_trilinear3d_tlba Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Bool -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_trilinear3d_tlba) Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors
upsample_bicubic2d_tlba
:: Tensor
-> [Int]
-> Bool
-> ([Double])
-> Tensor
upsample_bicubic2d_tlba :: Tensor -> [Int] -> Bool -> [Double] -> Tensor
upsample_bicubic2d_tlba Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Bool -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_bicubic2d_tlba) Tensor
_input [Int]
_output_size Bool
_align_corners [Double]
_scale_factors
upsample_nearest1d_tla
:: Tensor
-> [Int]
-> ([Double])
-> Tensor
upsample_nearest1d_tla :: Tensor -> [Int] -> [Double] -> Tensor
upsample_nearest1d_tla Tensor
_input [Int]
_output_size [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_nearest1d_tla) Tensor
_input [Int]
_output_size [Double]
_scale_factors
upsample_nearest2d_tla
:: Tensor
-> [Int]
-> ([Double])
-> Tensor
upsample_nearest2d_tla :: Tensor -> [Int] -> [Double] -> Tensor
upsample_nearest2d_tla Tensor
_input [Int]
_output_size [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_nearest2d_tla) Tensor
_input [Int]
_output_size [Double]
_scale_factors
upsample_nearest3d_tla
:: Tensor
-> [Int]
-> ([Double])
-> Tensor
upsample_nearest3d_tla :: Tensor -> [Int] -> [Double] -> Tensor
upsample_nearest3d_tla Tensor
_input [Int]
_output_size [Double]
_scale_factors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> [Double] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
ATen.upsample_nearest3d_tla) Tensor
_input [Int]
_output_size [Double]
_scale_factors
upsample_bilinear2d_tlbdd
:: Tensor
-> (Int,Int)
-> Bool
-> Double
-> Double
-> Tensor
upsample_bilinear2d_tlbdd :: Tensor -> (Int, Int) -> Bool -> Double -> Double -> Tensor
upsample_bilinear2d_tlbdd Tensor
_self (Int, Int)
_output_size Bool
_align_corners Double
_scales_h Double
_scales_w = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> Bool -> Double -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.upsample_bilinear2d_tlbdd) Tensor
_self (Int, Int)
_output_size Bool
_align_corners Double
_scales_h Double
_scales_w
upsample_bicubic2d_tlbdd
:: Tensor
-> (Int,Int)
-> Bool
-> Double
-> Double
-> Tensor
upsample_bicubic2d_tlbdd :: Tensor -> (Int, Int) -> Bool -> Double -> Double -> Tensor
upsample_bicubic2d_tlbdd Tensor
_self (Int, Int)
_output_size Bool
_align_corners Double
_scales_h Double
_scales_w = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> Bool -> Double -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.upsample_bicubic2d_tlbdd) Tensor
_self (Int, Int)
_output_size Bool
_align_corners Double
_scales_h Double
_scales_w
upsample_trilinear3d_tlbddd
:: Tensor
-> (Int,Int,Int)
-> Bool
-> Double
-> Double
-> Double
-> Tensor
upsample_trilinear3d_tlbddd :: Tensor
-> (Int, Int, Int) -> Bool -> Double -> Double -> Double -> Tensor
upsample_trilinear3d_tlbddd Tensor
_self (Int, Int, Int)
_output_size Bool
_align_corners Double
_scales_d Double
_scales_h Double
_scales_w = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int, Int)
-> Bool
-> Double
-> Double
-> Double
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.upsample_trilinear3d_tlbddd) Tensor
_self (Int, Int, Int)
_output_size Bool
_align_corners Double
_scales_d Double
_scales_h Double
_scales_w
upsample_nearest2d_tldd
:: Tensor
-> (Int,Int)
-> Double
-> Double
-> Tensor
upsample_nearest2d_tldd :: Tensor -> (Int, Int) -> Double -> Double -> Tensor
upsample_nearest2d_tldd Tensor
_self (Int, Int)
_output_size Double
_scales_h Double
_scales_w = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor -> (Int, Int) -> Double -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.upsample_nearest2d_tldd) Tensor
_self (Int, Int)
_output_size Double
_scales_h Double
_scales_w
upsample_nearest3d_tlddd
:: Tensor
-> (Int,Int,Int)
-> Double
-> Double
-> Double
-> Tensor
upsample_nearest3d_tlddd :: Tensor -> (Int, Int, Int) -> Double -> Double -> Double -> Tensor
upsample_nearest3d_tlddd Tensor
_self (Int, Int, Int)
_output_size Double
_scales_d Double
_scales_h Double
_scales_w = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int, Int)
-> Double
-> Double
-> Double
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.upsample_nearest3d_tlddd) Tensor
_self (Int, Int, Int)
_output_size Double
_scales_d Double
_scales_h Double
_scales_w
slow_conv_transpose2d
:: Tensor
-> Tensor
-> (Int,Int)
-> Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Tensor
slow_conv_transpose2d :: Tensor
-> Tensor
-> (Int, Int)
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Tensor
slow_conv_transpose2d Tensor
_self Tensor
_weight (Int, Int)
_kernel_size Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_output_padding (Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int)
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.slow_conv_transpose2d_ttltllll) Tensor
_self Tensor
_weight (Int, Int)
_kernel_size Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_output_padding (Int, Int)
_dilation
slow_conv_transpose3d
:: Tensor
-> Tensor
-> (Int,Int,Int)
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
slow_conv_transpose3d :: Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
slow_conv_transpose3d Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_output_padding (Int, Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.slow_conv_transpose3d_ttltllll) Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_output_padding (Int, Int, Int)
_dilation
thnn_conv2d
:: Tensor
-> Tensor
-> (Int,Int)
-> Tensor
-> (Int,Int)
-> (Int,Int)
-> Tensor
thnn_conv2d :: Tensor
-> Tensor
-> (Int, Int)
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> Tensor
thnn_conv2d Tensor
_self Tensor
_weight (Int, Int)
_kernel_size Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int)
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.thnn_conv2d_ttltll) Tensor
_self Tensor
_weight (Int, Int)
_kernel_size Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding
conv_depthwise3d
:: Tensor
-> Tensor
-> (Int,Int,Int)
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
conv_depthwise3d :: Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
conv_depthwise3d Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.conv_depthwise3d_ttltlll) Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation
slow_conv3d
:: Tensor
-> Tensor
-> (Int,Int,Int)
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
slow_conv3d :: Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
slow_conv3d Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.slow_conv3d_ttltll) Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding
slow_conv3d_forward
:: Tensor
-> Tensor
-> (Int,Int,Int)
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
slow_conv3d_forward :: Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
slow_conv3d_forward Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.slow_conv3d_forward_ttltll) Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding
slow_conv_dilated2d
:: Tensor
-> Tensor
-> (Int,Int)
-> Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Tensor
slow_conv_dilated2d :: Tensor
-> Tensor
-> (Int, Int)
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Tensor
slow_conv_dilated2d Tensor
_self Tensor
_weight (Int, Int)
_kernel_size Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int)
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.slow_conv_dilated2d_ttltlll) Tensor
_self Tensor
_weight (Int, Int)
_kernel_size Tensor
_bias (Int, Int)
_stride (Int, Int)
_padding (Int, Int)
_dilation
slow_conv_dilated3d
:: Tensor
-> Tensor
-> (Int,Int,Int)
-> Tensor
-> (Int,Int,Int)
-> (Int,Int,Int)
-> (Int,Int,Int)
-> Tensor
slow_conv_dilated3d :: Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> Tensor
slow_conv_dilated3d Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> (Int, Int, Int)
-> Tensor
-> (Int, Int, Int)
-> (Int, Int, Int)
-> (Int, Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
cast7 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.slow_conv_dilated3d_ttltlll) Tensor
_self Tensor
_weight (Int, Int, Int)
_kernel_size Tensor
_bias (Int, Int, Int)
_stride (Int, Int, Int)
_padding (Int, Int, Int)
_dilation
col2im
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Tensor
col2im :: Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> Tensor
col2im Tensor
_self (Int, Int)
_output_size (Int, Int)
_kernel_size (Int, Int)
_dilation (Int, Int)
_padding (Int, Int)
_stride = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.col2im_tlllll) Tensor
_self (Int, Int)
_output_size (Int, Int)
_kernel_size (Int, Int)
_dilation (Int, Int)
_padding (Int, Int)
_stride
column_stack
:: [Tensor]
-> Tensor
column_stack :: [Tensor] -> Tensor
column_stack [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.column_stack_l) [Tensor]
_tensors
im2col
:: Tensor
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> (Int,Int)
-> Tensor
im2col :: Tensor
-> (Int, Int) -> (Int, Int) -> (Int, Int) -> (Int, Int) -> Tensor
im2col Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_dilation (Int, Int)
_padding (Int, Int)
_stride = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> (Int, Int)
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.im2col_tllll) Tensor
_self (Int, Int)
_kernel_size (Int, Int)
_dilation (Int, Int)
_padding (Int, Int)
_stride
isfinite
:: Tensor
-> Tensor
isfinite :: Tensor -> Tensor
isfinite Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.isfinite_t) Tensor
_self
isinf
:: Tensor
-> Tensor
isinf :: Tensor -> Tensor
isinf Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.isinf_t) Tensor
_self
isposinf
:: Tensor
-> Tensor
isposinf :: Tensor -> Tensor
isposinf Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.isposinf_t) Tensor
_self
isneginf
:: Tensor
-> Tensor
isneginf :: Tensor -> Tensor
isneginf Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.isneginf_t) Tensor
_self
special_entr
:: Tensor
-> Tensor
special_entr :: Tensor -> Tensor
special_entr Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_entr_t) Tensor
_self
special_ndtri
:: Tensor
-> Tensor
special_ndtri :: Tensor -> Tensor
special_ndtri Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_ndtri_t) Tensor
_self
special_log_ndtr
:: Tensor
-> Tensor
special_log_ndtr :: Tensor -> Tensor
special_log_ndtr Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_log_ndtr_t) Tensor
_self
special_expm1
:: Tensor
-> Tensor
special_expm1 :: Tensor -> Tensor
special_expm1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_expm1_t) Tensor
_self
special_exp2
:: Tensor
-> Tensor
special_exp2 :: Tensor -> Tensor
special_exp2 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_exp2_t) Tensor
_self
special_psi
:: Tensor
-> Tensor
special_psi :: Tensor -> Tensor
special_psi Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_psi_t) Tensor
_self
special_digamma
:: Tensor
-> Tensor
special_digamma :: Tensor -> Tensor
special_digamma Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_digamma_t) Tensor
_self
special_gammaln
:: Tensor
-> Tensor
special_gammaln :: Tensor -> Tensor
special_gammaln Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_gammaln_t) Tensor
_self
special_erf
:: Tensor
-> Tensor
special_erf :: Tensor -> Tensor
special_erf Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_erf_t) Tensor
_self
special_erfc
:: Tensor
-> Tensor
special_erfc :: Tensor -> Tensor
special_erfc Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_erfc_t) Tensor
_self
special_erfcx
:: Tensor
-> Tensor
special_erfcx :: Tensor -> Tensor
special_erfcx Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_erfcx_t) Tensor
_self
special_erfinv
:: Tensor
-> Tensor
special_erfinv :: Tensor -> Tensor
special_erfinv Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_erfinv_t) Tensor
_self
special_ndtr
:: Tensor
-> Tensor
special_ndtr :: Tensor -> Tensor
special_ndtr Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_ndtr_t) Tensor
_self
special_xlog1py_tt
:: Tensor
-> Tensor
-> Tensor
special_xlog1py_tt :: Tensor -> Tensor -> Tensor
special_xlog1py_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_xlog1py_tt) Tensor
_self Tensor
_other
special_xlog1py_st
:: Float
-> Tensor
-> Tensor
special_xlog1py_st :: Float -> Tensor -> Tensor
special_xlog1py_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_xlog1py_st) Float
_self Tensor
_other
special_xlog1py_ts
:: Tensor
-> Float
-> Tensor
special_xlog1py_ts :: Tensor -> Float -> Tensor
special_xlog1py_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_xlog1py_ts) Tensor
_self Float
_other
special_xlogy_tt
:: Tensor
-> Tensor
-> Tensor
special_xlogy_tt :: Tensor -> Tensor -> Tensor
special_xlogy_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_xlogy_tt) Tensor
_self Tensor
_other
special_xlogy_st
:: Float
-> Tensor
-> Tensor
special_xlogy_st :: Float -> Tensor -> Tensor
special_xlogy_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_xlogy_st) Float
_self Tensor
_other
special_xlogy_ts
:: Tensor
-> Float
-> Tensor
special_xlogy_ts :: Tensor -> Float -> Tensor
special_xlogy_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_xlogy_ts) Tensor
_self Float
_other
special_zeta_tt
:: Tensor
-> Tensor
-> Tensor
special_zeta_tt :: Tensor -> Tensor -> Tensor
special_zeta_tt Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_zeta_tt) Tensor
_self Tensor
_other
special_zeta_st
:: Float
-> Tensor
-> Tensor
special_zeta_st :: Float -> Tensor -> Tensor
special_zeta_st Float
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_zeta_st) Float
_self Tensor
_other
special_zeta_ts
:: Tensor
-> Float
-> Tensor
special_zeta_ts :: Tensor -> Float -> Tensor
special_zeta_ts Tensor
_self Float
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_zeta_ts) Tensor
_self Float
_other
special_i0
:: Tensor
-> Tensor
special_i0 :: Tensor -> Tensor
special_i0 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_i0_t) Tensor
_self
special_i0e
:: Tensor
-> Tensor
special_i0e :: Tensor -> Tensor
special_i0e Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_i0e_t) Tensor
_self
special_i1
:: Tensor
-> Tensor
special_i1 :: Tensor -> Tensor
special_i1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_i1_t) Tensor
_self
special_i1e
:: Tensor
-> Tensor
special_i1e :: Tensor -> Tensor
special_i1e Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_i1e_t) Tensor
_self
special_logit
:: Tensor
-> Double
-> Tensor
special_logit :: Tensor -> Double -> Tensor
special_logit Tensor
_self Double
_eps = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
ATen.special_logit_td) Tensor
_self Double
_eps
special_polygamma
:: Int
-> Tensor
-> Tensor
special_polygamma :: Int -> Tensor -> Tensor
special_polygamma Int
_n Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((Int64 -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Int -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Int64 -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_polygamma_lt) Int
_n Tensor
_self
special_logsumexp
:: Tensor
-> Int
-> Bool
-> Tensor
special_logsumexp :: Tensor -> Int -> Bool -> Tensor
special_logsumexp Tensor
_self Int
_dim Bool
_keepdim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.special_logsumexp_tlb) Tensor
_self Int
_dim Bool
_keepdim
special_expit
:: Tensor
-> Tensor
special_expit :: Tensor -> Tensor
special_expit Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_expit_t) Tensor
_self
special_sinc
:: Tensor
-> Tensor
special_sinc :: Tensor -> Tensor
special_sinc Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_sinc_t) Tensor
_self
special_round
:: Tensor
-> Int
-> Tensor
special_round :: Tensor -> Int -> Tensor
special_round Tensor
_self Int
_decimals = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.special_round_tl) Tensor
_self Int
_decimals
special_log1p
:: Tensor
-> Tensor
special_log1p :: Tensor -> Tensor
special_log1p Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_log1p_t) Tensor
_self
special_log_softmax
:: Tensor
-> Int
-> DType
-> Tensor
special_log_softmax :: Tensor -> Int -> DType -> Tensor
special_log_softmax Tensor
_self Int
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.special_log_softmax_tls) Tensor
_self Int
_dim DType
_dtype
special_gammainc
:: Tensor
-> Tensor
-> Tensor
special_gammainc :: Tensor -> Tensor -> Tensor
special_gammainc Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_gammainc_tt) Tensor
_self Tensor
_other
special_gammaincc
:: Tensor
-> Tensor
-> Tensor
special_gammaincc :: Tensor -> Tensor -> Tensor
special_gammaincc Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_gammaincc_tt) Tensor
_self Tensor
_other
special_multigammaln
:: Tensor
-> Int
-> Tensor
special_multigammaln :: Tensor -> Int -> Tensor
special_multigammaln Tensor
_self Int
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.special_multigammaln_tl) Tensor
_self Int
_p
special_softmax
:: Tensor
-> Int
-> DType
-> Tensor
special_softmax :: Tensor -> Int -> DType -> Tensor
special_softmax Tensor
_self Int
_dim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> Int64 -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.special_softmax_tls) Tensor
_self Int
_dim DType
_dtype
fft_fft
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_fft :: Tensor -> Int -> Int -> String -> Tensor
fft_fft Tensor
_self Int
_n Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.fft_fft_tlls) Tensor
_self Int
_n Int
_dim String
_norm
fft_ifft
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_ifft :: Tensor -> Int -> Int -> String -> Tensor
fft_ifft Tensor
_self Int
_n Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.fft_ifft_tlls) Tensor
_self Int
_n Int
_dim String
_norm
fft_rfft
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_rfft :: Tensor -> Int -> Int -> String -> Tensor
fft_rfft Tensor
_self Int
_n Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.fft_rfft_tlls) Tensor
_self Int
_n Int
_dim String
_norm
fft_irfft
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_irfft :: Tensor -> Int -> Int -> String -> Tensor
fft_irfft Tensor
_self Int
_n Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.fft_irfft_tlls) Tensor
_self Int
_n Int
_dim String
_norm
fft_hfft
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_hfft :: Tensor -> Int -> Int -> String -> Tensor
fft_hfft Tensor
_self Int
_n Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.fft_hfft_tlls) Tensor
_self Int
_n Int
_dim String
_norm
fft_ihfft
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_ihfft :: Tensor -> Int -> Int -> String -> Tensor
fft_ihfft Tensor
_self Int
_n Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.fft_ihfft_tlls) Tensor
_self Int
_n Int
_dim String
_norm
fft_fft2
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_fft2 :: Tensor -> Int -> Int -> String -> Tensor
fft_fft2 Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_fft2_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_ifft2
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_ifft2 :: Tensor -> Int -> Int -> String -> Tensor
fft_ifft2 Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_ifft2_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_rfft2
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_rfft2 :: Tensor -> Int -> Int -> String -> Tensor
fft_rfft2 Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_rfft2_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_irfft2
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_irfft2 :: Tensor -> Int -> Int -> String -> Tensor
fft_irfft2 Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_irfft2_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_hfft2
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_hfft2 :: Tensor -> Int -> Int -> String -> Tensor
fft_hfft2 Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_hfft2_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_ihfft2
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_ihfft2 :: Tensor -> Int -> Int -> String -> Tensor
fft_ihfft2 Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_ihfft2_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_fftn
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_fftn :: Tensor -> Int -> Int -> String -> Tensor
fft_fftn Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_fftn_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_ifftn
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_ifftn :: Tensor -> Int -> Int -> String -> Tensor
fft_ifftn Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_ifftn_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_rfftn
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_rfftn :: Tensor -> Int -> Int -> String -> Tensor
fft_rfftn Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_rfftn_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_irfftn
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_irfftn :: Tensor -> Int -> Int -> String -> Tensor
fft_irfftn Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_irfftn_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_hfftn
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_hfftn :: Tensor -> Int -> Int -> String -> Tensor
fft_hfftn Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_hfftn_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_ihfftn
:: Tensor
-> Int
-> Int
-> String
-> Tensor
fft_ihfftn :: Tensor -> Int -> Int -> String -> Tensor
fft_ihfftn Tensor
_self Int
_s Int
_dim String
_norm = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> String -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
ATen.fft_ihfftn_tlls) Tensor
_self Int
_s Int
_dim String
_norm
fft_fftshift
:: Tensor
-> Int
-> Tensor
fft_fftshift :: Tensor -> Int -> Tensor
fft_fftshift Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.fft_fftshift_tl) Tensor
_self Int
_dim
fft_ifftshift
:: Tensor
-> Int
-> Tensor
fft_ifftshift :: Tensor -> Int -> Tensor
fft_ifftshift Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.fft_ifftshift_tl) Tensor
_self Int
_dim
linalg_cholesky_ex
:: Tensor
-> Bool
-> Bool
-> (Tensor,Tensor)
linalg_cholesky_ex :: Tensor -> Bool -> Bool -> (Tensor, Tensor)
linalg_cholesky_ex Tensor
_self Bool
_upper Bool
_check_errors = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CBool -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_cholesky_ex_tbb) Tensor
_self Bool
_upper Bool
_check_errors
linalg_cholesky
:: Tensor
-> Bool
-> Tensor
linalg_cholesky :: Tensor -> Bool -> Tensor
linalg_cholesky Tensor
_self Bool
_upper = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_cholesky_tb) Tensor
_self Bool
_upper
linalg_cross
:: Tensor
-> Tensor
-> Int
-> Tensor
linalg_cross :: Tensor -> Tensor -> Int -> Tensor
linalg_cross Tensor
_self Tensor
_other Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.linalg_cross_ttl) Tensor
_self Tensor
_other Int
_dim
linalg_lu_factor
:: Tensor
-> Bool
-> (Tensor,Tensor)
linalg_lu_factor :: Tensor -> Bool -> (Tensor, Tensor)
linalg_lu_factor Tensor
_A Bool
_pivot = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_lu_factor_tb) Tensor
_A Bool
_pivot
linalg_lu_factor_ex
:: Tensor
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
linalg_lu_factor_ex :: Tensor -> Bool -> Bool -> (Tensor, Tensor, Tensor)
linalg_lu_factor_ex Tensor
_A Bool
_pivot Bool
_check_errors = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Bool -> Bool -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.linalg_lu_factor_ex_tbb) Tensor
_A Bool
_pivot Bool
_check_errors
linalg_lu
:: Tensor
-> Bool
-> (Tensor,Tensor,Tensor)
linalg_lu :: Tensor -> Bool -> (Tensor, Tensor, Tensor)
linalg_lu Tensor
_A Bool
_pivot = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.linalg_lu_tb) Tensor
_A Bool
_pivot
linalg_lu_solve
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Bool
-> Tensor
linalg_lu_solve :: Tensor -> Tensor -> Tensor -> Bool -> Bool -> Tensor
linalg_lu_solve Tensor
_LU Tensor
_pivots Tensor
_B Bool
_left Bool
_adjoint = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Bool -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
ATen.linalg_lu_solve_tttbb) Tensor
_LU Tensor
_pivots Tensor
_B Bool
_left Bool
_adjoint
linalg_det
:: Tensor
-> Tensor
linalg_det :: Tensor -> Tensor
linalg_det Tensor
_A = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linalg_det_t) Tensor
_A
det
:: Tensor
-> Tensor
det :: Tensor -> Tensor
det Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.det_t) Tensor
_self
linalg_ldl_factor_ex
:: Tensor
-> Bool
-> Bool
-> (Tensor,Tensor,Tensor)
linalg_ldl_factor_ex :: Tensor -> Bool -> Bool -> (Tensor, Tensor, Tensor)
linalg_ldl_factor_ex Tensor
_self Bool
_hermitian Bool
_check_errors = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Bool -> Bool -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.linalg_ldl_factor_ex_tbb) Tensor
_self Bool
_hermitian Bool
_check_errors
linalg_ldl_factor
:: Tensor
-> Bool
-> (Tensor,Tensor)
linalg_ldl_factor :: Tensor -> Bool -> (Tensor, Tensor)
linalg_ldl_factor Tensor
_self Bool
_hermitian = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_ldl_factor_tb) Tensor
_self Bool
_hermitian
linalg_ldl_solve
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Tensor
linalg_ldl_solve :: Tensor -> Tensor -> Tensor -> Bool -> Tensor
linalg_ldl_solve Tensor
_LD Tensor
_pivots Tensor
_B Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
ATen.linalg_ldl_solve_tttb) Tensor
_LD Tensor
_pivots Tensor
_B Bool
_hermitian
linalg_lstsq
:: Tensor
-> Tensor
-> Double
-> String
-> (Tensor,Tensor,Tensor,Tensor)
linalg_lstsq :: Tensor
-> Tensor -> Double -> String -> (Tensor, Tensor, Tensor, Tensor)
linalg_lstsq Tensor
_a Tensor
_b Double
_rcond String
_driver = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor
-> Tensor
-> Double
-> String
-> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.linalg_lstsq_ttds) Tensor
_a Tensor
_b Double
_rcond String
_driver
lstsq
:: Tensor
-> Tensor
-> Tensor
lstsq :: Tensor -> Tensor -> Tensor
lstsq Tensor
_b Tensor
_a =
let (Tensor
t0,Tensor
_,Tensor
_,Tensor
_) = IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor, Tensor)
-> (Tensor, Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> Tensor -> Tensor -> IO (Tensor, Tensor, Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
ATen.linalg_lstsq_tt) Tensor
_a Tensor
_b :: (Tensor,Tensor,Tensor,Tensor)
in Tensor
t0
linalg_matmul
:: Tensor
-> Tensor
-> Tensor
linalg_matmul :: Tensor -> Tensor -> Tensor
linalg_matmul Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linalg_matmul_tt) Tensor
_self Tensor
_other
linalg_vecdot
:: Tensor
-> Tensor
-> Int
-> Tensor
linalg_vecdot :: Tensor -> Tensor -> Int -> Tensor
linalg_vecdot Tensor
_x Tensor
_y Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.linalg_vecdot_ttl) Tensor
_x Tensor
_y Int
_dim
linalg_matrix_exp
:: Tensor
-> Tensor
linalg_matrix_exp :: Tensor -> Tensor
linalg_matrix_exp Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linalg_matrix_exp_t) Tensor
_self
linalg_slogdet
:: Tensor
-> (Tensor,Tensor)
linalg_slogdet :: Tensor -> (Tensor, Tensor)
linalg_slogdet Tensor
_A = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> IO (Tensor, Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_slogdet_t) Tensor
_A
slogdet
:: Tensor
-> (Tensor,Tensor)
slogdet :: Tensor -> (Tensor, Tensor)
slogdet Tensor
_self = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> IO (Tensor, Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.slogdet_t) Tensor
_self
logdet
:: Tensor
-> Tensor
logdet :: Tensor -> Tensor
logdet Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.logdet_t) Tensor
_self
linalg_eig
:: Tensor
-> (Tensor,Tensor)
linalg_eig :: Tensor -> (Tensor, Tensor)
linalg_eig Tensor
_self = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> IO (Tensor, Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_eig_t) Tensor
_self
linalg_eigvals
:: Tensor
-> Tensor
linalg_eigvals :: Tensor -> Tensor
linalg_eigvals Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linalg_eigvals_t) Tensor
_self
linalg_eigh
:: Tensor
-> String
-> (Tensor,Tensor)
linalg_eigh :: Tensor -> String -> (Tensor, Tensor)
linalg_eigh Tensor
_self String
_UPLO = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> String -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_eigh_ts) Tensor
_self String
_UPLO
linalg_eigvalsh
:: Tensor
-> String
-> Tensor
linalg_eigvalsh :: Tensor -> String -> Tensor
linalg_eigvalsh Tensor
_self String
_UPLO = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr StdString -> IO (ForeignPtr Tensor))
-> Tensor -> String -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.linalg_eigvalsh_ts) Tensor
_self String
_UPLO
linalg_householder_product
:: Tensor
-> Tensor
-> Tensor
linalg_householder_product :: Tensor -> Tensor -> Tensor
linalg_householder_product Tensor
_input Tensor
_tau = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linalg_householder_product_tt) Tensor
_input Tensor
_tau
linalg_inv_ex
:: Tensor
-> Bool
-> (Tensor,Tensor)
linalg_inv_ex :: Tensor -> Bool -> (Tensor, Tensor)
linalg_inv_ex Tensor
_A Bool
_check_errors = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_inv_ex_tb) Tensor
_A Bool
_check_errors
linalg_inv
:: Tensor
-> Tensor
linalg_inv :: Tensor -> Tensor
linalg_inv Tensor
_A = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.linalg_inv_t) Tensor
_A
inverse
:: Tensor
-> Tensor
inverse :: Tensor -> Tensor
inverse Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.inverse_t) Tensor
_self
inner
:: Tensor
-> Tensor
-> Tensor
inner :: Tensor -> Tensor -> Tensor
inner Tensor
_self Tensor
_other = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.inner_tt) Tensor
_self Tensor
_other
outer
:: Tensor
-> Tensor
-> Tensor
outer :: Tensor -> Tensor -> Tensor
outer Tensor
_self Tensor
_vec2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.outer_tt) Tensor
_self Tensor
_vec2
ger
:: Tensor
-> Tensor
-> Tensor
ger :: Tensor -> Tensor -> Tensor
ger Tensor
_self Tensor
_vec2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ger_tt) Tensor
_self Tensor
_vec2
linalg_norm_tslbs
:: Tensor
-> Float
-> Int
-> Bool
-> DType
-> Tensor
linalg_norm_tslbs :: Tensor -> Float -> Int -> Bool -> DType -> Tensor
linalg_norm_tslbs Tensor
_self Float
_ord Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.linalg_norm_tslbs) Tensor
_self Float
_ord Int
_dim Bool
_keepdim DType
_dtype
linalg_vector_norm
:: Tensor
-> Float
-> Int
-> Bool
-> DType
-> Tensor
linalg_vector_norm :: Tensor -> Float -> Int -> Bool -> DType -> Tensor
linalg_vector_norm Tensor
_self Float
_ord Int
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> Int -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.linalg_vector_norm_tslbs) Tensor
_self Float
_ord Int
_dim Bool
_keepdim DType
_dtype
linalg_matrix_norm_tslbs
:: Tensor
-> Float
-> [Int]
-> Bool
-> DType
-> Tensor
linalg_matrix_norm_tslbs :: Tensor -> Float -> [Int] -> Bool -> DType -> Tensor
linalg_matrix_norm_tslbs Tensor
_self Float
_ord [Int]
_dim Bool
_keepdim DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor))
-> Tensor -> Float -> [Int] -> Bool -> DType -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
ATen.linalg_matrix_norm_tslbs) Tensor
_self Float
_ord [Int]
_dim Bool
_keepdim DType
_dtype
linalg_svd
:: Tensor
-> Bool
-> String
-> (Tensor,Tensor,Tensor)
linalg_svd :: Tensor -> Bool -> String -> (Tensor, Tensor, Tensor)
linalg_svd Tensor
_A Bool
_full_matrices String
_driver = IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor))
-> IO (Tensor, Tensor, Tensor) -> (Tensor, Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
-> Tensor -> Bool -> String -> IO (Tensor, Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CBool
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
ATen.linalg_svd_tbs) Tensor
_A Bool
_full_matrices String
_driver
linalg_svdvals
:: Tensor
-> String
-> Tensor
linalg_svdvals :: Tensor -> String -> Tensor
linalg_svdvals Tensor
_A String
_driver = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr StdString -> IO (ForeignPtr Tensor))
-> Tensor -> String -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr StdString -> IO (ForeignPtr Tensor)
ATen.linalg_svdvals_ts) Tensor
_A String
_driver
linalg_cond_ts
:: Tensor
-> Float
-> Tensor
linalg_cond_ts :: Tensor -> Float -> Tensor
linalg_cond_ts Tensor
_self Float
_p = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.linalg_cond_ts) Tensor
_self Float
_p
linalg_pinv_tttb
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Tensor
linalg_pinv_tttb :: Tensor -> Tensor -> Tensor -> Bool -> Tensor
linalg_pinv_tttb Tensor
_self Tensor
_atol Tensor
_rtol Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
ATen.linalg_pinv_tttb) Tensor
_self Tensor
_atol Tensor
_rtol Bool
_hermitian
linalg_pinv_tddb
:: Tensor
-> Double
-> Double
-> Bool
-> Tensor
linalg_pinv_tddb :: Tensor -> Double -> Double -> Bool -> Tensor
linalg_pinv_tddb Tensor
_self Double
_atol Double
_rtol Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CDouble -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_pinv_tddb) Tensor
_self Double
_atol Double
_rtol Bool
_hermitian
linalg_pinv_tdb
:: Tensor
-> Double
-> Bool
-> Tensor
linalg_pinv_tdb :: Tensor -> Double -> Bool -> Tensor
linalg_pinv_tdb Tensor
_self Double
_rcond Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_pinv_tdb) Tensor
_self Double
_rcond Bool
_hermitian
linalg_pinv_ttb
:: Tensor
-> Tensor
-> Bool
-> Tensor
linalg_pinv_ttb :: Tensor -> Tensor -> Bool -> Tensor
linalg_pinv_ttb Tensor
_self Tensor
_rcond Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_pinv_ttb) Tensor
_self Tensor
_rcond Bool
_hermitian
linalg_solve_ex
:: Tensor
-> Tensor
-> Bool
-> Bool
-> (Tensor,Tensor)
linalg_solve_ex :: Tensor -> Tensor -> Bool -> Bool -> (Tensor, Tensor)
linalg_solve_ex Tensor
_A Tensor
_B Bool
_left Bool
_check_errors = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> Tensor -> Bool -> Bool -> IO (Tensor, Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_solve_ex_ttbb) Tensor
_A Tensor
_B Bool
_left Bool
_check_errors
linalg_solve
:: Tensor
-> Tensor
-> Bool
-> Tensor
linalg_solve :: Tensor -> Tensor -> Bool -> Tensor
linalg_solve Tensor
_A Tensor
_B Bool
_left = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_solve_ttb) Tensor
_A Tensor
_B Bool
_left
linalg_tensorinv
:: Tensor
-> Int
-> Tensor
linalg_tensorinv :: Tensor -> Int -> Tensor
linalg_tensorinv Tensor
_self Int
_ind = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.linalg_tensorinv_tl) Tensor
_self Int
_ind
linalg_tensorsolve
:: Tensor
-> Tensor
-> [Int]
-> Tensor
linalg_tensorsolve :: Tensor -> Tensor -> [Int] -> Tensor
linalg_tensorsolve Tensor
_self Tensor
_other [Int]
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
ATen.linalg_tensorsolve_ttl) Tensor
_self Tensor
_other [Int]
_dims
linalg_qr
:: Tensor
-> String
-> (Tensor,Tensor)
linalg_qr :: Tensor -> String -> (Tensor, Tensor)
linalg_qr Tensor
_A String
_mode = IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a. IO a -> a
unsafePerformIO (IO (Tensor, Tensor) -> (Tensor, Tensor))
-> IO (Tensor, Tensor) -> (Tensor, Tensor)
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor))))
-> Tensor -> String -> IO (Tensor, Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
ATen.linalg_qr_ts) Tensor
_A String
_mode
linalg_matrix_power
:: Tensor
-> Int
-> Tensor
linalg_matrix_power :: Tensor -> Int -> Tensor
linalg_matrix_power Tensor
_self Int
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.linalg_matrix_power_tl) Tensor
_self Int
_n
linalg_matrix_rank_tttb
:: Tensor
-> Tensor
-> Tensor
-> Bool
-> Tensor
linalg_matrix_rank_tttb :: Tensor -> Tensor -> Tensor -> Bool -> Tensor
linalg_matrix_rank_tttb Tensor
_input Tensor
_atol Tensor
_rtol Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
ATen.linalg_matrix_rank_tttb) Tensor
_input Tensor
_atol Tensor
_rtol Bool
_hermitian
linalg_matrix_rank_tddb
:: Tensor
-> Double
-> Double
-> Bool
-> Tensor
linalg_matrix_rank_tddb :: Tensor -> Double -> Double -> Bool -> Tensor
linalg_matrix_rank_tddb Tensor
_self Double
_atol Double
_rtol Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> CDouble -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_matrix_rank_tddb) Tensor
_self Double
_atol Double
_rtol Bool
_hermitian
linalg_matrix_rank_tdb
:: Tensor
-> Double
-> Bool
-> Tensor
linalg_matrix_rank_tdb :: Tensor -> Double -> Bool -> Tensor
linalg_matrix_rank_tdb Tensor
_self Double
_tol Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> CDouble -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_matrix_rank_tdb) Tensor
_self Double
_tol Bool
_hermitian
linalg_matrix_rank_ttb
:: Tensor
-> Tensor
-> Bool
-> Tensor
linalg_matrix_rank_ttb :: Tensor -> Tensor -> Bool -> Tensor
linalg_matrix_rank_ttb Tensor
_input Tensor
_tol Bool
_hermitian = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.linalg_matrix_rank_ttb) Tensor
_input Tensor
_tol Bool
_hermitian
linalg_multi_dot
:: [Tensor]
-> Tensor
linalg_multi_dot :: [Tensor] -> Tensor
linalg_multi_dot [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.linalg_multi_dot_l) [Tensor]
_tensors
nested_to_padded_tensor
:: Tensor
-> Double
-> [Int]
-> Tensor
nested_to_padded_tensor :: Tensor -> Double -> [Int] -> Tensor
nested_to_padded_tensor Tensor
_self Double
_padding [Int]
_output_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> CDouble -> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> Double -> [Int] -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> CDouble -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.nested_to_padded_tensor_tdl) Tensor
_self Double
_padding [Int]
_output_size
segment_reduce
:: Tensor
-> String
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Bool
-> Float
-> Tensor
segment_reduce :: Tensor
-> String
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Bool
-> Float
-> Tensor
segment_reduce Tensor
_data String
_reduce Tensor
_lengths Tensor
_indices Tensor
_offsets Int
_axis Bool
_unsafe Float
_initial = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor))
-> Tensor
-> String
-> Tensor
-> Tensor
-> Tensor
-> Int
-> Bool
-> Float
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
cast8 ForeignPtr Tensor
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
ATen.segment_reduce_tstttlbs) Tensor
_data String
_reduce Tensor
_lengths Tensor
_indices Tensor
_offsets Int
_axis Bool
_unsafe Float
_initial
pad_sequence
:: [Tensor]
-> Bool
-> Double
-> Tensor
pad_sequence :: [Tensor] -> Bool -> Double -> Tensor
pad_sequence [Tensor]
_sequences Bool
_batch_first Double
_padding_value = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList
-> CBool -> CDouble -> IO (ForeignPtr Tensor))
-> [Tensor] -> Bool -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr TensorList -> CBool -> CDouble -> IO (ForeignPtr Tensor)
ATen.pad_sequence_lbd) [Tensor]
_sequences Bool
_batch_first Double
_padding_value
flatten_dense_tensors
:: [Tensor]
-> Tensor
flatten_dense_tensors :: [Tensor] -> Tensor
flatten_dense_tensors [Tensor]
_tensors = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr TensorList -> IO (ForeignPtr Tensor))
-> [Tensor] -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr TensorList -> IO (ForeignPtr Tensor)
ATen.flatten_dense_tensors_l) [Tensor]
_tensors
unflatten_dense_tensors
:: Tensor
-> [Tensor]
-> [Tensor]
unflatten_dense_tensors :: Tensor -> [Tensor] -> [Tensor]
unflatten_dense_tensors Tensor
_flat [Tensor]
_tensors = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr TensorList -> IO (ForeignPtr TensorList))
-> Tensor -> [Tensor] -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor
-> ForeignPtr TensorList -> IO (ForeignPtr TensorList)
ATen.unflatten_dense_tensors_tl) Tensor
_flat [Tensor]
_tensors
view_as_real_copy
:: Tensor
-> Tensor
view_as_real_copy :: Tensor -> Tensor
view_as_real_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.view_as_real_copy_t) Tensor
_self
view_as_complex_copy
:: Tensor
-> Tensor
view_as_complex_copy :: Tensor -> Tensor
view_as_complex_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.view_as_complex_copy_t) Tensor
_self
as_strided_copy
:: Tensor
-> [Int]
-> [Int]
-> Int
-> Tensor
as_strided_copy :: Tensor -> [Int] -> [Int] -> Int -> Tensor
as_strided_copy Tensor
_self [Int]
_size [Int]
_stride Int
_storage_offset = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> [Int] -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
ATen.as_strided_copy_tlll) Tensor
_self [Int]
_size [Int]
_stride Int
_storage_offset
diagonal_copy
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
diagonal_copy :: Tensor -> Int -> Int -> Int -> Tensor
diagonal_copy Tensor
_self Int
_offset Int
_dim1 Int
_dim2 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.diagonal_copy_tlll) Tensor
_self Int
_offset Int
_dim1 Int
_dim2
expand_copy
:: Tensor
-> [Int]
-> Bool
-> Tensor
expand_copy :: Tensor -> [Int] -> Bool -> Tensor
expand_copy Tensor
_self [Int]
_size Bool
_implicit = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
ATen.expand_copy_tlb) Tensor
_self [Int]
_size Bool
_implicit
permute_copy
:: Tensor
-> [Int]
-> Tensor
permute_copy :: Tensor -> [Int] -> Tensor
permute_copy Tensor
_self [Int]
_dims = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.permute_copy_tl) Tensor
_self [Int]
_dims
select_copy
:: Tensor
-> Int
-> Int
-> Tensor
select_copy :: Tensor -> Int -> Int -> Tensor
select_copy Tensor
_self Int
_dim Int
_index = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.select_copy_tll) Tensor
_self Int
_dim Int
_index
detach_copy
:: Tensor
-> Tensor
detach_copy :: Tensor -> Tensor
detach_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.detach_copy_t) Tensor
_self
slice_copy
:: Tensor
-> Int
-> Int
-> Int
-> Int
-> Tensor
slice_copy :: Tensor -> Int -> Int -> Int -> Int -> Tensor
slice_copy Tensor
_self Int
_dim Int
_start Int
_end Int
_step = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
cast5 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.slice_copy_tllll) Tensor
_self Int
_dim Int
_start Int
_end Int
_step
split_copy
:: Tensor
-> Int
-> Int
-> [Tensor]
split_copy :: Tensor -> Int -> Int -> [Tensor]
split_copy Tensor
_self Int
_split_size Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
ATen.split_copy_tll) Tensor
_self Int
_split_size Int
_dim
split_with_sizes_copy
:: Tensor
-> [Int]
-> Int
-> [Tensor]
split_with_sizes_copy :: Tensor -> [Int] -> Int -> [Tensor]
split_with_sizes_copy Tensor
_self [Int]
_split_sizes Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> [Int] -> Int -> IO [Tensor]
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList)
ATen.split_with_sizes_copy_tll) Tensor
_self [Int]
_split_sizes Int
_dim
squeeze_copy_t
:: Tensor
-> Tensor
squeeze_copy_t :: Tensor -> Tensor
squeeze_copy_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.squeeze_copy_t) Tensor
_self
squeeze_copy_tl
:: Tensor
-> Int
-> Tensor
squeeze_copy_tl :: Tensor -> Int -> Tensor
squeeze_copy_tl Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.squeeze_copy_tl) Tensor
_self Int
_dim
t_copy
:: Tensor
-> Tensor
t_copy :: Tensor -> Tensor
t_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.t_copy_t) Tensor
_self
transpose_copy
:: Tensor
-> Int
-> Int
-> Tensor
transpose_copy :: Tensor -> Int -> Int -> Tensor
transpose_copy Tensor
_self Int
_dim0 Int
_dim1 = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.transpose_copy_tll) Tensor
_self Int
_dim0 Int
_dim1
unsqueeze_copy
:: Tensor
-> Int
-> Tensor
unsqueeze_copy :: Tensor -> Int -> Tensor
unsqueeze_copy Tensor
_self Int
_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
ATen.unsqueeze_copy_tl) Tensor
_self Int
_dim
indices_copy
:: Tensor
-> Tensor
indices_copy :: Tensor -> Tensor
indices_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.indices_copy_t) Tensor
_self
values_copy
:: Tensor
-> Tensor
values_copy :: Tensor -> Tensor
values_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.values_copy_t) Tensor
_self
crow_indices_copy
:: Tensor
-> Tensor
crow_indices_copy :: Tensor -> Tensor
crow_indices_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.crow_indices_copy_t) Tensor
_self
col_indices_copy
:: Tensor
-> Tensor
col_indices_copy :: Tensor -> Tensor
col_indices_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.col_indices_copy_t) Tensor
_self
ccol_indices_copy
:: Tensor
-> Tensor
ccol_indices_copy :: Tensor -> Tensor
ccol_indices_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.ccol_indices_copy_t) Tensor
_self
row_indices_copy
:: Tensor
-> Tensor
row_indices_copy :: Tensor -> Tensor
row_indices_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.row_indices_copy_t) Tensor
_self
unbind_copy
:: Tensor
-> Int
-> [Tensor]
unbind_copy :: Tensor -> Int -> [Tensor]
unbind_copy Tensor
_self Int
_dim = IO [Tensor] -> [Tensor]
forall a. IO a -> a
unsafePerformIO (IO [Tensor] -> [Tensor]) -> IO [Tensor] -> [Tensor]
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList))
-> Tensor -> Int -> IO [Tensor]
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
ATen.unbind_copy_tl) Tensor
_self Int
_dim
view_copy_tl
:: Tensor
-> [Int]
-> Tensor
view_copy_tl :: Tensor -> [Int] -> Tensor
view_copy_tl Tensor
_self [Int]
_size = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
ATen.view_copy_tl) Tensor
_self [Int]
_size
view_copy_ts
:: Tensor
-> DType
-> Tensor
view_copy_ts :: Tensor -> DType -> Tensor
view_copy_ts Tensor
_self DType
_dtype = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> DType -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.view_copy_ts) Tensor
_self DType
_dtype
unfold_copy
:: Tensor
-> Int
-> Int
-> Int
-> Tensor
unfold_copy :: Tensor -> Int -> Int -> Int -> Tensor
unfold_copy Tensor
_self Int
_dimension Int
_size Int
_step = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> Int -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.unfold_copy_tlll) Tensor
_self Int
_dimension Int
_size Int
_step
alias_copy
:: Tensor
-> Tensor
alias_copy :: Tensor -> Tensor
alias_copy Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.alias_copy_t) Tensor
_self
scaled_dot_product_attention
:: Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Bool
-> Tensor
scaled_dot_product_attention :: Tensor -> Tensor -> Tensor -> Tensor -> Double -> Bool -> Tensor
scaled_dot_product_attention Tensor
_query Tensor
_key Tensor
_value Tensor
_attn_mask Double
_dropout_p Bool
_is_causal = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor))
-> Tensor
-> Tensor
-> Tensor
-> Tensor
-> Double
-> Bool
-> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
cast6 ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CBool
-> IO (ForeignPtr Tensor)
ATen.scaled_dot_product_attention_ttttdb) Tensor
_query Tensor
_key Tensor
_value Tensor
_attn_mask Double
_dropout_p Bool
_is_causal
special_airy_ai
:: Tensor
-> Tensor
special_airy_ai :: Tensor -> Tensor
special_airy_ai Tensor
_x = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_airy_ai_t) Tensor
_x
special_bessel_j0
:: Tensor
-> Tensor
special_bessel_j0 :: Tensor -> Tensor
special_bessel_j0 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_bessel_j0_t) Tensor
_self
special_bessel_j1
:: Tensor
-> Tensor
special_bessel_j1 :: Tensor -> Tensor
special_bessel_j1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_bessel_j1_t) Tensor
_self
special_bessel_y0
:: Tensor
-> Tensor
special_bessel_y0 :: Tensor -> Tensor
special_bessel_y0 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_bessel_y0_t) Tensor
_self
special_bessel_y1
:: Tensor
-> Tensor
special_bessel_y1 :: Tensor -> Tensor
special_bessel_y1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_bessel_y1_t) Tensor
_self
special_chebyshev_polynomial_t_tt
:: Tensor
-> Tensor
-> Tensor
special_chebyshev_polynomial_t_tt :: Tensor -> Tensor -> Tensor
special_chebyshev_polynomial_t_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_t_tt) Tensor
_x Tensor
_n
special_chebyshev_polynomial_t_st
:: Float
-> Tensor
-> Tensor
special_chebyshev_polynomial_t_st :: Float -> Tensor -> Tensor
special_chebyshev_polynomial_t_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_t_st) Float
_x Tensor
_n
special_chebyshev_polynomial_t_ts
:: Tensor
-> Float
-> Tensor
special_chebyshev_polynomial_t_ts :: Tensor -> Float -> Tensor
special_chebyshev_polynomial_t_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_t_ts) Tensor
_x Float
_n
special_chebyshev_polynomial_u_tt
:: Tensor
-> Tensor
-> Tensor
special_chebyshev_polynomial_u_tt :: Tensor -> Tensor -> Tensor
special_chebyshev_polynomial_u_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_u_tt) Tensor
_x Tensor
_n
special_chebyshev_polynomial_u_st
:: Float
-> Tensor
-> Tensor
special_chebyshev_polynomial_u_st :: Float -> Tensor -> Tensor
special_chebyshev_polynomial_u_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_u_st) Float
_x Tensor
_n
special_chebyshev_polynomial_u_ts
:: Tensor
-> Float
-> Tensor
special_chebyshev_polynomial_u_ts :: Tensor -> Float -> Tensor
special_chebyshev_polynomial_u_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_u_ts) Tensor
_x Float
_n
special_chebyshev_polynomial_v_tt
:: Tensor
-> Tensor
-> Tensor
special_chebyshev_polynomial_v_tt :: Tensor -> Tensor -> Tensor
special_chebyshev_polynomial_v_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_v_tt) Tensor
_x Tensor
_n
special_chebyshev_polynomial_v_st
:: Float
-> Tensor
-> Tensor
special_chebyshev_polynomial_v_st :: Float -> Tensor -> Tensor
special_chebyshev_polynomial_v_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_v_st) Float
_x Tensor
_n
special_chebyshev_polynomial_v_ts
:: Tensor
-> Float
-> Tensor
special_chebyshev_polynomial_v_ts :: Tensor -> Float -> Tensor
special_chebyshev_polynomial_v_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_v_ts) Tensor
_x Float
_n
special_chebyshev_polynomial_w_tt
:: Tensor
-> Tensor
-> Tensor
special_chebyshev_polynomial_w_tt :: Tensor -> Tensor -> Tensor
special_chebyshev_polynomial_w_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_w_tt) Tensor
_x Tensor
_n
special_chebyshev_polynomial_w_st
:: Float
-> Tensor
-> Tensor
special_chebyshev_polynomial_w_st :: Float -> Tensor -> Tensor
special_chebyshev_polynomial_w_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_w_st) Float
_x Tensor
_n
special_chebyshev_polynomial_w_ts
:: Tensor
-> Float
-> Tensor
special_chebyshev_polynomial_w_ts :: Tensor -> Float -> Tensor
special_chebyshev_polynomial_w_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_chebyshev_polynomial_w_ts) Tensor
_x Float
_n
special_hermite_polynomial_h_tt
:: Tensor
-> Tensor
-> Tensor
special_hermite_polynomial_h_tt :: Tensor -> Tensor -> Tensor
special_hermite_polynomial_h_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_hermite_polynomial_h_tt) Tensor
_x Tensor
_n
special_hermite_polynomial_h_st
:: Float
-> Tensor
-> Tensor
special_hermite_polynomial_h_st :: Float -> Tensor -> Tensor
special_hermite_polynomial_h_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_hermite_polynomial_h_st) Float
_x Tensor
_n
special_hermite_polynomial_h_ts
:: Tensor
-> Float
-> Tensor
special_hermite_polynomial_h_ts :: Tensor -> Float -> Tensor
special_hermite_polynomial_h_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_hermite_polynomial_h_ts) Tensor
_x Float
_n
special_hermite_polynomial_he_tt
:: Tensor
-> Tensor
-> Tensor
special_hermite_polynomial_he_tt :: Tensor -> Tensor -> Tensor
special_hermite_polynomial_he_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_hermite_polynomial_he_tt) Tensor
_x Tensor
_n
special_hermite_polynomial_he_st
:: Float
-> Tensor
-> Tensor
special_hermite_polynomial_he_st :: Float -> Tensor -> Tensor
special_hermite_polynomial_he_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_hermite_polynomial_he_st) Float
_x Tensor
_n
special_hermite_polynomial_he_ts
:: Tensor
-> Float
-> Tensor
special_hermite_polynomial_he_ts :: Tensor -> Float -> Tensor
special_hermite_polynomial_he_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_hermite_polynomial_he_ts) Tensor
_x Float
_n
special_laguerre_polynomial_l_tt
:: Tensor
-> Tensor
-> Tensor
special_laguerre_polynomial_l_tt :: Tensor -> Tensor -> Tensor
special_laguerre_polynomial_l_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_laguerre_polynomial_l_tt) Tensor
_x Tensor
_n
special_laguerre_polynomial_l_st
:: Float
-> Tensor
-> Tensor
special_laguerre_polynomial_l_st :: Float -> Tensor -> Tensor
special_laguerre_polynomial_l_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_laguerre_polynomial_l_st) Float
_x Tensor
_n
special_laguerre_polynomial_l_ts
:: Tensor
-> Float
-> Tensor
special_laguerre_polynomial_l_ts :: Tensor -> Float -> Tensor
special_laguerre_polynomial_l_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_laguerre_polynomial_l_ts) Tensor
_x Float
_n
special_legendre_polynomial_p_tt
:: Tensor
-> Tensor
-> Tensor
special_legendre_polynomial_p_tt :: Tensor -> Tensor -> Tensor
special_legendre_polynomial_p_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_legendre_polynomial_p_tt) Tensor
_x Tensor
_n
special_legendre_polynomial_p_st
:: Float
-> Tensor
-> Tensor
special_legendre_polynomial_p_st :: Float -> Tensor -> Tensor
special_legendre_polynomial_p_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_legendre_polynomial_p_st) Float
_x Tensor
_n
special_legendre_polynomial_p_ts
:: Tensor
-> Float
-> Tensor
special_legendre_polynomial_p_ts :: Tensor -> Float -> Tensor
special_legendre_polynomial_p_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_legendre_polynomial_p_ts) Tensor
_x Float
_n
special_modified_bessel_i0
:: Tensor
-> Tensor
special_modified_bessel_i0 :: Tensor -> Tensor
special_modified_bessel_i0 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_modified_bessel_i0_t) Tensor
_self
special_modified_bessel_i1
:: Tensor
-> Tensor
special_modified_bessel_i1 :: Tensor -> Tensor
special_modified_bessel_i1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_modified_bessel_i1_t) Tensor
_self
special_modified_bessel_k0
:: Tensor
-> Tensor
special_modified_bessel_k0 :: Tensor -> Tensor
special_modified_bessel_k0 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_modified_bessel_k0_t) Tensor
_self
special_modified_bessel_k1
:: Tensor
-> Tensor
special_modified_bessel_k1 :: Tensor -> Tensor
special_modified_bessel_k1 Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_modified_bessel_k1_t) Tensor
_self
special_scaled_modified_bessel_k0
:: Tensor
-> Tensor
special_scaled_modified_bessel_k0 :: Tensor -> Tensor
special_scaled_modified_bessel_k0 Tensor
_x = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_scaled_modified_bessel_k0_t) Tensor
_x
special_scaled_modified_bessel_k1
:: Tensor
-> Tensor
special_scaled_modified_bessel_k1 :: Tensor -> Tensor
special_scaled_modified_bessel_k1 Tensor
_x = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_scaled_modified_bessel_k1_t) Tensor
_x
special_shifted_chebyshev_polynomial_t_tt
:: Tensor
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_t_tt :: Tensor -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_t_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_t_tt) Tensor
_x Tensor
_n
special_shifted_chebyshev_polynomial_t_st
:: Float
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_t_st :: Float -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_t_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_t_st) Float
_x Tensor
_n
special_shifted_chebyshev_polynomial_t_ts
:: Tensor
-> Float
-> Tensor
special_shifted_chebyshev_polynomial_t_ts :: Tensor -> Float -> Tensor
special_shifted_chebyshev_polynomial_t_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_t_ts) Tensor
_x Float
_n
special_shifted_chebyshev_polynomial_u_tt
:: Tensor
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_u_tt :: Tensor -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_u_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_u_tt) Tensor
_x Tensor
_n
special_shifted_chebyshev_polynomial_u_st
:: Float
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_u_st :: Float -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_u_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_u_st) Float
_x Tensor
_n
special_shifted_chebyshev_polynomial_u_ts
:: Tensor
-> Float
-> Tensor
special_shifted_chebyshev_polynomial_u_ts :: Tensor -> Float -> Tensor
special_shifted_chebyshev_polynomial_u_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_u_ts) Tensor
_x Float
_n
special_shifted_chebyshev_polynomial_v_tt
:: Tensor
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_v_tt :: Tensor -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_v_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_v_tt) Tensor
_x Tensor
_n
special_shifted_chebyshev_polynomial_v_st
:: Float
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_v_st :: Float -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_v_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_v_st) Float
_x Tensor
_n
special_shifted_chebyshev_polynomial_v_ts
:: Tensor
-> Float
-> Tensor
special_shifted_chebyshev_polynomial_v_ts :: Tensor -> Float -> Tensor
special_shifted_chebyshev_polynomial_v_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_v_ts) Tensor
_x Float
_n
special_shifted_chebyshev_polynomial_w_tt
:: Tensor
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_w_tt :: Tensor -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_w_tt Tensor
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_w_tt) Tensor
_x Tensor
_n
special_shifted_chebyshev_polynomial_w_st
:: Float
-> Tensor
-> Tensor
special_shifted_chebyshev_polynomial_w_st :: Float -> Tensor -> Tensor
special_shifted_chebyshev_polynomial_w_st Float
_x Tensor
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Float -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Scalar -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_w_st) Float
_x Tensor
_n
special_shifted_chebyshev_polynomial_w_ts
:: Tensor
-> Float
-> Tensor
special_shifted_chebyshev_polynomial_w_ts :: Tensor -> Float -> Tensor
special_shifted_chebyshev_polynomial_w_ts Tensor
_x Float
_n = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor))
-> Tensor -> Float -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
ATen.special_shifted_chebyshev_polynomial_w_ts) Tensor
_x Float
_n
special_spherical_bessel_j0
:: Tensor
-> Tensor
special_spherical_bessel_j0 :: Tensor -> Tensor
special_spherical_bessel_j0 Tensor
_x = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.special_spherical_bessel_j0_t) Tensor
_x
embedding_renorm
:: Tensor
-> Tensor
-> Double
-> Double
-> Tensor
embedding_renorm :: Tensor -> Tensor -> Double -> Double -> Tensor
embedding_renorm Tensor
_self Tensor
_indices Double
_max_norm Double
_norm_type = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Double -> Double -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
ATen.embedding_renorm_ttdd) Tensor
_self Tensor
_indices Double
_max_norm Double
_norm_type
resize
:: Tensor
-> [Int]
-> ATen.MemoryFormat
-> Tensor
resize :: Tensor -> [Int] -> MemoryFormat -> Tensor
resize Tensor
_self [Int]
_size MemoryFormat
_memory_format = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> MemoryFormat -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr IntArray -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.resize_tlM) Tensor
_self [Int]
_size MemoryFormat
_memory_format
resize_as
:: Tensor
-> Tensor
-> ATen.MemoryFormat
-> Tensor
resize_as :: Tensor -> Tensor -> MemoryFormat -> Tensor
resize_as Tensor
_self Tensor
_the_template MemoryFormat
_memory_format = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> MemoryFormat -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> MemoryFormat -> IO (ForeignPtr Tensor)
ATen.resize_as_ttM) Tensor
_self Tensor
_the_template MemoryFormat
_memory_format
resize_as_sparse
:: Tensor
-> Tensor
-> Tensor
resize_as_sparse :: Tensor -> Tensor -> Tensor
resize_as_sparse Tensor
_self Tensor
_the_template = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.resize_as_sparse_tt) Tensor
_self Tensor
_the_template
zero
:: Tensor
-> Tensor
zero :: Tensor -> Tensor
zero Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.zero_t) Tensor
_self
sparse_resize
:: Tensor
-> [Int]
-> Int
-> Int
-> Tensor
sparse_resize :: Tensor -> [Int] -> Int -> Int -> Tensor
sparse_resize Tensor
_self [Int]
_size Int
_sparse_dim Int
_dense_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.sparse_resize_tlll) Tensor
_self [Int]
_size Int
_sparse_dim Int
_dense_dim
sparse_resize_and_clear
:: Tensor
-> [Int]
-> Int
-> Int
-> Tensor
sparse_resize_and_clear :: Tensor -> [Int] -> Int -> Int -> Tensor
sparse_resize_and_clear Tensor
_self [Int]
_size Int
_sparse_dim Int
_dense_dim = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> Int64 -> IO (ForeignPtr Tensor))
-> Tensor -> [Int] -> Int -> Int -> IO Tensor
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
cast4 ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
ATen.sparse_resize_and_clear_tlll) Tensor
_self [Int]
_size Int
_sparse_dim Int
_dense_dim
copy_sparse_to_sparse
:: Tensor
-> Tensor
-> Bool
-> Tensor
copy_sparse_to_sparse :: Tensor -> Tensor -> Bool -> Tensor
copy_sparse_to_sparse Tensor
_self Tensor
_src Bool
_non_blocking = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> Bool -> IO Tensor
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
cast3 ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
ATen.copy_sparse_to_sparse_ttb) Tensor
_self Tensor
_src Bool
_non_blocking
set_tt
:: Tensor
-> Tensor
-> Tensor
set_tt :: Tensor -> Tensor -> Tensor
set_tt Tensor
_self Tensor
_source = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> Tensor -> IO Tensor
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.set_tt) Tensor
_self Tensor
_source
set_t
:: Tensor
-> Tensor
set_t :: Tensor -> Tensor
set_t Tensor
_self = IO Tensor -> Tensor
forall a. IO a -> a
unsafePerformIO (IO Tensor -> Tensor) -> IO Tensor -> Tensor
forall a b. (a -> b) -> a -> b
$ ((ForeignPtr Tensor -> IO (ForeignPtr Tensor))
-> Tensor -> IO Tensor
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ATen.set_t) Tensor
_self