hasktorch-indef-0.0.1.0: Core Hasktorch abstractions wrapping FFI bindings

Copyright(c) Sam Stites 2017
LicenseBSD3
Maintainersam@stites.io
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Torch.Indef.Dynamic.NN

Description

NN backpack API which is _not recommended to be used directly_. This package is just a wrapper around the backpack signatures of Torch's C-based NN library.

Instead, use NN which includes an AD abstraction, simple forward- and backward- functions, and staticly-typed dimension-level checking.

This library will, over time, iterate into type-safe code -- but for the moment we hoist the safety into the dependent types, which is faster to iterate with and is semantically clearer for development (the errors take a bit of getting used to).

Synopsis

Documentation

_abs_updateOutput :: Dynamic -> Dynamic -> IO () Source #

abs forward

_gatedLinear_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

gatedLinear backward-update (updates the layer and bias tensors)

_hardTanh_updateOutput :: Dynamic -> Dynamic -> Double -> Double -> Bool -> IO () Source #

hardTanh forward pass (updates the output tensor)

_hardTanh_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Double -> Double -> Bool -> IO () Source #

hardTanh backward-update (updates the layer and bias tensors)

_im2Col_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

im2Col forward pass (updates the output tensor)

_im2Col_updateGradInput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

im2Col backward-update (updates the layer and bias tensors)

_col2Im_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

col2Im forward pass (updates the output tensor)

_col2Im_updateGradInput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

col2Im backward-update (updates the layer and bias tensors)

_gRUFused_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

gRUFused forward pass (updates the output tensor)

_gRUFused_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

gRUFused backward-update (updates the layer and bias tensors)

_lSTMFused_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

lSTMFused forward pass (updates the output tensor)

_lSTMFused_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

lSTMFused backward-update (updates the layer and bias tensors)

_logSigmoid_updateOutput :: Dynamic -> Dynamic -> Dynamic -> IO () Source #

logSigmoid forward pass (updates the output tensor)

_logSigmoid_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

logSigmoid backward-update (updates the layer and bias tensors)

_logSoftMax_updateOutput :: Dynamic -> Dynamic -> Integer -> IO () Source #

logSoftMax forward pass (updates the output tensor)

_logSoftMax_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Integer -> IO () Source #

logSoftMax backward-update (updates the layer and bias tensors)

_sigmoid_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> IO () Source #

sigmoid backward-update (updates the layer and bias tensors)

_softMax_updateOutput :: Dynamic -> Dynamic -> Integer -> IO () Source #

softMax forward pass (updates the output tensor)

_softMax_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Integer -> IO () Source #

softMax backward-update (updates the layer and bias tensors)

_softPlus_updateOutput :: Dynamic -> Dynamic -> Double -> Double -> IO () Source #

softPlus forward pass (updates the output tensor)

_softPlus_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Double -> Double -> IO () Source #

softPlus backward-update (updates the layer and bias tensors)

_softShrink_updateOutput :: Dynamic -> Dynamic -> Double -> IO () Source #

softShrink forward pass (updates the output tensor)

_softShrink_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Double -> IO () Source #

softShrink backward-update (updates the layer and bias tensors)

_sparseLinear_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

sparseLinear forward pass (updates the output tensor)

_sparseLinear_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Double -> Double -> IO () Source #

sparseLinear backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_sparseLinear_zeroGradParameters :: Dynamic -> Dynamic -> Dynamic -> IO () Source #

sparseLinear zeroGradParameters

_sparseLinear_updateParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Double -> IO () Source #

sparseLinear updateParameters

_sparseLinear_legacyUpdateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

sparseLinear legacyUpdateOutput

_sparseLinear_legacyAccGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Double -> Double -> IO () Source #

sparseLinear legacyAccGradParameters

_sqrt_updateOutput :: Dynamic -> Dynamic -> Double -> IO () Source #

sqrt forward pass (updates the output tensor)

_sqrt_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> IO () Source #

sqrt backward-update (updates the layer and bias tensors)

_square_updateOutput :: Dynamic -> Dynamic -> IO () Source #

square forward pass (updates the output tensor)

_square_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> IO () Source #

square backward-update (updates the layer and bias tensors)

_tanh_updateOutput :: Dynamic -> Dynamic -> IO () Source #

tanh forward pass (updates the output tensor)

_tanh_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> IO () Source #

tanh backward-update (updates the layer and bias tensors)

_temporalConvolution_updateOutput Source #

Arguments

:: Dynamic

input

-> Dynamic

output -- this is the mutated return value

-> Dynamic

2d weight tensor

-> Dynamic

1d bias tensor

-> Int

kernel width

-> Int

step size

-> Int

feature size

-> Int

output size

-> IO () 

temporalConvolution forward pass (updates the output tensor)

_temporalConvolution_updateGradInput Source #

Arguments

:: Dynamic

input

-> Dynamic

grad output

-> Dynamic

grad input -- this is the mutated return value

-> Dynamic

weights

-> Int

kernel width

-> Int

step size

-> IO () 

temporalConvolution backward-update (updates the layer and bias tensors)

_temporalConvolution_accGradParameters Source #

Arguments

:: Dynamic

input

-> Dynamic

grad output

-> Dynamic

grad weight -- this is a mutated argument and torch will accumulate this gradient

-> Dynamic

grad bias -- this is a mutated argument and torch will accumulate this gradient

-> Int

kernel width

-> Int

step size

-> Double

scale

-> IO () 

temporalConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_temporalRowConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Bool -> IO () Source #

temporalRowConvolution forward pass (updates the output tensor)

_temporalRowConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Bool -> IO () Source #

temporalRowConvolution backward-update (updates the layer and bias tensors)

_temporalRowConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Bool -> Double -> IO () Source #

temporalRowConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_temporalUpSamplingNearest_updateOutput :: Dynamic -> Dynamic -> Int -> IO () Source #

temporalUpSamplingNearest forward pass (updates the output tensor)

_temporalUpSamplingNearest_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

temporalUpSamplingNearest backward-update (updates the layer and bias tensors)

_temporalUpSamplingLinear_updateOutput :: Dynamic -> Dynamic -> Int -> IO () Source #

temporalUpSamplingLinear forward pass (updates the output tensor)

_temporalUpSamplingLinear_updateGradInput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

temporalUpSamplingLinear backward-update (updates the layer and bias tensors)

_batchNormalization_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Bool -> Double -> Double -> IO () Source #

batchNormalization forward pass (updates the output tensor)

_batchNormalization_backward :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Bool -> Double -> Double -> IO () Source #

batchNormalization backward

spatialConvolutionMM_updateOutput Source #

Arguments

:: Dynamic

input

-> Dynamic

3D weight tensor (connTable:size(1) x kH x kW)

-> Dynamic

1D bias tensor (nOutputPlane)

-> (Int, Int)

(kW, kH) kernel height and width

-> (Int, Int)

(dW, dH) step of the convolution in width and height dimensions. C-default is 1 for both.

-> (Int, Int)

(pW, pH) zero padding to the input plane for width and height. (kW-1)/2 is often used. C-default is 0 for both.

-> IO Dynamic

output

spatialConvolutionMM forward pass

_spatialConvolutionMM_updateOutput Source #

Arguments

:: Dynamic

input

-> Dynamic

output

-> Dynamic

3D weight tensor (connTable:size(1) x kH x kW)

-> Dynamic

1D bias tensor (nOutputPlane)

-> Dynamic

BUFFER: temporary columns

-> Dynamic

BUFFER: buffer of ones for bias accumulation

-> (Int, Int)

(kW, kH) kernel height and width

-> (Int, Int)

(dW, dH) step of the convolution in width and height dimensions. C-default is 1 for both.

-> (Int, Int)

(pW, pH) zero padding to the input plane for width and height. (kW-1)/2 is often used. C-default is 0 for both.

-> IO () 

spatialConvolutionMM forward pass

_spatialConvolutionMM_updateGradInput Source #

Arguments

:: Dynamic

input

-> Dynamic

gradOutput

-> Dynamic

gradInput

-> Dynamic

weight

-> Dynamic

columns

-> Dynamic

ones

-> (Int, Int)

(kW, kH) kernel height and width

-> (Int, Int)

(dW, dH) step of the convolution in width and height dimensions

-> (Int, Int)

(pW, pH) zero padding to the input plane for width and height. (kW-1)/2 is often used.

-> IO () 

spatialConvolutionMM backward-update (updates the layer and bias tensors)

_spatialConvolutionMM_accGradParameters Source #

Arguments

:: Dynamic

input

-> Dynamic

gradOutput

-> Dynamic

gradWeight

-> Dynamic

gradBias

-> Dynamic

finput/columns <<- required. This can be NULL in C if gradWeight is NULL.

-> Dynamic

ones

-> (Int, Int)

(kW, kH) kernel height and width

-> (Int, Int)

(dW, dH) step of the convolution in width and height dimensions

-> (Int, Int)

(pW, pH) zero padding to the input plane for width and height. (kW-1)/2 is often used.

-> Double 
-> IO () 

spatialConvolutionMM backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialConvolutionLocal_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

spatialConvolutionLocal forward pass (updates the output tensor)

_spatialConvolutionLocal_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> CLLong -> CLLong -> CLLong -> CLLong -> IO () Source #

spatialConvolutionLocal backward-update (updates the layer and bias tensors)

_spatialConvolutionLocal_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> CLLong -> CLLong -> CLLong -> CLLong -> Double -> IO () Source #

spatialConvolutionLocal backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialFullConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialFullConvolution forward pass (updates the output tensor)

_spatialFullConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialFullConvolution backward-update (updates the layer and bias tensors)

_spatialFullConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

spatialFullConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialDilatedConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialDilatedConvolution forward pass (updates the output tensor)

_spatialDilatedConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialDilatedConvolution backward-update (updates the layer and bias tensors)

_spatialDilatedConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

spatialDilatedConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialFullDilatedConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialFullDilatedConvolution forward pass (updates the output tensor)

_spatialFullDilatedConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialFullDilatedConvolution backward-update (updates the layer and bias tensors)

_spatialFullDilatedConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

spatialFullDilatedConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialSubSampling_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

spatialSubSampling forward pass (updates the output tensor)

_spatialSubSampling_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

spatialSubSampling backward-update (updates the layer and bias tensors)

_spatialSubSampling_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Double -> IO () Source #

spatialSubSampling backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialUpSamplingNearest_updateOutput :: Dynamic -> Dynamic -> Int -> IO () Source #

spatialUpSamplingNearest forward pass (updates the output tensor)

_spatialUpSamplingNearest_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

spatialUpSamplingNearest backward-update (updates the layer and bias tensors)

_spatialUpSamplingBilinear_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> IO () Source #

spatialUpSamplingBilinear forward pass (updates the output tensor)

_spatialUpSamplingBilinear_updateGradInput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

spatialUpSamplingBilinear backward-update (updates the layer and bias tensors)

_spatialGridSamplerBilinear_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

spatialGridSamplerBilinear forward pass (updates the output tensor)

_spatialGridSamplerBilinear_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

spatialGridSamplerBilinear backward-update (updates the layer and bias tensors)

_volumetricGridSamplerBilinear_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

volumetricGridSamplerBilinear forward pass (updates the output tensor)

_volumetricGridSamplerBilinear_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

volumetricGridSamplerBilinear backward-update (updates the layer and bias tensors)

_volumetricConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricConvolution forward pass (updates the output tensor)

_volumetricConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricConvolution backward-update (updates the layer and bias tensors)

_volumetricConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

volumetricConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_volumetricFullConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricFullConvolution forward pass (updates the output tensor)

_volumetricFullConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricFullConvolution backward-update (updates the layer and bias tensors)

_volumetricFullConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

volumetricFullConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_volumetricDilatedConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricDilatedConvolution forward pass (updates the output tensor)

_volumetricDilatedConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricDilatedConvolution backward-update (updates the layer and bias tensors)

_volumetricDilatedConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

volumetricDilatedConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_volumetricFullDilatedConvolution_updateOutput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricFullDilatedConvolution forward pass (updates the output tensor)

_volumetricFullDilatedConvolution_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricFullDilatedConvolution backward-update (updates the layer and bias tensors)

_volumetricFullDilatedConvolution_accGradParameters :: Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Double -> IO () Source #

volumetricFullDilatedConvolution backward-update (updates the layer and bias tensors). Called accGradParameters in C to indicate accumulating the gradient parameters.

_spatialReflectionPadding_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

spatialReflectionPadding forward pass (updates the output tensor)

_spatialReflectionPadding_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

spatialReflectionPadding backward-update (updates the layer and bias tensors)

_spatialReplicationPadding_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

spatialReplicationPadding forward pass (updates the output tensor)

_spatialReplicationPadding_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> IO () Source #

spatialReplicationPadding backward-update (updates the layer and bias tensors)

_volumetricReplicationPadding_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricReplicationPadding forward pass (updates the output tensor)

_volumetricReplicationPadding_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricReplicationPadding backward-update (updates the layer and bias tensors)

_volumetricUpSamplingNearest_updateOutput :: Dynamic -> Dynamic -> Int -> IO () Source #

volumetricUpSamplingNearest forward pass (updates the output tensor)

_volumetricUpSamplingNearest_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> IO () Source #

volumetricUpSamplingNearest backward-update (updates the layer and bias tensors)

_volumetricUpSamplingTrilinear_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> Int -> IO () Source #

volumetricUpSamplingTrilinear forward pass (updates the output tensor)

_volumetricUpSamplingTrilinear_updateGradInput :: Dynamic -> Dynamic -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #

volumetricUpSamplingTrilinear backward-update (updates the layer and bias tensors)

_temporalReflectionPadding_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> IO () Source #

temporalReflectionPadding forward pass (updates the output tensor)

_temporalReflectionPadding_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> Int -> IO () Source #

temporalReflectionPadding backward-update (updates the layer and bias tensors)

_temporalReplicationPadding_updateOutput :: Dynamic -> Dynamic -> Int -> Int -> IO () Source #

temporalReplicationPadding forward pass (updates the output tensor)

_temporalReplicationPadding_updateGradInput :: Dynamic -> Dynamic -> Dynamic -> Int -> Int -> IO () Source #

temporalReplicationPadding backward-update (updates the layer and bias tensors)