Safe Haskell | None |
---|---|
Language | Haskell98 |
Numeric.SGD.ParamSet
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-out all elements
Element-wise addition
Elementi-wise substruction
Element-wise multiplication
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 # | |
Defined in Numeric.SGD.ParamSet | |
ParamSet a => ParamSet (Maybe a) Source # |
This differs from the corresponding instance in the backprop library, where
|
Defined in Numeric.SGD.ParamSet | |
KnownNat n => ParamSet (R n) 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. |
Defined in Numeric.SGD.ParamSet | |
(KnownNat n, KnownNat m) => ParamSet (L n m) Source # | |
Defined in Numeric.SGD.ParamSet |