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

module Torch.Internal.Managed.Type.Tensor.Tensor0 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.Tensor0 as Unmanaged





newTensor
  :: IO (ForeignPtr Tensor)
newTensor :: IO (ForeignPtr Tensor)
newTensor = IO (Ptr Tensor) -> IO (ForeignPtr Tensor)
forall a ca. Castable a ca => IO ca -> IO a
cast0 IO (Ptr Tensor)
Unmanaged.newTensor

newTensor_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
newTensor_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
newTensor_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.newTensor_t

tensor___dispatch_contiguous
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor___dispatch_contiguous :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor___dispatch_contiguous = (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___dispatch_contiguous

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

tensor_contiguous
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_contiguous :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_contiguous = (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_contiguous

tensor_cpu
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cpu :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_cpu = (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_cpu

tensor_cuda
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cuda :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_cuda = (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_cuda

tensor_mps
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_mps :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_mps = (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_mps

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

tensor_defined
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_defined :: ForeignPtr Tensor -> IO CBool
tensor_defined = (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_defined

tensor_dim
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_dim :: ForeignPtr Tensor -> IO Int64
tensor_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_dim

tensor_element_size
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_element_size :: ForeignPtr Tensor -> IO Int64
tensor_element_size = (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_element_size

tensor_get_device
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_get_device :: ForeignPtr Tensor -> IO Int64
tensor_get_device = (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_get_device

tensor_has_names
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_has_names :: ForeignPtr Tensor -> IO CBool
tensor_has_names = (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_has_names

tensor_has_storage
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_has_storage :: ForeignPtr Tensor -> IO CBool
tensor_has_storage = (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_has_storage

tensor_hip
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_hip :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_hip = (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_hip

tensor_is_alias_of_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (CBool)
tensor_is_alias_of_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool
tensor_is_alias_of_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_alias_of_t

tensor_is_contiguous
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_contiguous :: ForeignPtr Tensor -> IO CBool
tensor_is_contiguous = (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_contiguous

tensor_is_cuda
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_cuda :: ForeignPtr Tensor -> IO CBool
tensor_is_cuda = (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_cuda

tensor_is_mps
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_mps :: ForeignPtr Tensor -> IO CBool
tensor_is_mps = (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_mps

tensor_is_hip
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_hip :: ForeignPtr Tensor -> IO CBool
tensor_is_hip = (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_hip

tensor_is_meta
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_meta :: ForeignPtr Tensor -> IO CBool
tensor_is_meta = (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_meta

tensor_is_metal
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_metal :: ForeignPtr Tensor -> IO CBool
tensor_is_metal = (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_metal

tensor_is_mkldnn
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_mkldnn :: ForeignPtr Tensor -> IO CBool
tensor_is_mkldnn = (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_mkldnn

tensor_is_non_overlapping_and_dense
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_non_overlapping_and_dense :: ForeignPtr Tensor -> IO CBool
tensor_is_non_overlapping_and_dense = (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_non_overlapping_and_dense

tensor_is_quantized
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_quantized :: ForeignPtr Tensor -> IO CBool
tensor_is_quantized = (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_quantized

tensor_is_same_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (CBool)
tensor_is_same_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO CBool
tensor_is_same_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_same_t

tensor_is_sparse
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_sparse :: ForeignPtr Tensor -> IO CBool
tensor_is_sparse = (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_sparse

tensor_is_vulkan
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_vulkan :: ForeignPtr Tensor -> IO CBool
tensor_is_vulkan = (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_vulkan

tensor_is_xpu
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_xpu :: ForeignPtr Tensor -> IO CBool
tensor_is_xpu = (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_xpu

tensor_item_double
  :: ForeignPtr Tensor
  -> IO (CDouble)
tensor_item_double :: ForeignPtr Tensor -> IO CDouble
tensor_item_double = (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_item_double

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

tensor_item_int64_t
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_item_int64_t :: ForeignPtr Tensor -> IO Int64
tensor_item_int64_t = (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_item_int64_t

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

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

tensor_metal
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_metal :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_metal = (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_metal

tensor_mutable_grad
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_mutable_grad :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_mutable_grad = (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_mutable_grad

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

tensor_ndimension
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_ndimension :: ForeignPtr Tensor -> IO Int64
tensor_ndimension = (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_ndimension

tensor_numel
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_numel :: ForeignPtr Tensor -> IO Int64
tensor_numel = (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_numel

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

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

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

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

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

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

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

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

tensor__assign__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__assign__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__assign__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__assign__t

tensor__at__s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor__at__s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor__at__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__at__s

tensor__at__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__at__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__at__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__at__t

tensor__at__l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor__at__l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor__at__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__at__l

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

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

tensor_requires_grad
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_requires_grad :: ForeignPtr Tensor -> IO CBool
tensor_requires_grad = (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_requires_grad

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

tensor_resize__l
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_resize__l :: ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_resize__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_resize__l

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

tensor_set_requires_grad_b
  :: ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_set_requires_grad_b :: ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
tensor_set_requires_grad_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_set_requires_grad_b

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

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

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

tensor_storage_offset
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_storage_offset :: ForeignPtr Tensor -> IO Int64
tensor_storage_offset = (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_storage_offset

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

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

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

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

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

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

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

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

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

tensor_to_dense
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_to_dense :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_to_dense = (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_to_dense

tensor_to_mkldnn
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_to_mkldnn :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_to_mkldnn = (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_to_mkldnn

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

tensor_vulkan
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_vulkan :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_vulkan = (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_vulkan

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

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

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

tensor_data
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_data :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_data = (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_data

tensor_is_leaf
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_is_leaf :: ForeignPtr Tensor -> IO CBool
tensor_is_leaf = (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_leaf

tensor_output_nr
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor_output_nr :: ForeignPtr Tensor -> IO Int64
tensor_output_nr = (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_output_nr

tensor__version
  :: ForeignPtr Tensor
  -> IO (Int64)
tensor__version :: ForeignPtr Tensor -> IO Int64
tensor__version = (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__version

tensor_requires_grad__b
  :: ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
tensor_requires_grad__b :: ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
tensor_requires_grad__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_requires_grad__b

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

tensor_retains_grad
  :: ForeignPtr Tensor
  -> IO (CBool)
tensor_retains_grad :: ForeignPtr Tensor -> IO CBool
tensor_retains_grad = (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_retains_grad

tensor__fw_primal_l
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
tensor__fw_primal_l :: ForeignPtr Tensor -> Int64 -> IO (ForeignPtr Tensor)
tensor__fw_primal_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__fw_primal_l

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

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

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

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

tensor_align_as_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_align_as_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_align_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_align_as_t

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

tensor_abs
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_abs :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_abs = (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_abs

tensor_abs_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_abs_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_abs_ = (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_abs_

tensor_absolute
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_absolute :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_absolute = (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_absolute

tensor_absolute_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_absolute_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_absolute_ = (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_absolute_

tensor_angle
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_angle :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_angle = (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_angle

tensor_sgn
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_sgn :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_sgn = (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_sgn

tensor_sgn_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_sgn_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_sgn_ = (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_sgn_

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

tensor__conj
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__conj :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__conj = (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__conj

tensor_conj
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_conj :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_conj = (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_conj

tensor__conj_physical
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__conj_physical :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__conj_physical = (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__conj_physical

tensor_conj_physical
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_conj_physical :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_conj_physical = (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_conj_physical

tensor_conj_physical_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_conj_physical_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_conj_physical_ = (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_conj_physical_

tensor_resolve_conj
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_resolve_conj :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_resolve_conj = (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_resolve_conj

tensor_resolve_neg
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_resolve_neg :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_resolve_neg = (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_resolve_neg

tensor__neg_view
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__neg_view :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__neg_view = (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__neg_view

tensor_acos
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_acos :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_acos = (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_acos

tensor_acos_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_acos_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_acos_ = (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_acos_

tensor_arccos
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arccos :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arccos = (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_arccos

tensor_arccos_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arccos_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arccos_ = (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_arccos_

tensor_add_ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_add_ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_add_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_add_ts

tensor_add__ts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_add__ts :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_add__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_add__ts

tensor_add_ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_add_ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_add_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_add_ss

tensor_add__ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_add__ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_add__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_add__ss

tensor_addmv_ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_addmv_ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_addmv_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_addmv_ttss

tensor_addmv__ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_addmv__ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_addmv__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_addmv__ttss

tensor_addr_ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_addr_ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_addr_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_addr_ttss

tensor_addr__ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_addr__ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_addr__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_addr__ttss

tensor__is_all_true
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__is_all_true :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__is_all_true = (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__is_all_true

tensor__is_any_true
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor__is_any_true :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor__is_any_true = (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__is_any_true

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

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

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

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

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

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

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

tensor_acosh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_acosh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_acosh = (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_acosh

tensor_acosh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_acosh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_acosh_ = (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_acosh_

tensor_arccosh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arccosh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arccosh = (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_arccosh

tensor_arccosh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arccosh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arccosh_ = (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_arccosh_

tensor_asinh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_asinh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_asinh = (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_asinh

tensor_asinh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_asinh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_asinh_ = (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_asinh_

tensor_arcsinh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arcsinh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arcsinh = (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_arcsinh

tensor_arcsinh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arcsinh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arcsinh_ = (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_arcsinh_

tensor_atanh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_atanh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_atanh = (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_atanh

tensor_atanh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_atanh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_atanh_ = (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_atanh_

tensor_arctanh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arctanh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arctanh = (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_arctanh

tensor_arctanh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arctanh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arctanh_ = (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_arctanh_

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

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

tensor_asin
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_asin :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_asin = (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_asin

tensor_asin_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_asin_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_asin_ = (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_asin_

tensor_arcsin
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arcsin :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arcsin = (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_arcsin

tensor_arcsin_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arcsin_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arcsin_ = (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_arcsin_

tensor_atan
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_atan :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_atan = (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_atan

tensor_atan_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_atan_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_atan_ = (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_atan_

tensor_arctan
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arctan :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arctan = (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_arctan

tensor_arctan_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_arctan_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_arctan_ = (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_arctan_

tensor_baddbmm_ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_baddbmm_ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_baddbmm_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_baddbmm_ttss

tensor_baddbmm__ttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_baddbmm__ttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
tensor_baddbmm__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_baddbmm__ttss

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

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

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

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

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

tensor_bitwise_not
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_bitwise_not :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_bitwise_not = (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_bitwise_not

tensor_bitwise_not_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_bitwise_not_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_bitwise_not_ = (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_bitwise_not_

tensor_copysign_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_copysign_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_copysign_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_copysign_t

tensor_copysign__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_copysign__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_copysign__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_copysign__t

tensor_copysign_s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_copysign_s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_copysign_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_copysign_s

tensor_copysign__s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_copysign__s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_copysign__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_copysign__s

tensor_logical_not
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_not :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_not = (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_logical_not

tensor_logical_not_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_not_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_not_ = (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_logical_not_

tensor_logical_xor_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_xor_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_xor_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_logical_xor_t

tensor_logical_xor__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_xor__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_xor__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_logical_xor__t

tensor_logical_and_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_and_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_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_logical_and_t

tensor_logical_and__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_and__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_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_logical_and__t

tensor_logical_or_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_or_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_or_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_logical_or_t

tensor_logical_or__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_logical_or__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_logical_or__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_logical_or__t

tensor_bmm_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_bmm_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_bmm_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_bmm_t

tensor_broadcast_to_l
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
tensor_broadcast_to_l :: ForeignPtr Tensor -> ForeignPtr IntArray -> IO (ForeignPtr Tensor)
tensor_broadcast_to_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_broadcast_to_l

tensor_ceil
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_ceil :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_ceil = (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_ceil

tensor_ceil_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_ceil_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_ceil_ = (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_ceil_

tensor_unsafe_chunk_ll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_unsafe_chunk_ll :: ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
tensor_unsafe_chunk_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_chunk_ll

tensor_chunk_ll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr TensorList)
tensor_chunk_ll :: ForeignPtr Tensor -> Int64 -> Int64 -> IO (ForeignPtr TensorList)
tensor_chunk_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_chunk_ll

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

tensor_clamp_ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clamp_ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clamp_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_clamp_ss

tensor_clamp_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clamp_tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clamp_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_clamp_tt

tensor_clamp__ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clamp__ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clamp__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_clamp__ss

tensor_clamp__tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clamp__tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clamp__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_clamp__tt

tensor_clamp_max_s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clamp_max_s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clamp_max_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_clamp_max_s

tensor_clamp_max_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clamp_max_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clamp_max_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_clamp_max_t

tensor_clamp_max__s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clamp_max__s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clamp_max__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_clamp_max__s

tensor_clamp_max__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clamp_max__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clamp_max__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_clamp_max__t

tensor_clamp_min_s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clamp_min_s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clamp_min_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_clamp_min_s

tensor_clamp_min_t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clamp_min_t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clamp_min_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_clamp_min_t

tensor_clamp_min__s
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clamp_min__s :: ForeignPtr Tensor -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clamp_min__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_clamp_min__s

tensor_clamp_min__t
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clamp_min__t :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clamp_min__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_clamp_min__t

tensor_clip_ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clip_ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clip_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_clip_ss

tensor_clip_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clip_tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clip_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_clip_tt

tensor_clip__ss
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
tensor_clip__ss :: ForeignPtr Tensor
-> ForeignPtr Scalar -> ForeignPtr Scalar -> IO (ForeignPtr Tensor)
tensor_clip__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_clip__ss

tensor_clip__tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_clip__tt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_clip__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_clip__tt

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

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

tensor_cos
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cos :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_cos = (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_cos

tensor_cos_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cos_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_cos_ = (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_cos_

tensor_cosh
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cosh :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_cosh = (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_cosh

tensor_cosh_
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cosh_ :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_cosh_ = (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_cosh_

tensor_cov_ltt
  :: ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_cov_ltt :: ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
tensor_cov_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_cov_ltt

tensor_corrcoef
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tensor_corrcoef :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tensor_corrcoef = (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_corrcoef

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

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

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