HLearn-distributions-1.0.0.1: Distributions for use with the HLearn library

Safe HaskellNone

HLearn.Models.Distributions.Multivariate.Internal.TypeLens

Contents

Description

This module provides convenient TemplateHaskell functions for making type lens suitable for use with multivariate distributions.

Given a data type that looks like:

data Character = Character
    { _name      :: String
    , _species   :: String
    , _job       :: Job
    , _isGood    :: Maybe Bool
    , _age       :: Double -- in years
    , _height    :: Double -- in feet
    , _weight    :: Double -- in pounds
    }
    deriving (Read,Show,Eq,Ord)
 
data Job = Manager | Crew | Henchman | Other
    deriving (Read,Show,Eq,Ord)

when we run the command:

makeTypeLenses ''Character

We generate the following type lenses automatically:

data TH_name    = TH_name
data TH_species = TH_species
data TH_job     = TH_job
data TH_isGood  = TH_isGood
data TH_age     = TH_age
data TH_height  = TH_height
data TH_weight  = TH_weight

instance TypeLens TH_name where
    type instance TypeLensIndex TH_name = Nat1Box Zero
instance TypeLens TH_species where
    type instance TypeLensIndex TH_species = Nat1Box (Succ Zero)
instance TypeLens TH_job where
    type instance TypeLensIndex TH_job = Nat1Box (Succ (Succ Zero))
instance TypeLens TH_isGood where
    type instance TypeLensIndex TH_isGood = Nat1Box (Succ (Succ (Succ Zero)))
instance TypeLens TH_age where
    type instance TypeLensIndex TH_age = Nat1Box (Succ (Succ (Succ (Succ Zero))))
instance TypeLens TH_height where
    type instance TypeLensIndex TH_height = Nat1Box (Succ (Succ (Succ (Succ (Succ Zero)))))
instance TypeLens TH_weight where
    type instance TypeLensIndex TH_weight = Nat1Box (Succ (Succ (Succ (Succ (Succ (Succ Zero))))))
        
instance Trainable Character where
    type instance GetHList Character = HList '[String,String,Job,Maybe Bool, Double,Double,Double]
    getHList var = name var:::species var:::job var:::isGood var:::age var:::height var:::weight var:::HNil

instance MultivariateLabels Character where
    getLabels dist = ["TH_name","TH_species","TH_job","TH_isGood","TH_age","TH_height","TH_weight"]

Synopsis

Lens

class Trainable t whereSource

The Trainable class allows us to convert data types into an isomorphic HList. All of our multivariate distributions work on HLists, so they work on all instances of Trainable as well.

Associated Types

type GetHList t Source

Methods

getHList :: t -> GetHList tSource

Instances

Trainable (HList xs) => Trainable (HList (: * x xs)) 
Trainable (HList ([] *)) 

class TypeLens i Source

This specifies a type level natural number (i.e. Nat1) that indexes at the right location into our HList

Associated Types

type TypeLensIndex i Source

TemplateHaskell

makeTypeLenses :: Name -> Q [Dec]Source

constructs the type lens

nameTransform :: String -> StringSource

given the name of one of our records, transform it into the name of our type lens