{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}

module Torch.Internal.Managed.Type.Tensor.Tensor2 where


import Foreign.C.String
import Foreign.C.Types
import Foreign
import Torch.Internal.Type
import Torch.Internal.Class
import Torch.Internal.Cast
import Torch.Internal.Objects
import qualified Torch.Internal.Unmanaged.Type.Tensor.Tensor2 as Unmanaged





tensor_sinh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_sinh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_sinh_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_sinh_

tensor_detach
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_detach :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_detach = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_detach

tensor_detach_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_detach_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_detach_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_detach_

tensor_size_n
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (Int64)
tensor_size_n :: ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64
tensor_size_n = (Ptr Tensor -> Ptr Dimname -> IO Int64)
-> ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Dimname -> IO Int64
Unmanaged.tensor_size_n

tensor_slice_llll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_slice_llll :: ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
tensor_slice_llll = (Ptr Tensor -> Int64 -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_slice_llll

tensor_slice_scatter_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_slice_scatter_tllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
tensor_slice_scatter_tllll = (Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Int64
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Int64
-> IO (Ptr Tensor)
Unmanaged.tensor_slice_scatter_tllll

tensor_select_scatter_tll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_select_scatter_tll :: ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
tensor_select_scatter_tll = (Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_select_scatter_tll

tensor_diagonal_scatter_tlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_diagonal_scatter_tlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
tensor_diagonal_scatter_tlll = (Ptr Tensor
 -> Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_diagonal_scatter_tlll

tensor_as_strided_scatter_tlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_as_strided_scatter_tlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
tensor_as_strided_scatter_tlll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
Unmanaged.tensor_as_strided_scatter_tlll

tensor_smm_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_smm_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_smm_t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_smm_t

tensor_softmax_ls
  :: ForeignPtr Tensor
  -> Int64
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_softmax_ls :: ForeignPtr Tensor -> Int64 -> ScalarType -> IO (ForeignPtr Tensor)
tensor_softmax_ls = (Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_softmax_ls

tensor_softmax_ns
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_softmax_ns :: ForeignPtr Tensor
-> ForeignPtr Dimname -> ScalarType -> IO (ForeignPtr Tensor)
tensor_softmax_ns = (Ptr Tensor -> Ptr Dimname -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Dimname -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_softmax_ns

tensor_unsafe_split_ll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_unsafe_split_ll :: ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
tensor_unsafe_split_ll = (Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr TensorList)
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 Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList)
Unmanaged.tensor_unsafe_split_ll

tensor_split_ll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_split_ll :: ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
tensor_split_ll = (Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr TensorList)
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 Ptr Tensor -> Int64 -> Int64 -> IO (Ptr TensorList)
Unmanaged.tensor_split_ll

-- tensor_split_ll
--   :: ForeignPtr Tensor
--   -> ForeignPtr IntArray
--   -> Int64
--   -> IO (ForeignPtr TensorList)
-- tensor_split_ll = cast3 Unmanaged.tensor_split_ll

tensor_unsafe_split_with_sizes_ll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_unsafe_split_with_sizes_ll :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList)
tensor_unsafe_split_with_sizes_ll = (Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr TensorList))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr TensorList)
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 Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr TensorList)
Unmanaged.tensor_unsafe_split_with_sizes_ll

tensor_split_with_sizes_ll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_split_with_sizes_ll :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr TensorList)
tensor_split_with_sizes_ll = (Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr TensorList))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr TensorList)
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 Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr TensorList)
Unmanaged.tensor_split_with_sizes_ll

tensor_squeeze
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_squeeze :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_squeeze = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_squeeze

tensor_squeeze_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_squeeze_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_squeeze_l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_squeeze_l

tensor_squeeze_n
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr Tensor)
tensor_squeeze_n :: ForeignPtr Tensor -> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
tensor_squeeze_n = (Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
Unmanaged.tensor_squeeze_n

-- tensor_squeeze_l
--   :: ForeignPtr Tensor
--   -> ForeignPtr IntArray
--   -> IO (ForeignPtr Tensor)
-- tensor_squeeze_l = cast2 Unmanaged.tensor_squeeze_l

tensor_squeeze_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_squeeze_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_squeeze_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_squeeze_

tensor_squeeze__l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_squeeze__l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_squeeze__l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_squeeze__l

-- tensor_squeeze__l
--   :: ForeignPtr Tensor
--   -> ForeignPtr IntArray
--   -> IO (ForeignPtr Tensor)
-- tensor_squeeze__l = cast2 Unmanaged.tensor_squeeze__l

tensor_squeeze__n
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr Tensor)
tensor_squeeze__n :: ForeignPtr Tensor -> ForeignPtr Dimname -> IO (ForeignPtr Tensor)
tensor_squeeze__n = (Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
Unmanaged.tensor_squeeze__n

tensor_sspaddmm_ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_sspaddmm_ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_sspaddmm_ttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.tensor_sspaddmm_ttss

tensor_stft_llltbbb
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_stft_llltbbb :: ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
tensor_stft_llltbbb = (Ptr Tensor
 -> Int64
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_stft_llltbbb

tensor_stft_llltbsbbb
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> CBool
  -> ForeignPtr StdString
  -> CBool
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_stft_llltbsbbb :: ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr StdString
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
tensor_stft_llltbsbbb = (Ptr Tensor
 -> Int64
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> CBool
 -> Ptr StdString
 -> CBool
 -> CBool
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr StdString
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> Ptr StdString
-> CBool
-> CBool
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_stft_llltbsbbb

tensor_istft_llltbbblb
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_istft_llltbbblb :: ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
tensor_istft_llltbbblb = (Ptr Tensor
 -> Int64
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> CBool
 -> Int64
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Int64
-> Int64
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> Int64
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_istft_llltbbblb

tensor_stride_n
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (Int64)
tensor_stride_n :: ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64
tensor_stride_n = (Ptr Tensor -> Ptr Dimname -> IO Int64)
-> ForeignPtr Tensor -> ForeignPtr Dimname -> IO Int64
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Dimname -> IO Int64
Unmanaged.tensor_stride_n

tensor_sum_s
  :: ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_sum_s :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_sum_s = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_sum_s

tensor_sum_lbs
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_sum_lbs :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_sum_lbs = (Ptr Tensor
 -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_sum_lbs

tensor_sum_Nbs
  :: ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_sum_Nbs :: ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_sum_Nbs = (Ptr Tensor
 -> Ptr DimnameList -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr DimnameList -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_sum_Nbs

tensor_nansum_lbs
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_nansum_lbs :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_nansum_lbs = (Ptr Tensor
 -> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr IntArray -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_nansum_lbs

tensor_sum_to_size_l
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_sum_to_size_l :: ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_sum_to_size_l = (Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.tensor_sum_to_size_l

tensor_sqrt
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_sqrt :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_sqrt = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_sqrt

tensor_sqrt_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_sqrt_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_sqrt_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_sqrt_

tensor_square
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_square :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_square = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_square

tensor_square_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_square_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_square_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_square_

tensor_std_b
  :: ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_std_b :: ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
tensor_std_b = (Ptr Tensor -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_std_b

tensor_std_lbb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_std_lbb :: ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> CBool -> IO (ForeignPtr Tensor)
tensor_std_lbb = (Ptr Tensor -> Ptr IntArray -> CBool -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> CBool -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_std_lbb

tensor_std_llb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_std_llb :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> CBool -> IO (ForeignPtr Tensor)
tensor_std_llb = (Ptr Tensor -> Ptr IntArray -> Int64 -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Int64 -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_std_llb

tensor_std_Nbb
  :: ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_std_Nbb :: ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
tensor_std_Nbb = (Ptr Tensor
 -> Ptr DimnameList -> CBool -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr DimnameList -> CBool -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_std_Nbb

tensor_std_Nlb
  :: ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_std_Nlb :: ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
tensor_std_Nlb = (Ptr Tensor
 -> Ptr DimnameList -> Int64 -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr DimnameList -> Int64 -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_std_Nlb

tensor_prod_s
  :: ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_prod_s :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_prod_s = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_prod_s

tensor_prod_lbs
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_prod_lbs :: ForeignPtr Tensor
-> Int64 -> CBool -> ScalarType -> IO (ForeignPtr Tensor)
tensor_prod_lbs = (Ptr Tensor -> Int64 -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_prod_lbs

tensor_prod_nbs
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_prod_nbs :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_prod_nbs = (Ptr Tensor
 -> Ptr Dimname -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Dimname -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_prod_nbs

tensor_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_t = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_t

tensor_t_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_t_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_t_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_t_

tensor_tan
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_tan :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_tan = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_tan

tensor_tan_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_tan_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_tan_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_tan_

tensor_tanh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_tanh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_tanh = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_tanh

tensor_tanh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_tanh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_tanh_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_tanh_

tensor_tile_l
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_tile_l :: ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_tile_l = (Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.tensor_tile_l

tensor_transpose_ll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_transpose_ll :: ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
tensor_transpose_ll = (Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_transpose_ll

tensor_transpose_nn
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Dimname
  -> IO (ForeignPtr Tensor)
tensor_transpose_nn :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
tensor_transpose_nn = (Ptr Tensor -> Ptr Dimname -> Ptr Dimname -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Dimname
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Dimname -> Ptr Dimname -> IO (Ptr Tensor)
Unmanaged.tensor_transpose_nn

tensor_transpose__ll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_transpose__ll :: ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
tensor_transpose__ll = (Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_transpose__ll

tensor_flip_l
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_flip_l :: ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_flip_l = (Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.tensor_flip_l

tensor_fliplr
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_fliplr :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_fliplr = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_fliplr

tensor_flipud
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_flipud :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_flipud = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_flipud

tensor_roll_ll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_roll_ll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
tensor_roll_ll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.tensor_roll_ll

tensor_rot90_ll
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_rot90_ll :: ForeignPtr Tensor
-> Int64 -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_rot90_ll = (Ptr Tensor -> Int64 -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr IntArray
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.tensor_rot90_ll

tensor__nested_tensor_size
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__nested_tensor_size :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__nested_tensor_size = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor__nested_tensor_size

tensor__nested_tensor_strides
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__nested_tensor_strides :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__nested_tensor_strides = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor__nested_tensor_strides

-- tensor__nested_tensor_offsets
--   :: ForeignPtr Tensor
--   -> IO (ForeignPtr IntArray)
-- tensor__nested_tensor_offsets = cast1 Unmanaged.tensor__nested_tensor_offsets

tensor_trunc
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_trunc :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_trunc = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_trunc

tensor_trunc_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_trunc_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_trunc_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_trunc_

tensor_fix
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_fix :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_fix = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_fix

tensor_fix_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_fix_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_fix_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_fix_

tensor_type_as_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_type_as_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_type_as_t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_type_as_t

tensor_unsqueeze_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_unsqueeze_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_unsqueeze_l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_unsqueeze_l

tensor_unsqueeze__l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_unsqueeze__l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_unsqueeze__l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_unsqueeze__l

tensor_var_b
  :: ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_var_b :: ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
tensor_var_b = (Ptr Tensor -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_var_b

tensor_var_lbb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_var_lbb :: ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> CBool -> IO (ForeignPtr Tensor)
tensor_var_lbb = (Ptr Tensor -> Ptr IntArray -> CBool -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> CBool -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_var_lbb

tensor_var_llb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_var_llb :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> CBool -> IO (ForeignPtr Tensor)
tensor_var_llb = (Ptr Tensor -> Ptr IntArray -> Int64 -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Int64 -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_var_llb

tensor_var_Nbb
  :: ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_var_Nbb :: ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
tensor_var_Nbb = (Ptr Tensor
 -> Ptr DimnameList -> CBool -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr DimnameList -> CBool -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_var_Nbb

tensor_var_Nlb
  :: ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_var_Nlb :: ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
tensor_var_Nlb = (Ptr Tensor
 -> Ptr DimnameList -> Int64 -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> Int64
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr DimnameList -> Int64 -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_var_Nlb

tensor_view_as_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_view_as_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_view_as_t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_view_as_t

tensor_where_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_where_tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_where_tt = (Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_where_tt

tensor_where_ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_where_ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_where_ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_where_ts

tensor_norm_ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_norm_ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ScalarType -> IO (ForeignPtr Tensor)
tensor_norm_ss = (Ptr Tensor -> Ptr Scalar -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Scalar -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_norm_ss

tensor_norm_s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_norm_s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_norm_s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_norm_s

tensor_norm_slbs
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_norm_slbs :: ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_norm_slbs = (Ptr Tensor
 -> Ptr Scalar
 -> Ptr IntArray
 -> CBool
 -> ScalarType
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Scalar
-> Ptr IntArray
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
Unmanaged.tensor_norm_slbs

tensor_norm_slb
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_norm_slb :: ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
tensor_norm_slb = (Ptr Tensor
 -> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Scalar -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_norm_slb

tensor_norm_sNbs
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr DimnameList
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_norm_sNbs :: ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_norm_sNbs = (Ptr Tensor
 -> Ptr Scalar
 -> Ptr DimnameList
 -> CBool
 -> ScalarType
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Scalar
-> Ptr DimnameList
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
Unmanaged.tensor_norm_sNbs

tensor_norm_sNb
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr DimnameList
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_norm_sNb :: ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor)
tensor_norm_sNb = (Ptr Tensor
 -> Ptr Scalar -> Ptr DimnameList -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Scalar -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_norm_sNb

tensor_frexp
  :: ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
tensor_frexp :: ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
tensor_frexp = (Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.tensor_frexp

tensor_clone_M
  :: ForeignPtr Tensor
  -> MemoryFormat
  -> IO (ForeignPtr Tensor)
tensor_clone_M :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_clone_M = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_clone_M

tensor_positive
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_positive :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_positive = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_positive

tensor_resize_as__tM
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> MemoryFormat
  -> IO (ForeignPtr Tensor)
tensor_resize_as__tM :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_resize_as__tM = (Ptr Tensor -> Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_resize_as__tM

tensor_resize_as_sparse__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_resize_as_sparse__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_resize_as_sparse__t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_resize_as_sparse__t

tensor_zero_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_zero_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_zero_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_zero_

tensor_sub_ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_sub_ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_sub_ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_sub_ts

tensor_sub__ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_sub__ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_sub__ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_sub__ts

tensor_sub_ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_sub_ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_sub_ss = (Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_sub_ss

tensor_sub__ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_sub__ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_sub__ss = (Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_sub__ss

tensor_subtract_ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_subtract_ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_subtract_ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_subtract_ts

tensor_subtract__ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_subtract__ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_subtract__ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_subtract__ts

tensor_subtract_ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_subtract_ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_subtract_ss = (Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_subtract_ss

tensor_subtract__ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_subtract__ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_subtract__ss = (Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Scalar -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_subtract__ss

tensor_heaviside_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_heaviside_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_heaviside_t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_heaviside_t

tensor_heaviside__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_heaviside__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_heaviside__t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_heaviside__t

tensor_addmm_ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_addmm_ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_addmm_ttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.tensor_addmm_ttss

tensor_addmm__ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_addmm__ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_addmm__ttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.tensor_addmm__ttss

tensor__addmm_activation_ttssb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor__addmm_activation_ttssb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> CBool
-> IO (ForeignPtr Tensor)
tensor__addmm_activation_ttssb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Scalar
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor__addmm_activation_ttssb

tensor_sparse_resize__lll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_sparse_resize__lll :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
tensor_sparse_resize__lll = (Ptr Tensor -> Ptr IntArray -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_sparse_resize__lll

tensor_sparse_resize_and_clear__lll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_sparse_resize_and_clear__lll :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
tensor_sparse_resize_and_clear__lll = (Ptr Tensor -> Ptr IntArray -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_sparse_resize_and_clear__lll

tensor_sparse_mask_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_sparse_mask_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_sparse_mask_t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_sparse_mask_t

tensor_to_dense_s
  :: ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_to_dense_s :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_to_dense_s = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_to_dense_s

tensor__to_dense_s
  :: ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor__to_dense_s :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor__to_dense_s = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor__to_dense_s

tensor_sparse_dim
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_sparse_dim :: ForeignPtr Tensor -> IO Int64
tensor_sparse_dim = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor_sparse_dim

tensor__dimI
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor__dimI :: ForeignPtr Tensor -> IO Int64
tensor__dimI = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor__dimI

tensor_dense_dim
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_dense_dim :: ForeignPtr Tensor -> IO Int64
tensor_dense_dim = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor_dense_dim

tensor__dimV
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor__dimV :: ForeignPtr Tensor -> IO Int64
tensor__dimV = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor__dimV

tensor__nnz
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor__nnz :: ForeignPtr Tensor -> IO Int64
tensor__nnz = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor__nnz

tensor_coalesce
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_coalesce :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_coalesce = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_coalesce

tensor_is_coalesced
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_coalesced :: ForeignPtr Tensor -> IO CBool
tensor_is_coalesced = (Ptr Tensor -> IO CBool) -> ForeignPtr Tensor -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO CBool
Unmanaged.tensor_is_coalesced

tensor__indices
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__indices :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__indices = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor__indices

tensor__values
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__values :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__values = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor__values

tensor__coalesced__b
  :: ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor__coalesced__b :: ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
tensor__coalesced__b = (Ptr Tensor -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor__coalesced__b

tensor_indices
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_indices :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_indices = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_indices

tensor_values
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_values :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_values = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_values

tensor_crow_indices
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_crow_indices :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_crow_indices = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_crow_indices

tensor_col_indices
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_col_indices :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_col_indices = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_col_indices

tensor_ccol_indices
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_ccol_indices :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_ccol_indices = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_ccol_indices

tensor_row_indices
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_row_indices :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_row_indices = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_row_indices

tensor_unbind_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_unbind_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
tensor_unbind_l = (Ptr Tensor -> Int64 -> IO (Ptr TensorList))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr TensorList)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr TensorList)
Unmanaged.tensor_unbind_l

tensor_unbind_n
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr TensorList)
tensor_unbind_n :: ForeignPtr Tensor
-> ForeignPtr Dimname -> IO (ForeignPtr TensorList)
tensor_unbind_n = (Ptr Tensor -> Ptr Dimname -> IO (Ptr TensorList))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr TensorList)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Dimname -> IO (Ptr TensorList)
Unmanaged.tensor_unbind_n

tensor_to_sparse_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_to_sparse_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_to_sparse_l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_to_sparse_l

tensor_to_sparse_Lll
  :: ForeignPtr Tensor
  -> Layout
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_to_sparse_Lll :: ForeignPtr Tensor
-> ScalarType
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
tensor_to_sparse_Lll = (Ptr Tensor
 -> ScalarType -> Ptr IntArray -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ScalarType
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor
-> ScalarType -> Ptr IntArray -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_to_sparse_Lll

tensor_to_sparse_csr_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_to_sparse_csr_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_to_sparse_csr_l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_to_sparse_csr_l

tensor_to_sparse_csc_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_to_sparse_csc_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor_to_sparse_csc_l = (Ptr Tensor -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_to_sparse_csc_l

tensor_to_sparse_bsr_ll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_to_sparse_bsr_ll :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr Tensor)
tensor_to_sparse_bsr_ll = (Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_to_sparse_bsr_ll

tensor_to_sparse_bsc_ll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor_to_sparse_bsc_ll :: ForeignPtr Tensor
-> ForeignPtr IntArray -> Int64 -> IO (ForeignPtr Tensor)
tensor_to_sparse_bsc_ll = (Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr IntArray -> Int64 -> IO (Ptr Tensor)
Unmanaged.tensor_to_sparse_bsc_ll

tensor_to_mkldnn_s
  :: ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_to_mkldnn_s :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_to_mkldnn_s = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_to_mkldnn_s

tensor_dequantize
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_dequantize :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_dequantize = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_dequantize

tensor_q_scale
  :: ForeignPtr Tensor
  -> IO (CDouble)
tensor_q_scale :: ForeignPtr Tensor -> IO CDouble
tensor_q_scale = (Ptr Tensor -> IO CDouble) -> ForeignPtr Tensor -> IO CDouble
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO CDouble
Unmanaged.tensor_q_scale

tensor_q_zero_point
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_q_zero_point :: ForeignPtr Tensor -> IO Int64
tensor_q_zero_point = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor_q_zero_point

tensor_q_per_channel_scales
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_q_per_channel_scales :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_q_per_channel_scales = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_q_per_channel_scales

tensor_q_per_channel_zero_points
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_q_per_channel_zero_points :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_q_per_channel_zero_points = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_q_per_channel_zero_points

tensor_q_per_channel_axis
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_q_per_channel_axis :: ForeignPtr Tensor -> IO Int64
tensor_q_per_channel_axis = (Ptr Tensor -> IO Int64) -> ForeignPtr Tensor -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO Int64
Unmanaged.tensor_q_per_channel_axis

tensor_int_repr
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_int_repr :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_int_repr = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_int_repr

tensor_qscheme
  :: ForeignPtr Tensor
  -> IO (QScheme)
tensor_qscheme :: ForeignPtr Tensor -> IO ScalarType
tensor_qscheme = (Ptr Tensor -> IO ScalarType) -> ForeignPtr Tensor -> IO ScalarType
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO ScalarType
Unmanaged.tensor_qscheme

tensor__autocast_to_reduced_precision_bbss
  :: ForeignPtr Tensor
  -> CBool
  -> CBool
  -> ScalarType
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor__autocast_to_reduced_precision_bbss :: ForeignPtr Tensor
-> CBool
-> CBool
-> ScalarType
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor__autocast_to_reduced_precision_bbss = (Ptr Tensor
 -> CBool -> CBool -> ScalarType -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> CBool
-> CBool
-> ScalarType
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> CBool -> CBool -> ScalarType -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor__autocast_to_reduced_precision_bbss

tensor__autocast_to_full_precision_bb
  :: ForeignPtr Tensor
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor__autocast_to_full_precision_bb :: ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr Tensor)
tensor__autocast_to_full_precision_bb = (Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> CBool -> CBool -> IO (ForeignPtr 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 Ptr Tensor -> CBool -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor__autocast_to_full_precision_bb

tensor_to_obbM
  :: ForeignPtr Tensor
  -> ForeignPtr TensorOptions
  -> CBool
  -> CBool
  -> MemoryFormat
  -> IO (ForeignPtr Tensor)
tensor_to_obbM :: ForeignPtr Tensor
-> ForeignPtr TensorOptions
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_to_obbM = (Ptr Tensor
 -> Ptr TensorOptions
 -> CBool
 -> CBool
 -> ScalarType
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr TensorOptions
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr TensorOptions
-> CBool
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
Unmanaged.tensor_to_obbM

tensor_to_DsbbM
  :: ForeignPtr Tensor
  -> DeviceType
  -> ScalarType
  -> CBool
  -> CBool
  -> MemoryFormat
  -> IO (ForeignPtr Tensor)
tensor_to_DsbbM :: ForeignPtr Tensor
-> DeviceType
-> ScalarType
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_to_DsbbM = (Ptr Tensor
 -> DeviceType
 -> ScalarType
 -> CBool
 -> CBool
 -> ScalarType
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> DeviceType
-> ScalarType
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> DeviceType
-> ScalarType
-> CBool
-> CBool
-> ScalarType
-> IO (Ptr Tensor)
Unmanaged.tensor_to_DsbbM

tensor_to_sbbM
  :: ForeignPtr Tensor
  -> ScalarType
  -> CBool
  -> CBool
  -> MemoryFormat
  -> IO (ForeignPtr Tensor)
tensor_to_sbbM :: ForeignPtr Tensor
-> ScalarType
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_to_sbbM = (Ptr Tensor
 -> ScalarType -> CBool -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ScalarType
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> ScalarType -> CBool -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_to_sbbM

tensor_to_tbbM
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> MemoryFormat
  -> IO (ForeignPtr Tensor)
tensor_to_tbbM :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr Tensor)
tensor_to_tbbM = (Ptr Tensor
 -> Ptr Tensor -> CBool -> CBool -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> ScalarType
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor -> CBool -> CBool -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_to_tbbM

tensor_item
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Scalar)
tensor_item :: ForeignPtr Tensor -> IO (ForeignPtr Scalar)
tensor_item = (Ptr Tensor -> IO (Ptr Scalar))
-> ForeignPtr Tensor -> IO (ForeignPtr Scalar)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Scalar)
Unmanaged.tensor_item

tensor_set__S
  :: ForeignPtr Tensor
  -> ForeignPtr Storage
  -> IO (ForeignPtr Tensor)
tensor_set__S :: ForeignPtr Tensor -> ForeignPtr Storage -> IO (ForeignPtr Tensor)
tensor_set__S = (Ptr Tensor -> Ptr Storage -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Storage
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Storage -> IO (Ptr Tensor)
Unmanaged.tensor_set__S

tensor_set__Slll
  :: ForeignPtr Tensor
  -> ForeignPtr Storage
  -> Int64
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_set__Slll :: ForeignPtr Tensor
-> ForeignPtr Storage
-> Int64
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
tensor_set__Slll = (Ptr Tensor
 -> Ptr Storage
 -> Int64
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Storage
-> Int64
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Storage
-> Int64
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.tensor_set__Slll

tensor_set__tlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_set__tlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
tensor_set__tlll = (Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Tensor
-> Int64
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.tensor_set__tlll

tensor_set__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_set__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_set__t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_set__t

tensor_set_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_set_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_set_ = (Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
cast1 Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_set_

tensor_is_set_to_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (CBool)
tensor_is_set_to_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool
tensor_is_set_to_t = (Ptr Tensor -> Ptr Tensor -> IO CBool)
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO CBool
Unmanaged.tensor_is_set_to_t

tensor_masked_fill__ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_masked_fill__ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_masked_fill__ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_masked_fill__ts

tensor_masked_fill_ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_masked_fill_ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_masked_fill_ts = (Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_masked_fill_ts

tensor_masked_fill__tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_masked_fill__tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_masked_fill__tt = (Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_masked_fill__tt

tensor_masked_fill_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_masked_fill_tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_masked_fill_tt = (Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_masked_fill_tt

tensor_masked_scatter__tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_masked_scatter__tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_masked_scatter__tt = (Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_masked_scatter__tt

tensor_masked_scatter_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_masked_scatter_tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_masked_scatter_tt = (Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_masked_scatter_tt

tensor_view_l
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_view_l :: ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_view_l = (Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.tensor_view_l

tensor_view_s
  :: ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr Tensor)
tensor_view_s :: ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
tensor_view_s = (Ptr Tensor -> ScalarType -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ScalarType -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> ScalarType -> IO (Ptr Tensor)
Unmanaged.tensor_view_s

tensor_put__ttb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_put__ttb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
tensor_put__ttb = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_put__ttb

tensor_put_ttb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_put_ttb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
tensor_put_ttb = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor -> Ptr Tensor -> Ptr Tensor -> CBool -> IO (Ptr Tensor)
Unmanaged.tensor_put_ttb

tensor_index_add__ltts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_add__ltts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_add__ltts = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.tensor_index_add__ltts

tensor_index_add_ltts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_add_ltts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_add_ltts = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.tensor_index_add_ltts

tensor_index_add_ntts
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_add_ntts :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_add_ntts = (Ptr Tensor
 -> Ptr Dimname
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.tensor_index_add_ntts

tensor_index_reduce__lttsb
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_index_reduce__lttsb :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
tensor_index_reduce__lttsb = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_index_reduce__lttsb

tensor_index_reduce_lttsb
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_index_reduce_lttsb :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
tensor_index_reduce_lttsb = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_index_reduce_lttsb

tensor_index_fill__lts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_fill__lts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_fill__lts = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill__lts

tensor_index_fill_lts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_fill_lts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_fill_lts = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill_lts

tensor_index_fill__ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_index_fill__ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_index_fill__ltt = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill__ltt

tensor_index_fill_ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_index_fill_ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_index_fill_ltt = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill_ltt

tensor_index_fill__nts
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_fill__nts :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_fill__nts = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill__nts

tensor_index_fill__ntt
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_index_fill__ntt :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_index_fill__ntt = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill__ntt

tensor_index_fill_nts
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_index_fill_nts :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_index_fill_nts = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill_nts

tensor_index_fill_ntt
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_index_fill_ntt :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_index_fill_ntt = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_index_fill_ntt

tensor_scatter_ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_scatter_ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_scatter_ltt = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_ltt

tensor_scatter__ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_scatter__ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_scatter__ltt = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_scatter__ltt

tensor_scatter_lts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_scatter_lts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_scatter_lts = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_lts

tensor_scatter__lts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_scatter__lts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_scatter__lts = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_scatter__lts

tensor_scatter_ltts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> IO (ForeignPtr Tensor)
tensor_scatter_ltts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
tensor_scatter_ltts = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
Unmanaged.tensor_scatter_ltts

tensor_scatter__ltts
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> IO (ForeignPtr Tensor)
tensor_scatter__ltts :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
tensor_scatter__ltts = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> IO (Ptr Tensor)
Unmanaged.tensor_scatter__ltts

tensor_scatter_ltss
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr StdString
  -> IO (ForeignPtr Tensor)
tensor_scatter_ltss :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
tensor_scatter_ltss = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr StdString
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> Ptr StdString
-> IO (Ptr Tensor)
Unmanaged.tensor_scatter_ltss

tensor_scatter__ltss
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr StdString
  -> IO (ForeignPtr Tensor)
tensor_scatter__ltss :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
tensor_scatter__ltss = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr StdString
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr StdString
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Scalar
-> Ptr StdString
-> IO (Ptr Tensor)
Unmanaged.tensor_scatter__ltss

tensor_scatter_ntt
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_scatter_ntt :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_scatter_ntt = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_ntt

tensor_scatter_nts
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_scatter_nts :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_scatter_nts = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_nts

tensor_scatter_add_ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_scatter_add_ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_scatter_add_ltt = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_add_ltt

tensor_scatter_add__ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_scatter_add__ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_scatter_add__ltt = (Ptr Tensor
 -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor -> Int64 -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_add__ltt

tensor_scatter_add_ntt
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_scatter_add_ntt :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_scatter_add_ntt = (Ptr Tensor
 -> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr 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 Ptr Tensor
-> Ptr Dimname -> Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_scatter_add_ntt

tensor_scatter_reduce_lttsb
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_scatter_reduce_lttsb :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
tensor_scatter_reduce_lttsb = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_scatter_reduce_lttsb

tensor_scatter_reduce__lttsb
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_scatter_reduce__lttsb :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
tensor_scatter_reduce__lttsb = (Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr 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 Ptr Tensor
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (Ptr Tensor)
Unmanaged.tensor_scatter_reduce__lttsb

tensor_eq__s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_eq__s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_eq__s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_eq__s

tensor_eq__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_eq__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_eq__t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_eq__t

tensor_bitwise_and_s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_bitwise_and_s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_bitwise_and_s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_bitwise_and_s

tensor_bitwise_and_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_bitwise_and_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_bitwise_and_t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_bitwise_and_t

tensor_bitwise_and__s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_bitwise_and__s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_bitwise_and__s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_bitwise_and__s

tensor_bitwise_and__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_bitwise_and__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_bitwise_and__t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor_bitwise_and__t

tensor___and___s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor___and___s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor___and___s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor___and___s

tensor___and___t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor___and___t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor___and___t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor___and___t

tensor___iand___s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor___iand___s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor___iand___s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor___iand___s

tensor___iand___t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor___iand___t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor___iand___t = (Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged.tensor___iand___t

tensor_bitwise_or_s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_bitwise_or_s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_bitwise_or_s = (Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor))
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
cast2 Ptr Tensor -> Ptr Scalar -> IO (Ptr Tensor)
Unmanaged.tensor_bitwise_or_s