Copyright | (c) Lars Brünjes, 2016 |
---|---|
License | MIT |
Maintainer | brunjlar@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
This modules provides utilities for data normalization.
- encode1ofN :: (Enum a, Num b, KnownNat n) => a -> Vector n b
- decode1ofN :: (Enum a, Num b, Ord b, Foldable f) => f b -> a
- encodeEquiDist :: forall a b n. (Enum a, Floating b, KnownNat n) => a -> Vector n b
- decodeEquiDist :: forall a b n. (Enum a, Ord b, Floating b, KnownNat n) => Vector n b -> a
- crossEntropyError :: (Enum a, KnownNat n) => a -> Diff (Vector n) Identity
- white :: (Applicative f, Traversable t, Eq a, Floating a) => t (f a) -> f a -> f a
- whiten :: (Applicative f, Traversable t) => Model f g a b c -> t b -> Model f g a b c
- type Classifier f n b c = StdModel f (Vector n) b c
- mkStdClassifier :: (Functor f, KnownNat n, Enum c) => Component f (Vector n) -> (b -> f Double) -> Classifier f n b c
Documentation
encode1ofN :: (Enum a, Num b, KnownNat n) => a -> Vector n b Source #
Provides "1 of n
" encoding for enumerable types.
>>>
:set -XDataKinds
>>>
encode1ofN LT :: Vector 3 Int
[1,0,0]
>>>
encode1ofN EQ :: Vector 3 Int
[0,1,0]
>>>
encode1ofN GT :: Vector 3 Int
[0,0,1]
decode1ofN :: (Enum a, Num b, Ord b, Foldable f) => f b -> a Source #
Provides "1 of n
" decoding for enumerable types.
>>>
decode1ofN [0.9, 0.3, 0.1 :: Double] :: Ordering
LT
>>>
decode1ofN [0.7, 0.8, 0.6 :: Double] :: Ordering
EQ
>>>
decode1ofN [0.2, 0.3, 0.8 :: Double] :: Ordering
GT
encodeEquiDist :: forall a b n. (Enum a, Floating b, KnownNat n) => a -> Vector n b Source #
Provides equidistant encoding for enumerable types.
>>>
:set -XDataKinds
>>>
encodeEquiDist LT :: Vector 2 Float
[1.0,0.0]
>>>
encodeEquiDist EQ :: Vector 2 Float
[-0.5,-0.86602545]
>>>
encodeEquiDist GT :: Vector 2 Float
[-0.5,0.86602545]
decodeEquiDist :: forall a b n. (Enum a, Ord b, Floating b, KnownNat n) => Vector n b -> a Source #
Provides equidistant decoding for enumerable types.
>>>
:set -XDataKinds
>>>
let u = fromJust (fromList [0.9, 0.2]) :: Vector 2 Double
>>>
decodeEquiDist u :: Ordering
LT
>>>
:set -XDataKinds
>>>
let v = fromJust (fromList [-0.4, -0.5]) :: Vector 2 Double
>>>
decodeEquiDist v :: Ordering
EQ
>>>
:set -XDataKinds
>>>
let w = fromJust (fromList [0.1, 0.8]) :: Vector 2 Double
>>>
decodeEquiDist w :: Ordering
GT
crossEntropyError :: (Enum a, KnownNat n) => a -> Diff (Vector n) Identity Source #
Computes the cross entropy error (assuming "1 of n" encoding).
>>>
runDiff (crossEntropyError LT) (cons 0.8 (cons 0.1 (cons 0.1 nil))) :: Identity Double
Identity 0.2231435513142097
>>>
runDiff (crossEntropyError EQ) (cons 0.8 (cons 0.1 (cons 0.1 nil))) :: Identity Double
Identity 2.3025850929940455
white :: (Applicative f, Traversable t, Eq a, Floating a) => t (f a) -> f a -> f a Source #
Function white
takes a batch of values (of a specific shape)
and computes a normalization function which whitens values of that shape,
so that each component has zero mean and unit variance.
>>>
:set -XDataKinds
>>>
let xss = [cons 1 (cons 1 nil), cons 1 (cons 2 nil), cons 1 (cons 3 nil)] :: [Vector 2 Double]
>>>
let f = white xss
>>>
f <$> xss
[[0.0,-1.2247448713915887],[0.0,0.0],[0.0,1.2247448713915887]]
:: (Applicative f, Traversable t) | |
=> Model f g a b c | original model |
-> t b | batch of input data |
-> Model f g a b c |
Modifies a Model
by whitening the input before feeding it into the embedded component.
type Classifier f n b c = StdModel f (Vector n) b c Source #
A
is a Classifier
f n b cModel
that classifies items of type b
into categories of type c
,
using a component with input shape f
and output shape
.Vector
n
:: (Functor f, KnownNat n, Enum c) | |
=> Component f (Vector n) | the embedded component |
-> (b -> f Double) | converts input |
-> Classifier f n b c |
Makes a standard Classifier
which uses a softmax layer, "1 of n" encoding and the cross entropy error.