sgd-0.7.0.1: Stochastic gradient descent

Safe HaskellNone
LanguageHaskell98

Numeric.SGD.ParamSet

Contents

Description

Provides the class ParamSet which is used to represent the set of parameters of a particular model. The goal of SGD is then to find the parameter values which minimize a given objective function.

Synopsis

Class

class ParamSet a where Source #

Class of types that can be treated as parameter sets. It provides basic element-wise operations (addition, multiplication, mapping) which are required to perform stochastic gradient descent. Many of the operations (add, mul, sub, div, etc.) have the same interpretation and follow the same laws (e.g. associativity) as the corresponding operations in Num and Fractional.

zero takes a parameter set as argument and "zero out"'s all its elements (as in the backprop library). This allows instances for Maybe, Map, etc., where the structure of the parameter set is dynamic. This leads to the following property:

add (zero x) x = x

However, zero does not have to obey (add (zero x) y = y).

A ParamSet can be also seen as a (structured) vector, hence pmap and norm_2. The latter is not strictly necessary to perform SGD, but it is useful to control the training process.

pmap should obey the following law:

pmap id x = x

If you leave the body of an instance declaration blank, GHC Generics will be used to derive instances if the type has a single constructor and each field is an instance of ParamSet.

Minimal complete definition

Nothing

Methods

pmap :: (Double -> Double) -> a -> a Source #

Element-wise mapping

zero :: a -> a Source #

Zero-out all elements

add :: a -> a -> a Source #

Element-wise addition

sub :: a -> a -> a Source #

Elementi-wise substruction

mul :: a -> a -> a Source #

Element-wise multiplication

div :: a -> a -> a Source #

Element-wise division

norm_2 :: a -> Double Source #

L2 norm

pmap :: (Generic a, GPMap (Rep a)) => (Double -> Double) -> a -> a Source #

Element-wise mapping

add :: (Generic a, GAdd (Rep a)) => a -> a -> a Source #

Element-wise addition

sub :: (Generic a, GSub (Rep a)) => a -> a -> a Source #

Elementi-wise substruction

mul :: (Generic a, GMul (Rep a)) => a -> a -> a Source #

Element-wise multiplication

div :: (Generic a, GDiv (Rep a)) => a -> a -> a Source #

Element-wise division

norm_2 :: (Generic a, GNorm2 (Rep a)) => a -> Double Source #

L2 norm

Instances
ParamSet Double Source # 
Instance details

Defined in Numeric.SGD.ParamSet

ParamSet a => ParamSet (Maybe a) Source #

Nothing represents a deactivated parameter set component. If Nothing is given as an argument to one of the ParamSet operations, the result is Nothing as well.

This differs from the corresponding instance in the backprop library, where Nothing is equivalent to `Just 0`. However, the implementation below seems to correspond adequately enough to the notion that a particular component is either active or not in both the parameter set and the gradient, hence it doesn't make sense to combine Just with Nothing.

Instance details

Defined in Numeric.SGD.ParamSet

Methods

pmap :: (Double -> Double) -> Maybe a -> Maybe a Source #

zero :: Maybe a -> Maybe a Source #

add :: Maybe a -> Maybe a -> Maybe a Source #

sub :: Maybe a -> Maybe a -> Maybe a Source #

mul :: Maybe a -> Maybe a -> Maybe a Source #

div :: Maybe a -> Maybe a -> Maybe a Source #

norm_2 :: Maybe a -> Double Source #

KnownNat n => ParamSet (R n) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

pmap :: (Double -> Double) -> R n -> R n Source #

zero :: R n -> R n Source #

add :: R n -> R n -> R n Source #

sub :: R n -> R n -> R n Source #

mul :: R n -> R n -> R n Source #

div :: R n -> R n -> R n Source #

norm_2 :: R n -> Double Source #

(Ord k, ParamSet a) => ParamSet (Map k a) Source #

A map with different parameter sets (of the same type) assigned to the individual keys.

When combining two maps with different sets of keys, only their intersection is preserved.

Instance details

Defined in Numeric.SGD.ParamSet

Methods

pmap :: (Double -> Double) -> Map k a -> Map k a Source #

zero :: Map k a -> Map k a Source #

add :: Map k a -> Map k a -> Map k a Source #

sub :: Map k a -> Map k a -> Map k a Source #

mul :: Map k a -> Map k a -> Map k a Source #

div :: Map k a -> Map k a -> Map k a Source #

norm_2 :: Map k a -> Double Source #

(KnownNat n, KnownNat m) => ParamSet (L n m) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

pmap :: (Double -> Double) -> L n m -> L n m Source #

zero :: L n m -> L n m Source #

add :: L n m -> L n m -> L n m Source #

sub :: L n m -> L n m -> L n m Source #

mul :: L n m -> L n m -> L n m Source #

div :: L n m -> L n m -> L n m Source #

norm_2 :: L n m -> Double Source #

Generics

class GPMap f Source #

Helper class for automatically deriving pmap using GHC Generics.

Minimal complete definition

gpmap

Instances
GPMap (V1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gpmap :: (Double -> Double) -> V1 t -> V1 t

GPMap (U1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gpmap :: (Double -> Double) -> U1 t -> U1 t

ParamSet a => GPMap (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gpmap :: (Double -> Double) -> K1 i a t -> K1 i a t

(GPMap f, GPMap g) => GPMap (f :*: g) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gpmap :: (Double -> Double) -> (f :*: g) t -> (f :*: g) t

GPMap f => GPMap (M1 i c f) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gpmap :: (Double -> Double) -> M1 i c f t -> M1 i c f t

class GAdd f Source #

Helper class for automatically deriving add using GHC Generics.

Minimal complete definition

gadd

Instances
GAdd (V1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gadd :: V1 t -> V1 t -> V1 t

GAdd (U1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gadd :: U1 t -> U1 t -> U1 t

ParamSet a => GAdd (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gadd :: K1 i a t -> K1 i a t -> K1 i a t

(GAdd f, GAdd g) => GAdd (f :*: g) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gadd :: (f :*: g) t -> (f :*: g) t -> (f :*: g) t

GAdd f => GAdd (M1 i c f) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gadd :: M1 i c f t -> M1 i c f t -> M1 i c f t

class GSub f Source #

Helper class for automatically deriving sub using GHC Generics.

Minimal complete definition

gsub

Instances
GSub (V1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gsub :: V1 t -> V1 t -> V1 t

GSub (U1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gsub :: U1 t -> U1 t -> U1 t

ParamSet a => GSub (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gsub :: K1 i a t -> K1 i a t -> K1 i a t

(GSub f, GSub g) => GSub (f :*: g) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gsub :: (f :*: g) t -> (f :*: g) t -> (f :*: g) t

GSub f => GSub (M1 i c f) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gsub :: M1 i c f t -> M1 i c f t -> M1 i c f t

class GDiv f Source #

Helper class for automatically deriving div using GHC Generics.

Minimal complete definition

gdiv

Instances
GDiv (V1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gdiv :: V1 t -> V1 t -> V1 t

GDiv (U1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gdiv :: U1 t -> U1 t -> U1 t

ParamSet a => GDiv (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gdiv :: K1 i a t -> K1 i a t -> K1 i a t

(GDiv f, GDiv g) => GDiv (f :*: g) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gdiv :: (f :*: g) t -> (f :*: g) t -> (f :*: g) t

GDiv f => GDiv (M1 i c f) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gdiv :: M1 i c f t -> M1 i c f t -> M1 i c f t

class GMul f Source #

Helper class for automatically deriving mul using GHC Generics.

Minimal complete definition

gmul

Instances
GMul (V1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gmul :: V1 t -> V1 t -> V1 t

GMul (U1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gmul :: U1 t -> U1 t -> U1 t

ParamSet a => GMul (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gmul :: K1 i a t -> K1 i a t -> K1 i a t

(GMul f, GMul g) => GMul (f :*: g) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gmul :: (f :*: g) t -> (f :*: g) t -> (f :*: g) t

GMul f => GMul (M1 i c f) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gmul :: M1 i c f t -> M1 i c f t -> M1 i c f t

class GNorm2 f Source #

Helper class for automatically deriving norm_2 using GHC Generics.

Minimal complete definition

gnorm_2

Instances
GNorm2 (V1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gnorm_2 :: V1 t -> Double

GNorm2 (U1 :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gnorm_2 :: U1 t -> Double

ParamSet a => GNorm2 (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gnorm_2 :: K1 i a t -> Double

(GNorm2 f, GNorm2 g) => GNorm2 (f :*: g) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gnorm_2 :: (f :*: g) t -> Double

GNorm2 f => GNorm2 (M1 i c f) Source # 
Instance details

Defined in Numeric.SGD.ParamSet

Methods

gnorm_2 :: M1 i c f t -> Double