-- generated by using spec/Declarations.yaml

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

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


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

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

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

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

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

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

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

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

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

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

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

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

-- sort_tbl
--   :: ForeignPtr Tensor
--   -> CBool
--   -> Int64
--   -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
-- sort_tbl = _cast3 Unmanaged.sort_tbl

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

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

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

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

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

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

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

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

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

msort_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
msort_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
msort_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.msort_out_tt

msort_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
msort_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
msort_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.msort_t

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

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

argsort_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
argsort_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
argsort_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.argsort_t

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

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

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

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

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

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

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

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

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

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

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

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

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

all_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
all_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
all_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.all_t

all_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
all_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
all_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.all_out_tt

any_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
any_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
any_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.any_t

any_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
any_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
any_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.any_out_tt

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

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

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

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

pow_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
pow_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
pow_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.pow_out_ttt

pow_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
pow_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
pow_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.pow_tt

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

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

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

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

float_power_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
float_power_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
float_power_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.float_power_out_ttt

float_power_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
float_power_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
float_power_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.float_power_tt

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

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

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

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

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

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

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

normal_functional_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
normal_functional_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
normal_functional_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.normal_functional_t

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

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

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

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

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

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

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

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

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

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

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

normal_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
normal_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
normal_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.normal_out_ttt

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

normal_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
normal_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
normal_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.normal_tt

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

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

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

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

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

alias_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
alias_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
alias_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.alias_t

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_foreach_add_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_add_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_add_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_add_lA

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

_foreach_sub_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_sub_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_sub_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_sub_lA

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

_foreach_div_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_div_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_div_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_div_lA

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

_foreach_mul_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_mul_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_mul_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_mul_lA

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

_foreach_clamp_min_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_clamp_min_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_clamp_min_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_clamp_min_lA

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

_foreach_clamp_max_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_clamp_max_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_clamp_max_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_clamp_max_lA

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

_foreach_maximum_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_maximum_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_maximum_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_maximum_lA

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

_foreach_minimum_lA
  :: ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_minimum_lA :: ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar) -> IO (ForeignPtr TensorList)
_foreach_minimum_lA = (Ptr TensorList -> Ptr (StdVector Scalar) -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 (StdVector Scalar) -> IO (Ptr TensorList)
Unmanaged._foreach_minimum_lA

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_foreach_addcdiv_lllA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_addcdiv_lllA :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO (ForeignPtr TensorList)
_foreach_addcdiv_lllA = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr (StdVector Scalar)
 -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 TensorList
-> Ptr TensorList
-> Ptr (StdVector Scalar)
-> IO (Ptr TensorList)
Unmanaged._foreach_addcdiv_lllA

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

_foreach_addcmul_lllA
  :: ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr TensorList
  -> ForeignPtr (StdVector Scalar)
  -> IO (ForeignPtr TensorList)
_foreach_addcmul_lllA :: ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> IO (ForeignPtr TensorList)
_foreach_addcmul_lllA = (Ptr TensorList
 -> Ptr TensorList
 -> Ptr TensorList
 -> Ptr (StdVector Scalar)
 -> IO (Ptr TensorList))
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr TensorList
-> ForeignPtr (StdVector Scalar)
-> 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 TensorList
-> Ptr TensorList
-> Ptr (StdVector Scalar)
-> IO (Ptr TensorList)
Unmanaged._foreach_addcmul_lllA

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_convert_indices_from_csr_to_coo_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_convert_indices_from_csr_to_coo_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_convert_indices_from_csr_to_coo_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._convert_indices_from_csr_to_coo_tt

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

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

_convert_indices_from_csr_to_coo_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
_convert_indices_from_csr_to_coo_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
_convert_indices_from_csr_to_coo_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._convert_indices_from_csr_to_coo_out_ttt

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

mse_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
mse_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
mse_loss_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.mse_loss_out_ttt

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

mse_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
mse_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
mse_loss_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.mse_loss_tt

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

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

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

l1_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
l1_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
l1_loss_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.l1_loss_tt

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

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

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

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

multi_margin_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
multi_margin_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
multi_margin_loss_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.multi_margin_loss_out_ttt

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

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

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

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

multi_margin_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
multi_margin_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
multi_margin_loss_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.multi_margin_loss_tt

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

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

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

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

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

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

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

multilabel_margin_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
multilabel_margin_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
multilabel_margin_loss_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.multilabel_margin_loss_out_ttt

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

multilabel_margin_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
multilabel_margin_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
multilabel_margin_loss_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.multilabel_margin_loss_tt

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

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

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

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

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

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

nll_loss_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
nll_loss_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.nll_loss_out_tttt

nll_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_loss_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.nll_loss_out_ttt

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

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

nll_loss_nd_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss_nd_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_loss_nd_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.nll_loss_nd_ttt

nll_loss_nd_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss_nd_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_loss_nd_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.nll_loss_nd_tt