sgd-0.5.0.0: Stochastic gradient descent

Safe HaskellNone
LanguageHaskell98

Numeric.SGD.ParamSet

Synopsis

Documentation

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 #