{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Torch.Internal.Managed.Native.Native12 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.Native12 as Unmanaged
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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = forall a 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = forall a 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_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 = forall a 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 = forall a 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 = forall a 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = forall a 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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_unpool2d_backward_out_ttttl
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool2d_backward_out_ttttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool2d_backward_out_ttttl = forall a ca x1 cx1 x2 cx2 x3 cx3 x4 cx4 y cy.
(Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3,
Castable x4 cx4, Castable y cy) =>
(ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy)
-> a -> x1 -> x2 -> x3 -> x4 -> IO y
_cast5 Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr Tensor
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_unpool2d_backward_out_ttttl
max_unpool2d_backward_tttl
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool2d_backward_tttl :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool2d_backward_tttl = 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_backward_tttl
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 = 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 = 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
max_unpool3d_backward_out_ttttlll
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool3d_backward_out_ttttlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool3d_backward_out_ttttlll = 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 IntArray
-> Ptr IntArray
-> Ptr IntArray
-> IO (Ptr Tensor)
Unmanaged.max_unpool3d_backward_out_ttttlll
max_unpool3d_backward_tttlll
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool3d_backward_tttlll :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> IO (ForeignPtr Tensor)
max_unpool3d_backward_tttlll = 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_backward_tttlll
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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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
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 = 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_linear1d_backward_tllba
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_linear1d_backward_tllba :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_linear1d_backward_tllba = 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
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_linear1d_backward_tllba
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 = 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_backward_tllba
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_bilinear2d_backward_tllba :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_bilinear2d_backward_tllba = 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
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_bilinear2d_backward_tllba
_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 = 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_bilinear2d_aa_backward_tllba
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_bilinear2d_aa_backward_tllba :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_bilinear2d_aa_backward_tllba = 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
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged._upsample_bilinear2d_aa_backward_tllba
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 = 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_trilinear3d_backward_tllba
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_backward_tllba :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_backward_tllba = 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
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_trilinear3d_backward_tllba
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 = 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_backward_tllba
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_tllba :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_tllba = 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
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_bicubic2d_backward_tllba
_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 = 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_bicubic2d_aa_backward_tllba
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_tllba :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_tllba = 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
-> Ptr (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged._upsample_bicubic2d_aa_backward_tllba
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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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_nearest1d_backward_tlla
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_nearest1d_backward_tlla :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_nearest1d_backward_tlla = 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 (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_nearest1d_backward_tlla
_upsample_nearest_exact1d_backward_tlla
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_nearest_exact1d_backward_tlla :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_nearest_exact1d_backward_tlla = 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 (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged._upsample_nearest_exact1d_backward_tlla
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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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_nearest2d_backward_tlla
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_nearest2d_backward_tlla :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_nearest2d_backward_tlla = 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 (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_nearest2d_backward_tlla
_upsample_nearest_exact2d_backward_tlla
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_nearest_exact2d_backward_tlla :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_nearest_exact2d_backward_tlla = 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 (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged._upsample_nearest_exact2d_backward_tlla
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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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_nearest3d_backward_tlla
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_nearest3d_backward_tlla :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
upsample_nearest3d_backward_tlla = 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 (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged.upsample_nearest3d_backward_tlla
_upsample_nearest_exact3d_backward_tlla
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_nearest_exact3d_backward_tlla :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> ForeignPtr (StdVector CDouble)
-> IO (ForeignPtr Tensor)
_upsample_nearest_exact3d_backward_tlla = 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 (StdVector CDouble)
-> IO (Ptr Tensor)
Unmanaged._upsample_nearest_exact3d_backward_tlla
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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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_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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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 = 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 = 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 = 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 = 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_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 = 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 = 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 = 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 = 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 = 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 = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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
upsample_bicubic2d_backward_out_ttllbdd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_out_ttllbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_out_ttllbdd = 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_bicubic2d_backward_out_ttllbdd
upsample_bicubic2d_backward_out_ttllbd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_out_ttllbd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_out_ttllbd = 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_bicubic2d_backward_out_ttllbd
upsample_bicubic2d_backward_out_ttllb
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_out_ttllb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_out_ttllb = 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_bicubic2d_backward_out_ttllb
upsample_bicubic2d_backward_tllbdd
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_tllbdd :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_tllbdd = 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_bicubic2d_backward_tllbdd
upsample_bicubic2d_backward_tllb
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_tllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_bicubic2d_backward_tllb = 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_bicubic2d_backward_tllb
_upsample_bicubic2d_aa_out_ttlbdd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_out_ttlbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_out_ttlbdd = 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_aa_out_ttlbdd
_upsample_bicubic2d_aa_out_ttlbd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_out_ttlbd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_out_ttlbd = 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_aa_out_ttlbd
_upsample_bicubic2d_aa_out_ttlb
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_out_ttlb = 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_aa_out_ttlb
_upsample_bicubic2d_aa_tlbdd
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_tlbdd :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_tlbdd = 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_aa_tlbdd
_upsample_bicubic2d_aa_tlb
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_tlb :: ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_tlb = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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_aa_tlb
_upsample_bicubic2d_aa_backward_out_ttllbdd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbdd = 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_bicubic2d_aa_backward_out_ttllbdd
_upsample_bicubic2d_aa_backward_out_ttllbd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllbd = 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_bicubic2d_aa_backward_out_ttllbd
_upsample_bicubic2d_aa_backward_out_ttllb
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_out_ttllb = 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_bicubic2d_aa_backward_out_ttllb
_upsample_bicubic2d_aa_backward_tllbdd
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_tllbdd :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_tllbdd = 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_bicubic2d_aa_backward_tllbdd
_upsample_bicubic2d_aa_backward_tllb
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_tllb :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
_upsample_bicubic2d_aa_backward_tllb = 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_bicubic2d_aa_backward_tllb
upsample_trilinear3d_out_ttlbddd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlbddd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlbddd = 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
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
Unmanaged.upsample_trilinear3d_out_ttlbddd
upsample_trilinear3d_out_ttlbdd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlbdd = 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_trilinear3d_out_ttlbdd
upsample_trilinear3d_out_ttlbd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlbd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlbd = 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_trilinear3d_out_ttlbd
upsample_trilinear3d_out_ttlb
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlb :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_out_ttlb = 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_trilinear3d_out_ttlb
upsample_trilinear3d_tlbddd
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_tlbddd :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_tlbddd = 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
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
Unmanaged.upsample_trilinear3d_tlbddd
upsample_trilinear3d_tlbdd
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_tlbdd :: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_tlbdd = 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_trilinear3d_tlbdd
upsample_trilinear3d_tlb
:: ForeignPtr Tensor
-> ForeignPtr IntArray
-> CBool
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_tlb :: ForeignPtr Tensor
-> ForeignPtr IntArray -> CBool -> IO (ForeignPtr Tensor)
upsample_trilinear3d_tlb = forall a ca x1 cx1 x2 cx2 y cy.
(Castable 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_trilinear3d_tlb
upsample_trilinear3d_backward_out_ttllbddd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_backward_out_ttllbddd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_backward_out_ttllbddd = 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
-> CBool
-> CDouble
-> CDouble
-> CDouble
-> IO (Ptr Tensor)
Unmanaged.upsample_trilinear3d_backward_out_ttllbddd
upsample_trilinear3d_backward_out_ttllbdd
:: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_backward_out_ttllbdd :: ForeignPtr Tensor
-> ForeignPtr Tensor
-> ForeignPtr IntArray
-> ForeignPtr IntArray
-> CBool
-> CDouble
-> CDouble
-> IO (ForeignPtr Tensor)
upsample_trilinear3d_backward_out_ttllbdd = 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_trilinear3d_backward_out_ttllbdd