-- generated by using spec/Declarations.yaml

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

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


nll_loss_tttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
nll_loss_tttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
nll_loss_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_tttll

nll_loss_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
nll_loss_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
nll_loss_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_tttl

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

nll_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_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.nll_loss_tt

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

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

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

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

nll_loss2d_out_ttttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
nll_loss2d_out_ttttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_out_ttttll

nll_loss2d_out_ttttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
nll_loss2d_out_ttttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_out_ttttl

nll_loss2d_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss2d_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_out_tttt

nll_loss2d_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss2d_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_out_ttt

nll_loss2d_tttll
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> Int64
  -> IO (ForeignPtr Tensor)
nll_loss2d_tttll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> Int64
-> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_tttll

nll_loss2d_tttl
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> Int64
  -> IO (ForeignPtr Tensor)
nll_loss2d_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> Int64
-> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_tttl

nll_loss2d_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss2d_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_ttt

nll_loss2d_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
nll_loss2d_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
nll_loss2d_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_loss2d_tt

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

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

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

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

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

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

smooth_l1_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
smooth_l1_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
smooth_l1_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.smooth_l1_loss_out_ttt

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

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

smooth_l1_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
smooth_l1_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
smooth_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.smooth_l1_loss_tt

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

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

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

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

huber_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
huber_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
huber_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.huber_loss_out_ttt

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

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

huber_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
huber_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
huber_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.huber_loss_tt

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

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

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

soft_margin_loss_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
soft_margin_loss_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
soft_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.soft_margin_loss_out_ttt

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

soft_margin_loss_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
soft_margin_loss_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
soft_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.soft_margin_loss_tt

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

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

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

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

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

elu_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
elu_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
elu_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.elu_out_tt

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

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

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

elu_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
elu_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
elu_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.elu_t

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

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

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

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

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

elu__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
elu__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
elu__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.elu__t

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

glu_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
glu_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
glu_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.glu_out_tt

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

glu_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
glu_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
glu_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.glu_t

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

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

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

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

hardsigmoid_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardsigmoid_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardsigmoid_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.hardsigmoid_out_tt

hardsigmoid_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardsigmoid_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardsigmoid_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.hardsigmoid_t

hardsigmoid__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardsigmoid__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardsigmoid__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.hardsigmoid__t

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

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

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

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

hardtanh_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardtanh_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardtanh_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.hardtanh_out_tt

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

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

hardtanh_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardtanh_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardtanh_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.hardtanh_t

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

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

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

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

hardtanh__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardtanh__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardtanh__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.hardtanh__t

hardswish_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardswish_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardswish_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.hardswish_out_tt

hardswish_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardswish_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardswish_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.hardswish_t

hardswish__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
hardswish__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
hardswish__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.hardswish__t

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

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

leaky_relu_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
leaky_relu_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
leaky_relu_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.leaky_relu_out_tt

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

leaky_relu_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
leaky_relu_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
leaky_relu_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.leaky_relu_t

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

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

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

leaky_relu__t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
leaky_relu__t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
leaky_relu__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.leaky_relu__t

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

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

log_sigmoid_forward_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
log_sigmoid_forward_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
log_sigmoid_forward_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.log_sigmoid_forward_out_ttt

log_sigmoid_forward_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr (StdTuple '(Tensor,Tensor)))
log_sigmoid_forward_t :: ForeignPtr Tensor -> IO (ForeignPtr (StdTuple '(Tensor, Tensor)))
log_sigmoid_forward_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.log_sigmoid_forward_t

log_sigmoid_backward_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
log_sigmoid_backward_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
log_sigmoid_backward_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.log_sigmoid_backward_out_tttt

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

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

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

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

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

rrelu_with_noise_out_ttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rrelu_with_noise_out_ttt :: ForeignPtr Tensor
-> ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
rrelu_with_noise_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.rrelu_with_noise_out_ttt

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

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

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

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

rrelu_with_noise_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rrelu_with_noise_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
rrelu_with_noise_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.rrelu_with_noise_tt

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

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

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

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

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

rrelu_with_noise__tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
rrelu_with_noise__tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
rrelu_with_noise__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.rrelu_with_noise__tt

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

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

softplus_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
softplus_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
softplus_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.softplus_out_tt

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

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

softplus_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
softplus_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
softplus_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.softplus_t

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

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

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

softshrink_out_tt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
softshrink_out_tt :: ForeignPtr Tensor -> ForeignPtr Tensor -> IO (ForeignPtr Tensor)
softshrink_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.softshrink_out_tt

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

softshrink_t
  :: ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
softshrink_t :: ForeignPtr Tensor -> IO (ForeignPtr Tensor)
softshrink_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.softshrink_t

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

adaptive_max_pool2d_backward_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
adaptive_max_pool2d_backward_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
adaptive_max_pool2d_backward_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.adaptive_max_pool2d_backward_out_tttt

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

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

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

adaptive_max_pool3d_backward_out_tttt
  :: ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> ForeignPtr Tensor
  -> IO (ForeignPtr Tensor)
adaptive_max_pool3d_backward_out_tttt :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> IO (ForeignPtr Tensor)
adaptive_max_pool3d_backward_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.adaptive_max_pool3d_backward_out_tttt

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

-- _upsample_bilinear2d_aa_tlbd
--   :: ForeignPtr Tensor
--   -> ForeignPtr IntArray
--   -> CBool
--   -> CDouble
--   -> IO (ForeignPtr Tensor)
-- _upsample_bilinear2d_aa_tlbd = _cast4 Unmanaged._upsample_bilinear2d_aa_tlbd

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

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

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

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

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

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

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

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

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

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

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

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