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.Static.NN.Conv1d

Description

Temporal (1D) Convolutions

Synopsis

Documentation

newtype Conv1d f o kW dW Source #

ADT representation of a convolutional 1d layer.

FIXME: the type is a bit of a hiccup: can we remove the kernel dimensions or move pad/stride into the phantoms?

See Conv2d for ideas.

Constructors

Conv1d 

Fields

Instances
(KnownDim f, KnownDim o, KnownDim kW, KnownDim dW) => Show (Conv1d f o kW dW) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv1d

Methods

showsPrec :: Int -> Conv1d f o kW dW -> ShowS #

show :: Conv1d f o kW dW -> String #

showList :: [Conv1d f o kW dW] -> ShowS #

(KnownDim (f * kW), KnownDim o) => Backprop (Conv1d f o kW dW) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv1d

Methods

zero :: Conv1d f o kW dW -> Conv1d f o kW dW

add :: Conv1d f o kW dW -> Conv1d f o kW dW -> Conv1d f o kW dW

one :: Conv1d f o kW dW -> Conv1d f o kW dW

weights :: Conv1d f o kW dW -> Tensor '[o, f * kW] Source #

get the weights from a Conv1d ADT

bias :: Conv1d f o kW dW -> Tensor '[o] Source #

get the bias from a Conv1d ADT

featureSize :: forall f o kW dW. KnownDim f => Conv1d f o kW dW -> Int Source #

get the featureSize from a Conv1d ADT

kernelWidth :: forall f o kW dW. KnownDim kW => Conv1d f o kW dW -> Int Source #

kW: The kernel width of the convolution

stepSize :: forall f o kW dW. KnownDim dW => Conv1d f o kW dW -> Int Source #

dW: The step of the convolution. Default is 1 in C.

conv1d :: forall s seq f kW dW o. Reifies s W => KnownDim (f * kW) => TemporalConvC seq f kW dW o => Double -> BVar s (Conv1d f o kW dW) -> BVar s (Tensor '[seq, f]) -> BVar s (Tensor '[seq, o]) Source #

Backprop convolution function

conv1d_forward :: TemporalConvC s f kW dW o => Conv1d f o kW dW -> Tensor '[s, f] -> IO (Tensor '[s, o]) Source #

If the input sequence is a 2D tensor of dimension (nInputFrame x inputFrameSize), the output sequence will be (nOutputFrame x outputFrameSize) where

nOutputFrame = (nInputFrame - kW) / dW + 1

conv1d_backwardGradInput Source #

Arguments

:: TemporalConvC seq f kW dW o 
=> Conv1d f o kW dW

conv1d state

-> Tensor '[seq, f]

input: s for 'sequence dimension', f for 'feature dimension'

-> Tensor '[seq, o]

grad output

-> IO (Tensor '[seq, f])

grad input

backward pass, computing the gradient input

conv1d_updGradParams Source #

Arguments

:: TemporalConvC s f kW dW o 
=> Conv1d f o kW dW

input state of conv1d (which includes weights and bias)

-> Tensor '[s, f]

input tensor

-> Tensor '[s, o]

output gradient

-> Double

scale

-> IO (Conv1d f o kW dW)

gradient of (weights, bias)

backward pass, computing the weight and bias parameters

WARNING: this is _pure_ which may be slow for large tensors. Speeding this up will be in active development as the need arises (see issue hasktorch/hasktorch#85)

conv1dBatch :: forall s seq f kW dW o b. Reifies s W => KnownDim b => KnownDim (f * kW) => TemporalConvC seq f kW dW o => Double -> BVar s (Conv1d f o kW dW) -> BVar s (Tensor '[b, seq, f]) -> BVar s (Tensor '[b, seq, o]) Source #

Backprop convolution function with batching

conv1d_forwardBatch :: TemporalConvC s f kW dW o => Conv1d f o kW dW -> Tensor '[b, s, f] -> IO (Tensor '[b, s, o]) Source #

Applies a 1D convolution over an input sequence composed of nInputFrame frames. The input tensor in forward(input) is expected to be a 2D tensor (nInputFrame x inputFrameSize) or a 3D tensor (nBatchFrame x nInputFrame x inputFrameSize).

conv1d_backwardGradInputBatch Source #

Arguments

:: TemporalConvC s f kW dW o 
=> KnownDim b 
=> Conv1d f o kW dW

conv1d state

-> Tensor '[b, s, f]

input: s for 'sequence dimension', f for 'feature dimension'

-> Tensor '[b, s, o]

grad output

-> IO (Tensor '[b, s, f])

output

conv1d_backwardGradInput with a batch dimension

conv1d_updGradParamsBatch Source #

Arguments

:: TemporalConvC s f kW dW o 
=> KnownDim b 
=> Conv1d f o kW dW

conv1d state

-> Tensor '[b, s, f]

input: s for 'sequence dimension', f for 'feature dimension'

-> Tensor '[b, s, o]

grad output

-> Double

scale

-> IO (Conv1d f o kW dW)

output

conv1d_updGradParams with a batch dimension

_temporalRowConvolution_updateOutput :: Tensor d -> Tensor d' -> Tensor d'' -> Tensor d''' -> Tensor d -> Tensor d -> Int -> Int -> Int -> Bool -> IO () Source #

temporalRowConvolution forward pass (updates the output tensor)

_temporalRowConvolution_updateGradInput :: Tensor d -> Tensor d' -> Tensor d'' -> Tensor d''' -> Tensor d -> Tensor d -> Int -> Int -> Int -> Bool -> IO () Source #

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

_temporalRowConvolution_updGradParameters :: Tensor d -> Tensor d' -> Tensor d'' -> Tensor d''' -> Tensor d -> Tensor d -> 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.