-- generated by using spec/Declarations.yaml

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

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


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

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

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

rsub_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rsub_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
rsub_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.rsub_tt

heaviside_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
heaviside_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
heaviside_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.heaviside_out_ttt

heaviside_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
heaviside_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
heaviside_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.heaviside_tt

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

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

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

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

_sparse_addmm_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_sparse_addmm_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_sparse_addmm_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._sparse_addmm_ttt

sparse_sampled_addmm_out_ttttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
sparse_sampled_addmm_out_ttttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
sparse_sampled_addmm_out_ttttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 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 Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.sparse_sampled_addmm_out_ttttss

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

sparse_sampled_addmm_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
sparse_sampled_addmm_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
sparse_sampled_addmm_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.sparse_sampled_addmm_out_tttt

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

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

sparse_sampled_addmm_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
sparse_sampled_addmm_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
sparse_sampled_addmm_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.sparse_sampled_addmm_ttt

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

_sparse_mm_reduce_impl_backward_tttsta
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> ForeignPtr Tensor
  -> ForeignPtr (StdArray '(CBool,2))
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_sparse_mm_reduce_impl_backward_tttsta :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> ForeignPtr (StdArray '(CBool, 2))
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_sparse_mm_reduce_impl_backward_tttsta = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> Ptr Tensor
 -> Ptr (StdArray '(CBool, 2))
 -> IO (Ptr (StdTuple '(Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> ForeignPtr Tensor
-> ForeignPtr (StdArray '(CBool, 2))
-> 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
-> Ptr StdString
-> Ptr Tensor
-> Ptr (StdArray '(CBool, 2))
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged._sparse_mm_reduce_impl_backward_tttsta

addmm_out_ttttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
addmm_out_ttttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
addmm_out_ttttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 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 Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.addmm_out_ttttss

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

addmm_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
addmm_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
addmm_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.addmm_out_tttt

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

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

addmm_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
addmm_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
addmm_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.addmm_ttt

_addmm_activation_out_ttttssb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> CBool
  -> IO (ForeignPtr Tensor)
_addmm_activation_out_ttttssb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> CBool
-> IO (ForeignPtr Tensor)
_addmm_activation_out_ttttssb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 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 Scalar
-> Ptr Scalar
-> CBool
-> IO (Ptr Tensor)
Unmanaged._addmm_activation_out_ttttssb

_addmm_activation_out_ttttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
_addmm_activation_out_ttttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
_addmm_activation_out_ttttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 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 Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged._addmm_activation_out_ttttss

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

_addmm_activation_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_addmm_activation_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
_addmm_activation_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._addmm_activation_out_tttt

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

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

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

_addmm_activation_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_addmm_activation_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_addmm_activation_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._addmm_activation_ttt

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

sparse_coo_tensor_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
sparse_coo_tensor_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
sparse_coo_tensor_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_coo_tensor_ttl

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

_sparse_coo_tensor_unsafe_ttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr IntArray
  -> IO (ForeignPtr Tensor)
_sparse_coo_tensor_unsafe_ttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
_sparse_coo_tensor_unsafe_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_coo_tensor_unsafe_ttl

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

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

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

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

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

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

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

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

_to_cpu_l
  :: ForeignPtr TensorList
  -> IO (ForeignPtr TensorList)
_to_cpu_l :: ForeignPtr TensorList -> IO (ForeignPtr TensorList)
_to_cpu_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._to_cpu_l

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

_coalesce_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_coalesce_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_coalesce_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._coalesce_t

hspmm_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hspmm_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hspmm_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.hspmm_out_ttt

hspmm_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hspmm_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hspmm_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.hspmm_tt

copy_sparse_to_sparse__ttb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
copy_sparse_to_sparse__ttb :: ForeignPtr Tensor
-> ForeignPtr Tensor -> CBool -> IO (ForeignPtr Tensor)
copy_sparse_to_sparse__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.copy_sparse_to_sparse__ttb

copy_sparse_to_sparse__tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
copy_sparse_to_sparse__tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
copy_sparse_to_sparse__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.copy_sparse_to_sparse__tt

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

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

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

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

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

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

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

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

mkldnn_reorder_conv2d_weight_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
mkldnn_reorder_conv2d_weight_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
mkldnn_reorder_conv2d_weight_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.mkldnn_reorder_conv2d_weight_t

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

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

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

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

mkldnn_reorder_conv3d_weight_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
mkldnn_reorder_conv3d_weight_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
mkldnn_reorder_conv3d_weight_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.mkldnn_reorder_conv3d_weight_t

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

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

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

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

quantize_per_tensor_ltts
  :: ForeignPtr TensorList
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ScalarType
  -> IO (ForeignPtr TensorList)
quantize_per_tensor_ltts :: ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ScalarType
-> IO (ForeignPtr TensorList)
quantize_per_tensor_ltts = (Ptr TensorList
 -> Ptr Tensor -> Ptr Tensor -> ScalarType -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ScalarType
-> IO (ForeignPtr TensorList)
forall a ca x1 cx1 x2 cx2 x3 cx3 y cy.
(Castable a ca, Castable 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 Tensor -> ScalarType -> IO (Ptr TensorList)
Unmanaged.quantize_per_tensor_ltts

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

dequantize_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
dequantize_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
dequantize_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.dequantize_t

dequantize_l
  :: ForeignPtr TensorList
  -> IO (ForeignPtr TensorList)
dequantize_l :: ForeignPtr TensorList -> IO (ForeignPtr TensorList)
dequantize_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.dequantize_l

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

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

q_per_channel_scales_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
q_per_channel_scales_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
q_per_channel_scales_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.q_per_channel_scales_t

q_per_channel_zero_points_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
q_per_channel_zero_points_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
q_per_channel_zero_points_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.q_per_channel_zero_points_t

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

int_repr_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
int_repr_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
int_repr_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.int_repr_t

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

_make_per_channel_quantized_tensor_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
_make_per_channel_quantized_tensor_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
_make_per_channel_quantized_tensor_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_per_channel_quantized_tensor_tttl

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

fused_moving_avg_obs_fake_quant_tttttttdlllbb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> CBool
  -> IO (ForeignPtr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllbb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllbb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> Int64
 -> Int64
 -> Int64
 -> CBool
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 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
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> CBool
-> IO (Ptr Tensor)
Unmanaged.fused_moving_avg_obs_fake_quant_tttttttdlllbb

fused_moving_avg_obs_fake_quant_tttttttdlllb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CDouble
  -> Int64
  -> Int64
  -> Int64
  -> CBool
  -> IO (ForeignPtr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
fused_moving_avg_obs_fake_quant_tttttttdlllb = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> CDouble
 -> Int64
 -> Int64
 -> Int64
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       x9 cx9 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
-> Ptr Tensor
-> Ptr Tensor
-> CDouble
-> Int64
-> Int64
-> Int64
-> CBool
-> IO (Ptr Tensor)
Unmanaged.fused_moving_avg_obs_fake_quant_tttttttdlllb

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

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

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

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

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

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

_saturate_weight_to_fp16_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_saturate_weight_to_fp16_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_saturate_weight_to_fp16_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._saturate_weight_to_fp16_t

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

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

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

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

_to_copy_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_to_copy_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_to_copy_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._to_copy_t

meshgrid_l
  :: ForeignPtr TensorList
  -> IO (ForeignPtr TensorList)
meshgrid_l :: ForeignPtr TensorList -> IO (ForeignPtr TensorList)
meshgrid_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.meshgrid_l

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

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

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

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

combinations_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
combinations_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
combinations_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.combinations_t

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

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

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

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

can_cast_ss
  :: ScalarType
  -> ScalarType
  -> IO (CBool)
can_cast_ss :: ScalarType -> ScalarType -> IO CBool
can_cast_ss = (ScalarType -> ScalarType -> IO CBool)
-> ScalarType -> ScalarType -> IO CBool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
_cast2 ScalarType -> ScalarType -> IO CBool
Unmanaged.can_cast_ss

promote_types_ss
  :: ScalarType
  -> ScalarType
  -> IO (ScalarType)
promote_types_ss :: ScalarType -> ScalarType -> IO ScalarType
promote_types_ss = (ScalarType -> ScalarType -> IO ScalarType)
-> ScalarType -> ScalarType -> IO ScalarType
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
_cast2 ScalarType -> ScalarType -> IO ScalarType
Unmanaged.promote_types_ss

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

_lstm_mps_tllbldbbb
  :: ForeignPtr Tensor
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> CBool
  -> Int64
  -> CDouble
  -> CBool
  -> CBool
  -> CBool
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor,Tensor)))
_lstm_mps_tllbldbbb :: ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO
     (ForeignPtr
        (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
_lstm_mps_tllbldbbb = (Ptr Tensor
 -> Ptr TensorList
 -> Ptr TensorList
 -> CBool
 -> Int64
 -> CDouble
 -> CBool
 -> CBool
 -> CBool
 -> IO
      (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor))))
-> ForeignPtr Tensor
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO
     (ForeignPtr
        (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 x6 cx6 x7 cx7 x8 cx8
       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 TensorList
-> Ptr TensorList
-> CBool
-> Int64
-> CDouble
-> CBool
-> CBool
-> CBool
-> IO
     (Ptr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor, Tensor)))
Unmanaged._lstm_mps_tllbldbbb

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

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

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

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

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

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

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

_thnn_fused_gru_cell_ttttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
_thnn_fused_gru_cell_ttttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
_thnn_fused_gru_cell_ttttt = (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
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
 Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> IO (Ptr (StdTuple '(Tensor, Tensor)))
Unmanaged._thnn_fused_gru_cell_ttttt

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

gru_cell_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
gru_cell_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
gru_cell_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.gru_cell_tttt

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

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

rnn_tanh_cell_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rnn_tanh_cell_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
rnn_tanh_cell_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.rnn_tanh_cell_tttt

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

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

rnn_relu_cell_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rnn_relu_cell_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
rnn_relu_cell_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.rnn_relu_cell_tttt

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

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

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

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

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

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

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

lift_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
lift_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
lift_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.lift_t

lift_fresh_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
lift_fresh_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
lift_fresh_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.lift_fresh_t

lift_fresh_copy_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
lift_fresh_copy_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
lift_fresh_copy_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.lift_fresh_copy_t

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

masked_fill_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
masked_fill_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
masked_fill_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.masked_fill_ttt

masked_scatter_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
masked_scatter_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
masked_scatter_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.masked_scatter_ttt

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

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

_masked_softmax_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_masked_softmax_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_masked_softmax_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._masked_softmax_tt

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

_masked_softmax_backward_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_masked_softmax_backward_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_masked_softmax_backward_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._masked_softmax_backward_ttt

put_tttb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> CBool
  -> IO (ForeignPtr Tensor)
put_tttb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> CBool
-> IO (ForeignPtr Tensor)
put_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.put_tttb

put_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
put_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
put_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.put_ttt

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

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

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

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

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

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

index_reduce_out_ttlttsb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> CBool
  -> IO (ForeignPtr Tensor)
index_reduce_out_ttlttsb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
index_reduce_out_ttlttsb = (Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 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
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (Ptr Tensor)
Unmanaged.index_reduce_out_ttlttsb

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

scatter_reduce_out_ttlttsb
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr StdString
  -> CBool
  -> IO (ForeignPtr Tensor)
scatter_reduce_out_ttlttsb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
scatter_reduce_out_ttlttsb = (Ptr Tensor
 -> Ptr Tensor
 -> Int64
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr StdString
 -> CBool
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr StdString
-> CBool
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 x5 cx5 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
-> Int64
-> Ptr Tensor
-> Ptr Tensor
-> Ptr StdString
-> CBool
-> IO (Ptr Tensor)
Unmanaged.scatter_reduce_out_ttlttsb

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

bitwise_and_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_and_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_and_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.bitwise_and_out_ttt

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

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

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

bitwise_and_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_and_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_and_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.bitwise_and_tt

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

__and___tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
__and___tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
__and___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.__and___tt

bitwise_or_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_or_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_or_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.bitwise_or_out_ttt

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

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

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

bitwise_or_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_or_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_or_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.bitwise_or_tt

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

__or___tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
__or___tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
__or___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.__or___tt

bitwise_xor_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_xor_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_xor_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.bitwise_xor_out_ttt

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

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

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

bitwise_xor_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_xor_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_xor_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.bitwise_xor_tt

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

__xor___tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
__xor___tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
__xor___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.__xor___tt

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

__lshift___tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
__lshift___tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
__lshift___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.__lshift___tt

bitwise_left_shift_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_left_shift_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_left_shift_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.bitwise_left_shift_tt

bitwise_left_shift_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_left_shift_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_left_shift_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.bitwise_left_shift_out_ttt

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

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

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

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

__rshift___tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
__rshift___tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
__rshift___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.__rshift___tt

bitwise_right_shift_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_right_shift_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_right_shift_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.bitwise_right_shift_tt

bitwise_right_shift_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
bitwise_right_shift_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
bitwise_right_shift_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.bitwise_right_shift_out_ttt

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

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

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

addbmm_out_ttttss
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Scalar
  -> ForeignPtr Scalar
  -> IO (ForeignPtr Tensor)
addbmm_out_ttttss :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
addbmm_out_ttttss = (Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Tensor
 -> Ptr Scalar
 -> Ptr Scalar
 -> IO (Ptr Tensor))
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Scalar
-> ForeignPtr Scalar
-> IO (ForeignPtr Tensor)
forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 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 Scalar
-> Ptr Scalar
-> IO (Ptr Tensor)
Unmanaged.addbmm_out_ttttss

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

addbmm_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
addbmm_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
addbmm_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.addbmm_out_tttt

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

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

addbmm_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
addbmm_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
addbmm_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.addbmm_ttt

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

diag_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
diag_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
diag_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.diag_out_tt

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

diag_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
diag_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
diag_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.diag_t

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

cross_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
cross_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
cross_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.cross_out_ttt

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

cross_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
cross_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
cross_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.cross_tt

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

triu_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
triu_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
triu_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.triu_out_tt

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

triu_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
triu_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
triu_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.triu_t

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

tril_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tril_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tril_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.tril_out_tt

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

tril_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
tril_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
tril_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.tril_t

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

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

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