-- generated by using spec/Declarations.yaml

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

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


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

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

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

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

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

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

random_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
random_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
random_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.random_out_tt

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

random_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
random_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
random_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.random_t

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

uniform_out_ttdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr Tensor)
uniform_out_ttdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
uniform_out_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.uniform_out_ttdd

uniform_out_ttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
uniform_out_ttd :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
uniform_out_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.uniform_out_ttd

uniform_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
uniform_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
uniform_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.uniform_out_tt

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

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

uniform_td
  :: ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
uniform_td :: ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
uniform_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.uniform_td

uniform_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
uniform_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
uniform_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.uniform_t

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

cauchy_out_ttdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr Tensor)
cauchy_out_ttdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
cauchy_out_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.cauchy_out_ttdd

cauchy_out_ttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
cauchy_out_ttd :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
cauchy_out_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.cauchy_out_ttd

cauchy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
cauchy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
cauchy_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.cauchy_out_tt

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

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

cauchy_td
  :: ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
cauchy_td :: ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
cauchy_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.cauchy_td

cauchy_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
cauchy_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
cauchy_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.cauchy_t

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

log_normal_out_ttdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr Tensor)
log_normal_out_ttdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
log_normal_out_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.log_normal_out_ttdd

log_normal_out_ttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
log_normal_out_ttd :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
log_normal_out_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.log_normal_out_ttd

log_normal_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
log_normal_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
log_normal_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.log_normal_out_tt

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

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

log_normal_td
  :: ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
log_normal_td :: ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
log_normal_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.log_normal_td

log_normal_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
log_normal_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
log_normal_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.log_normal_t

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

exponential_out_ttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
exponential_out_ttd :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
exponential_out_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.exponential_out_ttd

exponential_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
exponential_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
exponential_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.exponential_out_tt

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

exponential_td
  :: ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
exponential_td :: ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
exponential_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.exponential_td

exponential_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
exponential_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
exponential_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.exponential_t

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

geometric_out_ttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
geometric_out_ttd :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
geometric_out_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.geometric_out_ttd

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

geometric_td
  :: ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
geometric_td :: ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
geometric_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.geometric_td

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

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

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

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

trace_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
trace_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
trace_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.trace_out_tt

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

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

dist_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
dist_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
dist_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.dist_out_ttt

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

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

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

_histogramdd_bin_edges_out_ltl
  :: ForeignPtr TensorList
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (())
_histogramdd_bin_edges_out_ltl :: ForeignPtr TensorList
-> ForeignPtr Tensor -> ForeignPtr IntArray -> IO ()
_histogramdd_bin_edges_out_ltl = (Ptr TensorList -> Ptr Tensor -> Ptr IntArray -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr Tensor -> Ptr IntArray -> IO ()
Unmanaged._histogramdd_bin_edges_out_ltl

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

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

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

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

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

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

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

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

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

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

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

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

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

normal_out_ttdd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> CDouble
  -> IO (ForeignPtr Tensor)
normal_out_ttdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
normal_out_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.normal_out_ttdd

-- normal_out_ttd
--   :: ForeignPtr Tensor
--   -> ForeignPtr Tensor
--   -> CDouble
--   -> IO (ForeignPtr Tensor)
-- normal_out_ttd = _cast3 Unmanaged.normal_out_ttd

-- normal_out_tt
--   :: ForeignPtr Tensor
--   -> ForeignPtr Tensor
--   -> IO (ForeignPtr Tensor)
-- normal_out_tt = _cast2 Unmanaged.normal_out_tt

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

_amp_foreach_non_finite_check_and_unscale_ltt
  :: ForeignPtr TensorList
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(TensorList,Tensor)))
_amp_foreach_non_finite_check_and_unscale_ltt :: ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(TensorList, Tensor)))
_amp_foreach_non_finite_check_and_unscale_ltt = (Ptr TensorList
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr (StdTuple '(TensorList, Tensor))))
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(TensorList, Tensor)))
forall a ca x1 cx1 x2 cx2 y 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 TensorList
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(TensorList, Tensor)))
Unmanaged._amp_foreach_non_finite_check_and_unscale_ltt

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

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

_foreach_add_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_add_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_add_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_add_out_lls

_foreach_sub_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_sub_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_sub_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_sub_out_lls

_foreach_mul_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_mul_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_mul_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_mul_out_lls

_foreach_div_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_div_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_div_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_div_out_lls

_foreach_clamp_min_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_clamp_min_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_clamp_min_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_clamp_min_out_lls

_foreach_clamp_max_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_clamp_max_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_clamp_max_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_clamp_max_out_lls

_foreach_maximum_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_maximum_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_maximum_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_maximum_out_lls

_foreach_minimum_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_minimum_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_minimum_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_minimum_out_lls

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

_foreach_add_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_add_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_add_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_add_out_lll

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

_foreach_sub_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_sub_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_sub_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_sub_out_lll

_foreach_mul_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_mul_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_mul_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_mul_out_lll

_foreach_div_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_div_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_div_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_div_out_lll

_foreach_clamp_min_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_clamp_min_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_clamp_min_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_clamp_min_out_lll

_foreach_clamp_max_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_clamp_max_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_clamp_max_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_clamp_max_out_lll

_foreach_maximum_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_maximum_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_maximum_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_maximum_out_lll

_foreach_minimum_out_lll
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> IO (())
_foreach_minimum_out_lll :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr TensorList -> IO ()
_foreach_minimum_out_lll = (Ptr TensorList -> Ptr TensorList -> Ptr TensorList -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr TensorList -> IO ()
Unmanaged._foreach_minimum_out_lll

_foreach_add_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_add_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_add_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_add_out_llA

_foreach_sub_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_sub_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_sub_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_sub_out_llA

_foreach_div_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_div_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_div_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_div_out_llA

_foreach_mul_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_mul_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_mul_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_mul_out_llA

_foreach_clamp_min_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_clamp_min_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_clamp_min_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_clamp_min_out_llA

_foreach_clamp_max_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_clamp_max_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_clamp_max_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_clamp_max_out_llA

_foreach_maximum_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_maximum_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_maximum_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_maximum_out_llA

_foreach_minimum_out_llA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (())
_foreach_minimum_out_llA :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr (StdVector Scalar) -> IO ()
_foreach_minimum_out_llA = (Ptr TensorList
 -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr (StdVector Scalar) -> IO ()
Unmanaged._foreach_minimum_out_llA

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

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

_foreach_zero_l
  :: ForeignPtr TensorList
  -> IO (ForeignPtr TensorList)
_foreach_zero_l :: ForeignPtr TensorList -> IO (ForeignPtr TensorList)
_foreach_zero_l = (Ptr TensorList -> IO (Ptr TensorList))
-> ForeignPtr TensorList -> IO (ForeignPtr TensorList)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr TensorList -> IO (Ptr TensorList)
Unmanaged._foreach_zero_l

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_foreach_norm_out_lls
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr Scalar
  -> IO (())
_foreach_norm_out_lls :: ForeignPtr TensorList
-> ForeignPtr TensorList -> ForeignPtr Scalar -> IO ()
_foreach_norm_out_lls = (Ptr TensorList -> Ptr TensorList -> Ptr Scalar -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr Scalar
-> IO ()
forall a ca x1 cx1 x2 cx2 y 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 TensorList -> Ptr TensorList -> Ptr Scalar -> IO ()
Unmanaged._foreach_norm_out_lls

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

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

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

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

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

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

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

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

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

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

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

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

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

hardswish_backward_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardswish_backward_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardswish_backward_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.hardswish_backward_out_ttt

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

mkldnn_adaptive_avg_pool2d_backward_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
mkldnn_adaptive_avg_pool2d_backward_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
mkldnn_adaptive_avg_pool2d_backward_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.mkldnn_adaptive_avg_pool2d_backward_out_ttt

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

_adaptive_avg_pool2d_backward_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_adaptive_avg_pool2d_backward_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_adaptive_avg_pool2d_backward_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._adaptive_avg_pool2d_backward_out_ttt

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

_adaptive_avg_pool3d_backward_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_adaptive_avg_pool3d_backward_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_adaptive_avg_pool3d_backward_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._adaptive_avg_pool3d_backward_out_ttt

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

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

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

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

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

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

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

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

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

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

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

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

isinf_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
isinf_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
isinf_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.isinf_out_tt

linalg_matrix_exp_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
linalg_matrix_exp_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
linalg_matrix_exp_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.linalg_matrix_exp_out_tt

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

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

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

_test_warn_in_autograd_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_test_warn_in_autograd_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_test_warn_in_autograd_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._test_warn_in_autograd_out_tt

_test_autograd_multiple_dispatch_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_test_autograd_multiple_dispatch_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_test_autograd_multiple_dispatch_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._test_autograd_multiple_dispatch_out_tt

_test_autograd_multiple_dispatch_view_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_test_autograd_multiple_dispatch_view_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_test_autograd_multiple_dispatch_view_copy_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._test_autograd_multiple_dispatch_view_copy_out_tt

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

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

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

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

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

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

segment_reduce_out_tts
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> IO (ForeignPtr Tensor)
segment_reduce_out_tts :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> IO (ForeignPtr Tensor)
segment_reduce_out_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.segment_reduce_out_tts

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

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

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

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

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

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

_nested_tensor_from_tensor_list_out_tlsLD
  :: ForeignPtr Tensor
  -> ForeignPtr TensorList
  -> ScalarType
  -> Layout
  -> DeviceType
  -> IO (ForeignPtr Tensor)
_nested_tensor_from_tensor_list_out_tlsLD :: ForeignPtr Tensor
-> ForeignPtr TensorList
-> ScalarType
-> ScalarType
-> DeviceType
-> IO (ForeignPtr Tensor)
_nested_tensor_from_tensor_list_out_tlsLD = (Ptr Tensor
 -> Ptr TensorList
 -> ScalarType
 -> ScalarType
 -> DeviceType
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> ScalarType
-> ScalarType
-> DeviceType
-> 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 TensorList
-> ScalarType
-> ScalarType
-> DeviceType
-> IO (Ptr Tensor)
Unmanaged._nested_tensor_from_tensor_list_out_tlsLD

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

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

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

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

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

view_as_real_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
view_as_real_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
view_as_real_copy_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.view_as_real_copy_out_tt

view_as_complex_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
view_as_complex_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
view_as_complex_copy_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.view_as_complex_copy_out_tt

_conj_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_conj_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_conj_copy_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._conj_copy_out_tt

_neg_view_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_neg_view_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_neg_view_copy_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._neg_view_copy_out_tt

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

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

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

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

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

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

diagonal_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
diagonal_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
diagonal_copy_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.diagonal_copy_out_tt

expand_copy_out_ttlb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> CBool
  -> IO (ForeignPtr Tensor)
expand_copy_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
expand_copy_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.expand_copy_out_ttlb

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

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

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

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

detach_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
detach_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
detach_copy_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.detach_copy_out_tt

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

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

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

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

slice_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
slice_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
slice_copy_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.slice_copy_out_tt

squeeze_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
squeeze_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
squeeze_copy_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.squeeze_copy_out_tt

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

t_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
t_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
t_copy_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.t_copy_out_tt

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

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

_indices_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_indices_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_indices_copy_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._indices_copy_out_tt

_values_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_values_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_values_copy_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._values_copy_out_tt

indices_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
indices_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
indices_copy_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.indices_copy_out_tt

values_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
values_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
values_copy_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.values_copy_out_tt

crow_indices_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
crow_indices_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
crow_indices_copy_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.crow_indices_copy_out_tt

col_indices_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
col_indices_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
col_indices_copy_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.col_indices_copy_out_tt

ccol_indices_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
ccol_indices_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
ccol_indices_copy_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.ccol_indices_copy_out_tt

row_indices_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
row_indices_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
row_indices_copy_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.row_indices_copy_out_tt

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

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

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

alias_copy_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
alias_copy_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
alias_copy_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.alias_copy_out_tt

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

to_padded_tensor_out_ttd
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> IO (ForeignPtr Tensor)
to_padded_tensor_out_ttd :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CDouble -> IO (ForeignPtr Tensor)
to_padded_tensor_out_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.to_padded_tensor_out_ttd

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

_transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> CDouble
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt = (Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> CDouble
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> ForeignPtr 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 x8 cx8
       x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 x14 cx14 x15 cx15 x16
       cx16 x17 cx17 x18 cx18 x19 cx19 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> cx15
 -> cx16
 -> cx17
 -> cx18
 -> cx19
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> x15
-> x16
-> x17
-> x18
-> x19
-> IO y
_cast20 Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CDouble
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
Unmanaged._transformer_encoder_layer_fwd_out_ttllttttbbdttttttttt

_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> CDouble
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
_transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt = (Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> CDouble
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> CDouble
-> 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 x8 cx8
       x9 cx9 x10 cx10 x11 cx11 x12 cx12 x13 cx13 x14 cx14 x15 cx15 x16
       cx16 x17 cx17 x18 cx18 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> cx15
 -> cx16
 -> cx17
 -> cx18
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> x15
-> x16
-> x17
-> x18
-> IO y
_cast19 Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> CDouble
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr Tensor)
Unmanaged._transformer_encoder_layer_fwd_out_ttllttttbbdtttttttt

_native_multi_head_attention_out_tttttlltttttbbl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> CBool
  -> Int64
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttlltttttbbl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttlltttttbbl = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> CBool
 -> Int64
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> CBool
-> Int64
-> IO (ForeignPtr (StdTuple '(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 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> IO y
_cast15 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> CBool
-> Int64
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged._native_multi_head_attention_out_tttttlltttttbbl

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

_native_multi_head_attention_out_tttttlltttttb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttlltttttb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttlltttttb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CBool
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr (StdTuple '(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 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> IO y
_cast13 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> CBool
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged._native_multi_head_attention_out_tttttlltttttb

_native_multi_head_attention_out_tttttllttttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_native_multi_head_attention_out_tttttllttttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_native_multi_head_attention_out_tttttllttttt = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(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 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> IO y
_cast12 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Int64
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged._native_multi_head_attention_out_tttttllttttt

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

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

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

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

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

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

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

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

_foobar_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_foobar_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_foobar_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._foobar_out_tt

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

_fused_adam_out_llllllldddddbbt
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> ForeignPtr Tensor
  -> IO (())
_fused_adam_out_llllllldddddbbt :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> IO ()
_fused_adam_out_llllllldddddbbt = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CBool
 -> CBool
 -> Ptr Tensor
 -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> IO ()
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 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> IO y
_cast15 Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> IO ()
Unmanaged._fused_adam_out_llllllldddddbbt

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

_fused_adam_lllllldddddbbtt
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_fused_adam_lllllldddddbbtt :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_fused_adam_lllllldddddbbtt = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CBool
 -> CBool
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO
      (Ptr
         (StdTuple
            '(TensorList, TensorList, TensorList, TensorList, TensorList))))
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, 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 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> IO y
_cast15 Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> Ptr Tensor
-> IO
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
Unmanaged._fused_adam_lllllldddddbbtt

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

_fused_adam_lllllldddddbb
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> IO (ForeignPtr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_fused_adam_lllllldddddbb :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_fused_adam_lllllldddddbb = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CBool
 -> CBool
 -> IO
      (Ptr
         (StdTuple
            '(TensorList, TensorList, TensorList, TensorList, TensorList))))
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, 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 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> IO y
_cast13 Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
Unmanaged._fused_adam_lllllldddddbb

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

_fused_adamw_out_llllllldddddbbt
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> ForeignPtr Tensor
  -> IO (())
_fused_adamw_out_llllllldddddbbt :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> IO ()
_fused_adamw_out_llllllldddddbbt = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CBool
 -> CBool
 -> Ptr Tensor
 -> IO ())
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> IO ()
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 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> IO y
_cast15 Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> IO ()
Unmanaged._fused_adamw_out_llllllldddddbbt

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

_fused_adamw_lllllldddddbbtt
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_fused_adamw_lllllldddddbbtt :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_fused_adamw_lllllldddddbbtt = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CBool
 -> CBool
 -> Ptr Tensor
 -> Ptr Tensor
 -> IO
      (Ptr
         (StdTuple
            '(TensorList, TensorList, TensorList, TensorList, TensorList))))
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, 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 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 y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> cx13
 -> cx14
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> x13
-> x14
-> IO y
_cast15 Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> Ptr Tensor
-> Ptr Tensor
-> IO
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
Unmanaged._fused_adamw_lllllldddddbbtt

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

_fused_adamw_lllllldddddbb
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CDouble
  -> CBool
  -> CBool
  -> IO (ForeignPtr (StdTuple '(TensorList,TensorList,TensorList,TensorList,TensorList)))
_fused_adamw_lllllldddddbb :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
_fused_adamw_lllllldddddbb = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CDouble
 -> CBool
 -> CBool
 -> IO
      (Ptr
         (StdTuple
            '(TensorList, TensorList, TensorList, TensorList, TensorList))))
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (ForeignPtr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, 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 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7,
 Castable x8 cx8, Castable x9 cx9, Castable x10 cx10,
 Castable x11 cx11, Castable x12 cx12, Castable y cy) =>
(ca
 -> cx1
 -> cx2
 -> cx3
 -> cx4
 -> cx5
 -> cx6
 -> cx7
 -> cx8
 -> cx9
 -> cx10
 -> cx11
 -> cx12
 -> IO cy)
-> a
-> x1
-> x2
-> x3
-> x4
-> x5
-> x6
-> x7
-> x8
-> x9
-> x10
-> x11
-> x12
-> IO y
_cast13 Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> Ptr TensorList
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CBool
-> CBool
-> IO
     (Ptr
        (StdTuple
           '(TensorList, TensorList, TensorList, TensorList, TensorList)))
Unmanaged._fused_adamw_lllllldddddbb