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.Conv2d

Description

Spatial (2D) Convolutions.

Excluding an optional batch dimension, spatial layers expect a 3D Tensor as input. The first dimension is the number of features (e.g. frameSize), the last two dimensions are spatial (e.g. height x width). These are commonly used for processing images.

Complete types and documentation at https://github.com/torch/nn/blob/master/doc/convolution.md#spatial-modules

Synopsis

Documentation

newtype Conv2d i o kers Source #

ADT representation of a convolutional 2d layer.

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

possibly something like Conv2d i o (kH, kW) (dH, dW) (pH, pW) or Conv2d i o (kH, kW) (Maybe (dH, dW)) (Maybe (pH, pW))

Constructors

Conv2d 

Fields

Instances
Param2d (Conv2d f o) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Conv2d f o (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Conv2d f o (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Conv2d f o (h, w) -> (i, i) Source #

All (KnownDim :: Nat -> Constraint) (i ': (o ': (Fst kers ': (Snd kers ': ([] :: [Nat]))))) => Num (Conv2d i o kers) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

(+) :: Conv2d i o kers -> Conv2d i o kers -> Conv2d i o kers #

(-) :: Conv2d i o kers -> Conv2d i o kers -> Conv2d i o kers #

(*) :: Conv2d i o kers -> Conv2d i o kers -> Conv2d i o kers #

negate :: Conv2d i o kers -> Conv2d i o kers #

abs :: Conv2d i o kers -> Conv2d i o kers #

signum :: Conv2d i o kers -> Conv2d i o kers #

fromInteger :: Integer -> Conv2d i o kers #

(KnownDim i, KnownDim o, KnownDim kH, KnownDim kW) => Show (Conv2d i o ((,) kH kW)) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

showsPrec :: Int -> Conv2d i o (kH, kW) -> ShowS #

show :: Conv2d i o (kH, kW) -> String #

showList :: [Conv2d i o (kH, kW)] -> ShowS #

(KnownDim i, KnownDim o, KnownDim kH, KnownDim kW) => Backprop (Conv2d i o ((,) kH kW)) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

zero :: Conv2d i o (kH, kW) -> Conv2d i o (kH, kW)

add :: Conv2d i o (kH, kW) -> Conv2d i o (kH, kW) -> Conv2d i o (kH, kW)

one :: Conv2d i o (kH, kW) -> Conv2d i o (kH, kW)

All (KnownDim :: Nat -> Constraint) (i ': (o ': (Fst kers ': (Snd kers ': ([] :: [Nat]))))) => Pairwise (Conv2d i o kers) HsReal Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

(^+) :: Conv2d i o kers -> HsReal -> Conv2d i o kers Source #

(^-) :: Conv2d i o kers -> HsReal -> Conv2d i o kers Source #

(^*) :: Conv2d i o kers -> HsReal -> Conv2d i o kers Source #

(^/) :: Conv2d i o kers -> HsReal -> Conv2d i o kers Source #

update Source #

Arguments

:: (KnownDim i, KnownDim o, KnownDim kH, KnownDim kW) 
=> Conv2d i o '(kH, kW)

network to update

-> HsReal

learning rate

-> Conv2d i o '(kH, kW)

gradient

-> Conv2d i o '(kH, kW)

updated network

update a Conv2d layer

update_ Source #

Arguments

:: (KnownDim i, KnownDim o, KnownDim kH, KnownDim kW) 
=> Conv2d i o '(kH, kW)

network to update

-> HsReal

learning rate

-> Conv2d i o '(kH, kW)

gradient

-> IO ()

update network

update a Conv2d layer inplace

weights :: Conv2d i o '(kH, kW) -> Tensor '[o, i, kH, kW] Source #

get the weights from a Conv2d ADT

bias :: Conv2d i o '(kH, kW) -> Tensor '[o] Source #

get the bias from a Conv2d ADT

featureSize :: forall i o kH kW. KnownDim i => Conv2d i o '(kH, kW) -> Int Source #

get the featureSize from a Conv2d ADT

outputSize :: forall f o kH kW. KnownDim o => Conv2d f o '(kH, kW) -> Int Source #

get the outputSize from a Conv2d ADT

kernelWidth :: forall i f o kH kW. (Integral i, KnownDim kW) => Conv2d f o '(kH, kW) -> i Source #

get the kernelWidth from a Conv2d ADT

kernelHeight :: forall i f o kH kW. (Integral i, KnownDim kH) => Conv2d f o '(kH, kW) -> i Source #

get the kernelHeight from a Conv2d ADT

kernel2d :: (Integral i, KnownDim kH, KnownDim kW) => Conv2d f o '(kH, kW) -> (i, i) Source #

get the kernel tuple as (width, height) from a Conv2d ADT

FIXME: Isn't this supposed to be "height" then "width"???

class Param2d (p :: (Nat, Nat) -> Type) where Source #

Typeclass to generically pull out Width and Height information from a parameter

FIXME: this can be replaced with simple functions.

Minimal complete definition

Nothing

Methods

paramW :: forall w h i. (KnownDim w, Integral i) => p '(h, w) -> i Source #

get the width parameter

paramH :: forall w h i. (KnownDim h, Integral i) => p '(h, w) -> i Source #

get the height parameter

param2d :: (KnownDim h, KnownDim w, Integral i) => p '(h, w) -> (i, i) Source #

get both parameters as a (width, height) tuple FIXME: Isn't this supposed to be "height" then "width"???

Instances
Param2d Dilation2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Dilation2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Dilation2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Dilation2d (h, w) -> (i, i) Source #

Param2d Kernel2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Kernel2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Kernel2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Kernel2d (h, w) -> (i, i) Source #

Param2d Padding2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Padding2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Padding2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Padding2d (h, w) -> (i, i) Source #

Param2d Step2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Step2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Step2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Step2d (h, w) -> (i, i) Source #

Param2d (Conv2d f o) Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Conv2d f o (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Conv2d f o (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Conv2d f o (h, w) -> (i, i) Source #

data Step2d (hw :: (Nat, Nat)) Source #

Representation of how much to step in the height and width dimensions

Constructors

Step2d 
Instances
Param2d Step2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Step2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Step2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Step2d (h, w) -> (i, i) Source #

data Padding2d (hw :: (Nat, Nat)) Source #

Representation of how much to pad in the height and width dimensions

Constructors

Padding2d 
Instances
Param2d Padding2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Padding2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Padding2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Padding2d (h, w) -> (i, i) Source #

data Kernel2d (hw :: (Nat, Nat)) Source #

Representation of how big a kernel will be in the height and width dimensions

Constructors

Kernel2d 
Instances
Param2d Kernel2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Kernel2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Kernel2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Kernel2d (h, w) -> (i, i) Source #

data Dilation2d (hw :: (Nat, Nat)) Source #

Representation of how much to dilate in the height and width dimensions

Constructors

Dilation2d 
Instances
Param2d Dilation2d Source # 
Instance details

Defined in Torch.Indef.Static.NN.Conv2d

Methods

paramW :: (KnownDim w, Integral i) => Dilation2d (h, w) -> i Source #

paramH :: (KnownDim h, Integral i) => Dilation2d (h, w) -> i Source #

param2d :: (KnownDim h, KnownDim w, Integral i) => Dilation2d (h, w) -> (i, i) Source #

type SpatialConvolutionC f h w kH kW dH dW pH pW oH oW = (All KnownDim '[(f * kH) * kW, oH * oW, f], SideCheck h kH dH pH oH, SideCheck w kW dW pW oW) Source #

Constraint to check both sides (height and width) of a function and assert that all nessecary dimension values are KnownDims.

type SideCheck h k d p o = (All KnownDim '[h, k, d, p, o], (k > 0) ~ True, (d > 0) ~ True, ((h + (2 * p)) < k) ~ False, (o > 0) ~ True, o ~ (Div ((h + (2 * p)) - k) d + 1)) Source #

Constraint to check valid dimensions on one side.

conv2dBatchIO Source #

Arguments

:: SpatialConvolutionC f h w kH kW dH dW pH pW oH oW 
=> All KnownDim '[f, o, b, (kW * kH) * f, oH * oW] 
=> Step2d '(dH, dW)

step of the convolution in width and height dimensions.

-> Padding2d '(pH, pW)

zero padding to the input plane for width and height.

-> Double

learning rate

-> Conv2d f o '(kH, kW)

conv2d state

-> Tensor '[b, f, h, w]

input: f stands for "features" or "input plane")

-> IO (Tensor '[b, o, oH, oW], Tensor '[b, o, oH, oW] -> IO (Conv2d f o '(kH, kW), Tensor '[b, f, h, w])) 

Backprop convolution function with batching

conv2dBatch Source #

Arguments

:: Reifies s W 
=> SpatialConvolutionC f h w kH kW dH dW pH pW oH oW 
=> All KnownDim '[f, o, kH, kW, dH, dW, pH, pW, b] 
=> All KnownDim '[(kW * kH) * f, oH * oW] 
=> Step2d '(dH, dW)

step of the convolution in width and height dimensions. C-default is 1 for both.

-> Padding2d '(pH, pW)

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

-> Double

learning rate

-> BVar s (Conv2d f o '(kH, kW))

conv2d state

-> BVar s (Tensor '[b, f, h, w])

input: f stands for "features" or "input plane")

-> BVar s (Tensor '[b, o, oH, oW]) 

Backprop convolution function with batching

conv2dIO Source #

Arguments

:: SpatialConvolutionC f h w kH kW dH dW pH pW oH oW 
=> All KnownDim '[f, o, (kW * kH) * f, oH * oW] 
=> Step2d '(dH, dW)

step of the convolution in width and height dimensions.

-> Padding2d '(pH, pW)

zero padding to the input plane for width and height.

-> Double

learning rate

-> Conv2d f o '(kH, kW)

conv2d state

-> Tensor '[f, h, w]

input: f stands for "features" or "input plane")

-> IO (Tensor '[o, oH, oW], Tensor '[o, oH, oW] -> IO (Conv2d f o '(kH, kW), Tensor '[f, h, w])) 

Backprop convolution function with batching

conv2d Source #

Arguments

:: Reifies s W 
=> SpatialConvolutionC f h w kH kW dH dW pH pW oH oW 
=> All KnownDim '[f, o, kH, kW, dH, dW, pH, pW] 
=> All KnownDim '[(kW * kH) * f, oH * oW] 
=> Step2d '(dH, dW)

step of the convolution in width and height dimensions. C-default is 1 for both.

-> Padding2d '(pH, pW)

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

-> Double

learning rate

-> BVar s (Conv2d f o '(kH, kW))

conv2d state

-> BVar s (Tensor '[f, h, w])

input: f stands for "features" or "input plane")

-> BVar s (Tensor '[o, oH, oW]) 

Backprop convolution function

genericConv2dWithIO Source #

Arguments

:: All Dimensions '[din, dout, fgin, inBuff] 
=> All KnownDim '[f, o, kH, kW, dH, dW, pH, pW] 
=> Maybe (Tensor fgin)

grad input buffer

-> Maybe (Tensor inBuff)

columns buffer

-> Maybe (Tensor inBuff)

ones buffer

-> Maybe (Tensor dout) 
-> Maybe (Tensor din) 
-> Maybe (Conv2d f o '(kH, kW)) 
-> Step2d '(dH, dW)

step of the convolution in width and height dimensions.

-> Padding2d '(pH, pW)

zero padding to the input plane for width and height.

-> Double

learning rate

-> Conv2d f o '(kH, kW)

conv2d state

-> Tensor din

input: f stands for "features" or "input plane")

-> IO (Tensor dout, Tensor dout -> IO (Conv2d f o '(kH, kW), Tensor din))