-- generated by using spec/Declarations.yaml

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

module Torch.Internal.Managed.Native.Native3 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.Native.Native3 as Unmanaged


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

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

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

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

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

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

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

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

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

logspace_out_tssld
  :: ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> Int64
  -> CDouble
  -> IO (ForeignPtr Tensor)
logspace_out_tssld :: ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> Int64
-> CDouble
-> IO (ForeignPtr Tensor)
logspace_out_tssld = (Ptr Tensor
 -> Ptr Scalar -> Ptr Scalar -> Int64 -> CDouble -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> Int64
-> CDouble
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Scalar -> Ptr Scalar -> Int64 -> CDouble -> IO (Ptr Tensor)
Unmanaged.logspace_out_tssld

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

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

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

log_softmax_out_ttls
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> ScalarType
  -> IO (ForeignPtr Tensor)
log_softmax_out_ttls :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> MemoryFormat
-> IO (ForeignPtr Tensor)
log_softmax_out_ttls = (Ptr Tensor
 -> Ptr Tensor -> Int64 -> MemoryFormat -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Int64 -> MemoryFormat -> IO (Ptr Tensor)
Unmanaged.log_softmax_out_ttls

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

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

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

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

_log_softmax_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
_log_softmax_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CBool -> IO (ForeignPtr Tensor)
_log_softmax_out_ttlb = (Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor -> Ptr Tensor -> Int64 -> CBool -> IO (Ptr Tensor)
Unmanaged._log_softmax_out_ttlb

_log_softmax_backward_data_ttls
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> ScalarType
  -> IO (ForeignPtr Tensor)
_log_softmax_backward_data_ttls :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> MemoryFormat
-> IO (ForeignPtr Tensor)
_log_softmax_backward_data_ttls = (Ptr Tensor
 -> Ptr Tensor -> Int64 -> MemoryFormat -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Int64 -> MemoryFormat -> IO (Ptr Tensor)
Unmanaged._log_softmax_backward_data_ttls

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

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

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

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

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

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

logcumsumexp_out_ttn
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr Tensor)
logcumsumexp_out_ttn :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
logcumsumexp_out_ttn = (Ptr Tensor -> Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr Dimname -> IO (Ptr Tensor)
Unmanaged.logcumsumexp_out_ttn

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

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

logsumexp_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
logsumexp_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
logsumexp_out_ttlb = (Ptr Tensor
 -> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
Unmanaged.logsumexp_out_ttlb

logsumexp_out_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
logsumexp_out_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
logsumexp_out_ttl = (Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.logsumexp_out_ttl

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

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

logsumexp_out_ttNb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> CBool
  -> IO (ForeignPtr Tensor)
logsumexp_out_ttNb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor)
logsumexp_out_ttNb = (Ptr Tensor
 -> Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
Unmanaged.logsumexp_out_ttNb

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

margin_ranking_loss_tttdl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> Int64
  -> IO (ForeignPtr Tensor)
margin_ranking_loss_tttdl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
margin_ranking_loss_tttdl = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor)
Unmanaged.margin_ranking_loss_tttdl

margin_ranking_loss_tttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
margin_ranking_loss_tttd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
margin_ranking_loss_tttd = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> CDouble -> IO (Ptr Tensor)
Unmanaged.margin_ranking_loss_tttd

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

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

matmul_backward_ttta
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr (StdArray '(CBool,2))
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
matmul_backward_ttta :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr (StdArray '(CBool, 2))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
matmul_backward_ttta = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr (StdArray '(CBool, 2))
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr (StdArray '(CBool, 2))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 2))
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.matmul_backward_ttta

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

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

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

matrix_exp_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
matrix_exp_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
matrix_exp_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.matrix_exp_t

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

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

_aminmax_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_aminmax_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_aminmax_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged._aminmax_tlb

_aminmax_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_aminmax_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_aminmax_tl = (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._aminmax_tl

aminmax_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
aminmax_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
aminmax_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.aminmax_tlb

aminmax_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
aminmax_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
aminmax_tl = (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.aminmax_tl

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

aminmax_out_tttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
aminmax_out_tttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
aminmax_out_tttlb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.aminmax_out_tttlb

aminmax_out_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
aminmax_out_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
aminmax_out_tttl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.aminmax_out_tttl

aminmax_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
aminmax_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
aminmax_out_ttt = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.aminmax_out_ttt

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

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

max_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_tlb

max_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_tl = (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.max_tl

max_out_tttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_out_tttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_out_tttlb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_out_tttlb

max_out_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_out_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_out_tttl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_out_tttl

max_tnb
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_tnb :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_tnb = (Ptr Tensor
 -> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_tnb

max_tn
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_tn :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_tn = (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.max_tn

max_out_tttnb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_out_tttnb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_out_tttnb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_out_tttnb

max_out_tttn
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_out_tttn :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_out_tttn = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_out_tttn

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

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

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

amax_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
amax_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
amax_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.amax_t

amax_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
amax_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
amax_out_ttlb = (Ptr Tensor
 -> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
Unmanaged.amax_out_ttlb

amax_out_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
amax_out_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
amax_out_ttl = (Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.amax_out_ttl

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

max_pool1d_with_indices_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_pool1d_with_indices_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_pool1d_with_indices_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_pool1d_with_indices_tllllb

max_pool1d_with_indices_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_pool1d_with_indices_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_pool1d_with_indices_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_pool1d_with_indices_tllll

max_pool1d_with_indices_tlll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_pool1d_with_indices_tlll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_pool1d_with_indices_tlll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_pool1d_with_indices_tlll

max_pool1d_with_indices_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_pool1d_with_indices_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_pool1d_with_indices_tll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_pool1d_with_indices_tll

max_pool1d_with_indices_tl
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
max_pool1d_with_indices_tl :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
max_pool1d_with_indices_tl = (Ptr Tensor
 -> Ptr IntArray -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> 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 IntArray -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.max_pool1d_with_indices_tl

max_pool1d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
max_pool1d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
max_pool1d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.max_pool1d_tllllb

max_pool1d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool1d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool1d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_pool1d_tllll

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

max_pool1d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool1d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool1d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.max_pool1d_tll

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

max_pool2d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
max_pool2d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
max_pool2d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.max_pool2d_tllllb

max_pool2d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool2d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool2d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_pool2d_tllll

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

max_pool2d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool2d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool2d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.max_pool2d_tll

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

max_pool2d_backward_ttllllb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
max_pool2d_backward_ttllllb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
max_pool2d_backward_ttllllb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.max_pool2d_backward_ttllllb

max_pool2d_backward_ttllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool2d_backward_ttllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool2d_backward_ttllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_pool2d_backward_ttllll

max_pool2d_backward_ttlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool2d_backward_ttlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool2d_backward_ttlll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_pool2d_backward_ttlll

max_pool2d_backward_ttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool2d_backward_ttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool2d_backward_ttll = (Ptr Tensor
 -> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.max_pool2d_backward_ttll

max_pool2d_backward_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool2d_backward_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool2d_backward_ttl = (Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.max_pool2d_backward_ttl

mkldnn_max_pool2d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_tllllb

mkldnn_max_pool2d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_tllll

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

mkldnn_max_pool2d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_tll

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

mkldnn_max_pool2d_backward_tttllllb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttllllb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttllllb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_backward_tttllllb

mkldnn_max_pool2d_backward_tttllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_backward_tttllll

mkldnn_max_pool2d_backward_tttlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttlll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_backward_tttlll

mkldnn_max_pool2d_backward_tttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_backward_tttll

mkldnn_max_pool2d_backward_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool2d_backward_tttl = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool2d_backward_tttl

mkldnn_max_pool3d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_tllllb

mkldnn_max_pool3d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_tllll

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

mkldnn_max_pool3d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_tll

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

mkldnn_max_pool3d_backward_tttllllb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttllllb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttllllb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_backward_tttllllb

mkldnn_max_pool3d_backward_tttllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_backward_tttllll

mkldnn_max_pool3d_backward_tttlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttlll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_backward_tttlll

mkldnn_max_pool3d_backward_tttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_backward_tttll

mkldnn_max_pool3d_backward_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mkldnn_max_pool3d_backward_tttl = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.mkldnn_max_pool3d_backward_tttl

quantized_max_pool1d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
quantized_max_pool1d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
quantized_max_pool1d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.quantized_max_pool1d_tllllb

quantized_max_pool1d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
quantized_max_pool1d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
quantized_max_pool1d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.quantized_max_pool1d_tllll

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

quantized_max_pool1d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
quantized_max_pool1d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
quantized_max_pool1d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.quantized_max_pool1d_tll

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

quantized_max_pool2d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
quantized_max_pool2d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
quantized_max_pool2d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.quantized_max_pool2d_tllllb

quantized_max_pool2d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
quantized_max_pool2d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
quantized_max_pool2d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.quantized_max_pool2d_tllll

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

quantized_max_pool2d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
quantized_max_pool2d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
quantized_max_pool2d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.quantized_max_pool2d_tll

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

max_pool3d_tllllb
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
max_pool3d_tllllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
max_pool3d_tllllb = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> CBool
-> IO (Ptr Tensor)
Unmanaged.max_pool3d_tllllb

max_pool3d_tllll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool3d_tllll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool3d_tllll = (Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_pool3d_tllll

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

max_pool3d_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
max_pool3d_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_pool3d_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.max_pool3d_tll

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

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

mean_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
mean_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
mean_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.mean_t

mean_tlbs
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
mean_tlbs :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
mean_tlbs = (Ptr Tensor
 -> Ptr IntArray -> CBool -> MemoryFormat -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr IntArray -> CBool -> MemoryFormat -> IO (Ptr Tensor)
Unmanaged.mean_tlbs

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

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

mean_out_ttlbs
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
mean_out_ttlbs :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
mean_out_ttlbs = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> CBool
 -> MemoryFormat
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> MemoryFormat
-> IO (Ptr Tensor)
Unmanaged.mean_out_ttlbs

mean_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
mean_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
mean_out_ttlb = (Ptr Tensor
 -> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
Unmanaged.mean_out_ttlb

mean_out_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
mean_out_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
mean_out_ttl = (Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.mean_out_ttl

mean_tNbs
  :: ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
mean_tNbs :: ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
mean_tNbs = (Ptr Tensor
 -> Ptr DimnameList -> CBool -> MemoryFormat -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr DimnameList -> CBool -> MemoryFormat -> IO (Ptr Tensor)
Unmanaged.mean_tNbs

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

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

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

mean_out_ttNb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr DimnameList
  -> CBool
  -> IO (ForeignPtr Tensor)
mean_out_ttNb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor)
mean_out_ttNb = (Ptr Tensor
 -> Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr DimnameList
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr DimnameList -> CBool -> IO (Ptr Tensor)
Unmanaged.mean_out_ttNb

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

nanmean_tlbs
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
nanmean_tlbs :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
nanmean_tlbs = (Ptr Tensor
 -> Ptr IntArray -> CBool -> MemoryFormat -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr IntArray -> CBool -> MemoryFormat -> IO (Ptr Tensor)
Unmanaged.nanmean_tlbs

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

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

nanmean_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nanmean_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nanmean_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.nanmean_t

nanmean_out_ttlbs
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> ScalarType
  -> IO (ForeignPtr Tensor)
nanmean_out_ttlbs :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
nanmean_out_ttlbs = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> CBool
 -> MemoryFormat
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> MemoryFormat
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> CBool
-> MemoryFormat
-> IO (Ptr Tensor)
Unmanaged.nanmean_out_ttlbs

nanmean_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
nanmean_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
nanmean_out_ttlb = (Ptr Tensor
 -> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
Unmanaged.nanmean_out_ttlb

nanmean_out_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
nanmean_out_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
nanmean_out_ttl = (Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.nanmean_out_ttl

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

median_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
median_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
median_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.median_t

median_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.median_tlb

median_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_tl = (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.median_tl

median_out_tttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_out_tttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_out_tttlb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.median_out_tttlb

median_out_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_out_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_out_tttl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.median_out_tttl

median_tnb
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_tnb :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_tnb = (Ptr Tensor
 -> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.median_tnb

median_tn
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_tn :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_tn = (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.median_tn

median_out_tttnb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_out_tttnb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_out_tttnb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.median_out_tttnb

median_out_tttn
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
median_out_tttn :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
median_out_tttn = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.median_out_tttn

nanmedian_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nanmedian_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nanmedian_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.nanmedian_t

nanmedian_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.nanmedian_tlb

nanmedian_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_tl = (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.nanmedian_tl

nanmedian_out_tttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_out_tttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_out_tttlb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.nanmedian_out_tttlb

nanmedian_out_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_out_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_out_tttl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.nanmedian_out_tttl

nanmedian_tnb
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_tnb :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_tnb = (Ptr Tensor
 -> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.nanmedian_tnb

nanmedian_tn
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_tn :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_tn = (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.nanmedian_tn

nanmedian_out_tttnb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_out_tttnb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_out_tttnb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.nanmedian_out_tttnb

nanmedian_out_tttn
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
nanmedian_out_tttn :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
nanmedian_out_tttn = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.nanmedian_out_tttn

min_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.min_tlb

min_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_tl = (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.min_tl

min_out_tttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_out_tttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_out_tttlb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.min_out_tttlb

min_out_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_out_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_out_tttl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.min_out_tttl

min_tnb
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_tnb :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_tnb = (Ptr Tensor
 -> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.min_tnb

min_tn
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_tn :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_tn = (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.min_tn

min_out_tttnb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_out_tttnb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_out_tttnb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.min_out_tttnb

min_out_tttn
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
min_out_tttn :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
min_out_tttn = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.min_out_tttn

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

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

amin_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
amin_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
amin_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.amin_t

amin_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
amin_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
amin_out_ttlb = (Ptr Tensor
 -> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr IntArray -> CBool -> IO (Ptr Tensor)
Unmanaged.amin_out_ttlb

amin_out_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
amin_out_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
amin_out_ttl = (Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.amin_out_ttl

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

_mps_convolution_tttllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
_mps_convolution_tttllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
_mps_convolution_tttllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
Unmanaged._mps_convolution_tttllll

mps_convolution_backward_tttlllla
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> ForeignPtr (StdArray '(CBool,3))
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
mps_convolution_backward_tttlllla :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr (StdArray '(CBool, 3))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
mps_convolution_backward_tttlllla = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> Ptr (StdArray '(CBool, 3))
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> ForeignPtr (StdArray '(CBool, 3))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged.mps_convolution_backward_tttlllla

mkldnn_convolution_tttllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
mkldnn_convolution_tttllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
mkldnn_convolution_tttllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
Unmanaged.mkldnn_convolution_tttllll

mkldnn_rnn_layer_tttttttbllllbbbb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> ForeignPtr IntArray
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
mkldnn_rnn_layer_tttttttbllllbbbb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr IntArray
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
mkldnn_rnn_layer_tttttttbllllbbbb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> Ptr IntArray
 -> Int64
 -> Int64
 -> Int64
 -> CBool
 -> CBool
 -> CBool
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> ForeignPtr IntArray
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 x14 cx14 x15 cx15 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
 Castable x14 cx14, Castable x15 cx15, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> cx15
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> x15
-> IO y
_cast16 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Ptr IntArray
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
Unmanaged.mkldnn_rnn_layer_tttttttbllllbbbb

mkldnn_rnn_layer_backward_tttttttttttttblllbbblbt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> CBool
  -> ForeignPtr IntArray
  -> CBool
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor,Tensor,Tensor)))
mkldnn_rnn_layer_backward_tttttttttttttblllbbblbt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr Tensor
-> IO
     (ForeignPtr
        (StdTuple
           '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
mkldnn_rnn_layer_backward_tttttttttttttblllbbblbt = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> Int64
 -> Int64
 -> Int64
 -> CBool
 -> CBool
 -> CBool
 -> Ptr IntArray
 -> CBool
 -> Ptr Tensor
 -> IO
      (Ptr
         (StdTuple
            '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr Tensor
-> IO
     (ForeignPtr
        (StdTuple
           '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 x14 cx14 x15 cx15 x16
       cx16 x17 cx17 x18 cx18 x19 cx19 x20 cx20 x21 cx21 x22 cx22 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
 Castable x14 cx14, Castable x15 cx15, Castable x16 cx16,
 Castable x17 cx17, Castable x18 cx18, Castable x19 cx19,
 Castable x20 cx20, Castable x21 cx21, Castable x22 cx22,
 Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> cx15
 -> cx16
 -> cx17
 -> cx18
 -> cx19
 -> cx20
 -> cx21
 -> cx22
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> x15
-> x16
-> x17
-> x18
-> x19
-> x20
-> x21
-> x22
-> IO y
_cast23 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> CBool
-> Ptr IntArray
-> CBool
-> Ptr Tensor
-> IO
     (Ptr
        (StdTuple
           '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
Unmanaged.mkldnn_rnn_layer_backward_tttttttttttttblllbbblbt

miopen_batch_norm_tttttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
miopen_batch_norm_tttttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
miopen_batch_norm_tttttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged.miopen_batch_norm_tttttbdd

miopen_batch_norm_backward_tttttttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
miopen_batch_norm_backward_tttttttd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
miopen_batch_norm_backward_tttttttd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged.miopen_batch_norm_backward_tttttttd

miopen_convolution_tttllllbb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
miopen_convolution_tttllllbb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
miopen_convolution_tttllllbb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> CBool
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable y cy) =>
(ca
 -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
_cast9 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
Unmanaged.miopen_convolution_tttllllbb

miopen_convolution_transpose_tttlllllbb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
miopen_convolution_transpose_tttlllllbb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
miopen_convolution_transpose_tttlllllbb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> CBool
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
_cast10 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
Unmanaged.miopen_convolution_transpose_tttlllllbb

miopen_depthwise_convolution_tttllllbb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
miopen_depthwise_convolution_tttllllbb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
miopen_depthwise_convolution_tttllllbb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> CBool
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable y cy) =>
(ca
 -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
_cast9 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
Unmanaged.miopen_depthwise_convolution_tttllllbb

miopen_convolution_relu_tttllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
miopen_convolution_relu_tttllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
miopen_convolution_relu_tttllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
Unmanaged.miopen_convolution_relu_tttllll

miopen_convolution_add_relu_tttstllll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> Int64
  -> IO (ForeignPtr Tensor)
miopen_convolution_add_relu_tttstllll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
miopen_convolution_add_relu_tttstllll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> Ptr IntArray
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable y cy) =>
(ca
 -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
_cast9 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Scalar
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> Ptr IntArray
-> Int64
-> IO (Ptr Tensor)
Unmanaged.miopen_convolution_add_relu_tttstllll

miopen_rnn_tllttlllbdbblt
  :: ForeignPtr Tensor
  -> ForeignPtr TensorList
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CDouble
  -> CBool
  -> CBool
  -> ForeignPtr IntArray
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)))
miopen_rnn_tllttlllbdbblt :: ForeignPtr Tensor
-> ForeignPtr TensorList
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO
     (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
miopen_rnn_tllttlllbdbblt = (Ptr Tensor
 -> Ptr TensorList
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Int64
 -> CBool
 -> CDouble
 -> CBool
 -> CBool
 -> Ptr IntArray
 -> Ptr Tensor
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> IO
     (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
 Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> IO y
_cast14 Ptr Tensor
-> Ptr TensorList
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> Ptr IntArray
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor)))
Unmanaged.miopen_rnn_tllttlllbdbblt

miopen_rnn_backward_tlltttttttlllbdbbltta
  :: ForeignPtr Tensor
  -> ForeignPtr TensorList
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CDouble
  -> CBool
  -> CBool
  -> ForeignPtr IntArray
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr (StdArray '(CBool,4))
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList)))
miopen_rnn_backward_tlltttttttlllbdbbltta :: ForeignPtr Tensor
-> ForeignPtr TensorList
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr (StdArray '(CBool, 4))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList)))
miopen_rnn_backward_tlltttttttlllbdbbltta = (Ptr Tensor
 -> Ptr TensorList
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Int64
 -> CBool
 -> CDouble
 -> CBool
 -> CBool
 -> Ptr IntArray
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr (StdArray '(CBool, 4))
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, TensorList))))
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> ForeignPtr IntArray
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr (StdArray '(CBool, 4))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 x14 cx14 x15 cx15 x16
       cx16 x17 cx17 x18 cx18 x19 cx19 x20 cx20 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable x13 cx13,
 Castable x14 cx14, Castable x15 cx15, Castable x16 cx16,
 Castable x17 cx17, Castable x18 cx18, Castable x19 cx19,
 Castable x20 cx20, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> cx15
 -> cx16
 -> cx17
 -> cx18
 -> cx19
 -> cx20
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> x15
-> x16
-> x17
-> x18
-> x19
-> x20
-> IO y
_cast21 Ptr Tensor
-> Ptr TensorList
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Int64
-> CBool
-> CDouble
-> CBool
-> CBool
-> Ptr IntArray
-> Ptr Tensor
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 4))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, TensorList)))
Unmanaged.miopen_rnn_backward_tlltttttttlllbdbbltta

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

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

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

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

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

mode_tlb
  :: ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_tlb :: ForeignPtr Tensor
-> Int64 -> CBool -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_tlb = (Ptr Tensor
 -> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Int64 -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_tlb

mode_tl
  :: ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_tl :: ForeignPtr Tensor
-> Int64 -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_tl = (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.mode_tl

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

mode_out_tttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_out_tttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_out_tttlb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_out_tttlb

mode_out_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_out_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_out_tttl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_out_tttl

mode_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_out_ttt = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_out_ttt

mode_tnb
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_tnb :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_tnb = (Ptr Tensor
 -> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor
-> Ptr Dimname -> CBool -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_tnb

mode_tn
  :: ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_tn :: ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_tn = (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.mode_tn

mode_out_tttnb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_out_tttnb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_out_tttnb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_out_tttnb

mode_out_tttn
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Dimname
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
mode_out_tttn :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
mode_out_tttn = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Dimname
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Dimname
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Dimname
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.mode_out_tttn

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

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

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

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

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

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

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

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

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

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

narrow_copy_tlll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
narrow_copy_tlll :: ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
narrow_copy_tlll = (Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.narrow_copy_tlll

narrow_copy_out_ttlll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
narrow_copy_out_ttlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
narrow_copy_out_ttlll = (Ptr Tensor
 -> Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.narrow_copy_out_ttlll

narrow_tlll
  :: ForeignPtr Tensor
  -> Int64
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
narrow_tlll :: ForeignPtr Tensor
-> Int64 -> Int64 -> Int64 -> IO (ForeignPtr Tensor)
narrow_tlll = (Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> Int64
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor -> Int64 -> Int64 -> Int64 -> IO (Ptr Tensor)
Unmanaged.narrow_tlll

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

native_batch_norm_tttttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
native_batch_norm_tttttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
native_batch_norm_tttttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged.native_batch_norm_tttttbdd

native_batch_norm_out_ttttttttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
native_batch_norm_out_ttttttttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
native_batch_norm_out_ttttttttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 x10 cx10 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> IO y
_cast11 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged.native_batch_norm_out_ttttttttbdd

_native_batch_norm_legit_tttttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
_native_batch_norm_legit_tttttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
_native_batch_norm_legit_tttttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged._native_batch_norm_legit_tttttbdd

_native_batch_norm_legit_out_ttttttttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
_native_batch_norm_legit_out_ttttttttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
_native_batch_norm_legit_out_ttttttttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 x10 cx10 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> IO y
_cast11 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged._native_batch_norm_legit_out_ttttttttbdd

_native_batch_norm_legit_tttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
_native_batch_norm_legit_tttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
_native_batch_norm_legit_tttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged._native_batch_norm_legit_tttbdd

_native_batch_norm_legit_out_ttttttbdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
_native_batch_norm_legit_out_ttttttbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
_native_batch_norm_legit_out_ttttttbdd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable y cy) =>
(ca
 -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
_cast9 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged._native_batch_norm_legit_out_ttttttbdd

batch_norm_stats_td
  :: ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
batch_norm_stats_td :: ForeignPtr Tensor
-> CDouble -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
batch_norm_stats_td = (Ptr Tensor -> CDouble -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> CDouble
-> 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 -> CDouble -> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.batch_norm_stats_td

batch_norm_elemt_tttttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
batch_norm_elemt_tttttd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
batch_norm_elemt_tttttd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
Unmanaged.batch_norm_elemt_tttttd

batch_norm_elemt_out_ttttttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
batch_norm_elemt_out_ttttttd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
batch_norm_elemt_out_ttttttd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
_cast7 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr Tensor)
Unmanaged.batch_norm_elemt_out_ttttttd

batch_norm_gather_stats_tttttddl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> CDouble
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
batch_norm_gather_stats_tttttddl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
batch_norm_gather_stats_tttttddl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> CDouble
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.batch_norm_gather_stats_tttttddl

batch_norm_gather_stats_with_counts_tttttddt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> CDouble
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
batch_norm_gather_stats_with_counts_tttttddt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
batch_norm_gather_stats_with_counts_tttttddt = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> CDouble
 -> Ptr Tensor
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> CDouble
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.batch_norm_gather_stats_with_counts_tttttddt

native_batch_norm_backward_tttttttbda
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CDouble
  -> ForeignPtr (StdArray '(CBool,3))
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor)))
native_batch_norm_backward_tttttttbda :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> ForeignPtr (StdArray '(CBool, 3))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
native_batch_norm_backward_tttttttbda = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CDouble
 -> Ptr (StdArray '(CBool, 3))
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CDouble
-> ForeignPtr (StdArray '(CBool, 3))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
_cast10 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CDouble
-> Ptr (StdArray '(CBool, 3))
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor)))
Unmanaged.native_batch_norm_backward_tttttttbda

batch_norm_backward_reduce_tttttbbb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor)))
batch_norm_backward_reduce_tttttbbb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
batch_norm_backward_reduce_tttttbbb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor)))
Unmanaged.batch_norm_backward_reduce_tttttbbb

batch_norm_backward_elemt_tttttttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
batch_norm_backward_elemt_tttttttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
batch_norm_backward_elemt_tttttttt = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
_cast8 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
Unmanaged.batch_norm_backward_elemt_tttttttt

batch_norm_update_stats_tttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
batch_norm_update_stats_tttd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
batch_norm_update_stats_tttd = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged.batch_norm_update_stats_tttd

is_vulkan_available
  :: IO (CBool)
is_vulkan_available :: IO CBool
is_vulkan_available = IO CBool -> IO CBool
forall a ca. Castable a ca => IO ca -> IO a
_cast0 IO CBool
Unmanaged.is_vulkan_available

_nnpack_available
  :: IO (CBool)
_nnpack_available :: IO CBool
_nnpack_available = IO CBool -> IO CBool
forall a ca. Castable a ca => IO ca -> IO a
_cast0 IO CBool
Unmanaged._nnpack_available

_nnpack_spatial_convolution_tttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
_nnpack_spatial_convolution_tttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
_nnpack_spatial_convolution_tttll = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr IntArray
 -> Ptr IntArray
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged._nnpack_spatial_convolution_tttll

_nnpack_spatial_convolution_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
_nnpack_spatial_convolution_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
_nnpack_spatial_convolution_tttl = (Ptr Tensor
 -> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> Ptr Tensor -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged._nnpack_spatial_convolution_tttl

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

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

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

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

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

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

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

ones_like_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
ones_like_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ones_like_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.ones_like_t

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

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

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

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

cdist_ttdl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> Int64
  -> IO (ForeignPtr Tensor)
cdist_ttdl :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor)
cdist_ttdl = (Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor)
Unmanaged.cdist_ttdl

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

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

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

_cdist_forward_ttdl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> Int64
  -> IO (ForeignPtr Tensor)
_cdist_forward_ttdl :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> Int64 -> IO (ForeignPtr Tensor)
_cdist_forward_ttdl = (Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor -> Ptr Tensor -> CDouble -> Int64 -> IO (Ptr Tensor)
Unmanaged._cdist_forward_ttdl

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

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

pdist_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
pdist_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
pdist_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.pdist_t

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

_pdist_forward_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_pdist_forward_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_pdist_forward_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._pdist_forward_t

_pdist_backward_ttdt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_pdist_backward_ttdt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
_pdist_backward_ttdt = (Ptr Tensor
 -> Ptr Tensor -> CDouble -> Ptr Tensor -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor
-> Ptr Tensor -> CDouble -> Ptr Tensor -> IO (Ptr Tensor)
Unmanaged._pdist_backward_ttdt

cosine_similarity_ttld
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> CDouble
  -> IO (ForeignPtr Tensor)
cosine_similarity_ttld :: ForeignPtr Tensor
-> ForeignPtr Tensor -> Int64 -> CDouble -> IO (ForeignPtr Tensor)
cosine_similarity_ttld = (Ptr Tensor -> Ptr Tensor -> Int64 -> CDouble -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> CDouble
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
_cast4 Ptr Tensor -> Ptr Tensor -> Int64 -> CDouble -> IO (Ptr Tensor)
Unmanaged.cosine_similarity_ttld

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

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

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

movedim_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
movedim_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
movedim_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.movedim_tll

moveaxis_tll
  :: ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
moveaxis_tll :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
moveaxis_tll = (Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) =>
(ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
_cast3 Ptr Tensor -> Ptr IntArray -> Ptr IntArray -> IO (Ptr Tensor)
Unmanaged.moveaxis_tll

adjoint_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
adjoint_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
adjoint_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.adjoint_t

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

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

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

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

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

_pin_memory_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_pin_memory_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_pin_memory_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._pin_memory_t

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

pinverse_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
pinverse_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
pinverse_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.pinverse_t

poisson_nll_loss_ttbbdl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> CDouble
  -> Int64
  -> IO (ForeignPtr Tensor)
poisson_nll_loss_ttbbdl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
poisson_nll_loss_ttbbdl = (Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> CDouble
 -> Int64
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> Int64
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
_cast6 Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CDouble
-> Int64
-> IO (Ptr Tensor)
Unmanaged.poisson_nll_loss_ttbbdl

rad2deg_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rad2deg_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
rad2deg_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.rad2deg_t

rad2deg__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rad2deg__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
rad2deg__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.rad2deg__t

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

deg2rad_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
deg2rad_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
deg2rad_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.deg2rad_t

deg2rad__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
deg2rad__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
deg2rad__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.deg2rad__t

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

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

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

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