experimenter-0.1.0.8: Perform scientific experiments stored in a DB, and generate reports.
Safe HaskellNone
LanguageHaskell2010

Experimenter.Eval.Type

Synopsis

Documentation

data Over a Source #

Over datatype to reduce data vectors.

Instances

Instances details
Eq (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

(==) :: Over a -> Over a -> Bool #

(/=) :: Over a -> Over a -> Bool #

Ord (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

compare :: Over a -> Over a -> Ordering #

(<) :: Over a -> Over a -> Bool #

(<=) :: Over a -> Over a -> Bool #

(>) :: Over a -> Over a -> Bool #

(>=) :: Over a -> Over a -> Bool #

max :: Over a -> Over a -> Over a #

min :: Over a -> Over a -> Over a #

Show (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

showsPrec :: Int -> Over a -> ShowS #

show :: Over a -> String #

showList :: [Over a] -> ShowS #

Generic (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep (Over a) :: Type -> Type #

Methods

from :: Over a -> Rep (Over a) x #

to :: Rep (Over a) x -> Over a #

Serialize (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

put :: Putter (Over a) #

get :: Get (Over a) #

NFData (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: Over a -> () #

type Rep (Over a) Source # 
Instance details

Defined in Experimenter.Eval.Type

type Rep (Over a) = D1 ('MetaData "Over" "Experimenter.Eval.Type" "experimenter-0.1.0.8-JmXKSiy6msa8YAuqhdPgpO" 'False) (C1 ('MetaCons "OverPeriods" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OverReplications" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverExperimentRepetitions" 'PrefixI 'False) (U1 :: Type -> Type)))

data StatsDef a Source #

Definition of statisics. Is used to define the desired output.

Constructors

Mean !(Over a) !(Of a) 
StdDev !(Over a) !(Of a) 
Sum !(Over a) !(Of a) 
Id !(Of a) 
Named !(StatsDef a) !ByteString 
Name !ByteString !(StatsDef a) 

Instances

Instances details
Eq (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

(==) :: StatsDef a -> StatsDef a -> Bool #

(/=) :: StatsDef a -> StatsDef a -> Bool #

Ord (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

compare :: StatsDef a -> StatsDef a -> Ordering #

(<) :: StatsDef a -> StatsDef a -> Bool #

(<=) :: StatsDef a -> StatsDef a -> Bool #

(>) :: StatsDef a -> StatsDef a -> Bool #

(>=) :: StatsDef a -> StatsDef a -> Bool #

max :: StatsDef a -> StatsDef a -> StatsDef a #

min :: StatsDef a -> StatsDef a -> StatsDef a #

Show (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

showsPrec :: Int -> StatsDef a -> ShowS #

show :: StatsDef a -> String #

showList :: [StatsDef a] -> ShowS #

Generic (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep (StatsDef a) :: Type -> Type #

Methods

from :: StatsDef a -> Rep (StatsDef a) x #

to :: Rep (StatsDef a) x -> StatsDef a #

Serialize (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

put :: Putter (StatsDef a) #

get :: Get (StatsDef a) #

NFData (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: StatsDef a -> () #

type Rep (StatsDef a) Source # 
Instance details

Defined in Experimenter.Eval.Type

type Rep (StatsDef a) = D1 ('MetaData "StatsDef" "Experimenter.Eval.Type" "experimenter-0.1.0.8-JmXKSiy6msa8YAuqhdPgpO" 'False) ((C1 ('MetaCons "Mean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Over a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: (C1 ('MetaCons "StdDev" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Over a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: C1 ('MetaCons "Sum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Over a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))))) :+: (C1 ('MetaCons "Id" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: (C1 ('MetaCons "Named" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StatsDef a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StatsDef a))))))

data Of a Source #

Constructors

Of !ByteString 
Stats !(StatsDef a) 
Div !(Of a) !(Of a) 
Add !(Of a) !(Of a) 
Sub !(Of a) !(Of a) 
Mult !(Of a) !(Of a) 
Last !(Of a) 
First !(Of a) 
EveryXthElem !Int !(Of a) 
Length !(Of a) 

Instances

Instances details
Eq (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

(==) :: Of a -> Of a -> Bool #

(/=) :: Of a -> Of a -> Bool #

Ord (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

compare :: Of a -> Of a -> Ordering #

(<) :: Of a -> Of a -> Bool #

(<=) :: Of a -> Of a -> Bool #

(>) :: Of a -> Of a -> Bool #

(>=) :: Of a -> Of a -> Bool #

max :: Of a -> Of a -> Of a #

min :: Of a -> Of a -> Of a #

Show (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

showsPrec :: Int -> Of a -> ShowS #

show :: Of a -> String #

showList :: [Of a] -> ShowS #

Generic (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep (Of a) :: Type -> Type #

Methods

from :: Of a -> Rep (Of a) x #

to :: Rep (Of a) x -> Of a #

Serialize (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

put :: Putter (Of a) #

get :: Get (Of a) #

NFData (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: Of a -> () #

type Rep (Of a) Source # 
Instance details

Defined in Experimenter.Eval.Type

type Rep (Of a) = D1 ('MetaData "Of" "Experimenter.Eval.Type" "experimenter-0.1.0.8-JmXKSiy6msa8YAuqhdPgpO" 'False) (((C1 ('MetaCons "Of" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Stats" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StatsDef a)))) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: (C1 ('MetaCons "Add" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: C1 ('MetaCons "Sub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)))))) :+: ((C1 ('MetaCons "Mult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: C1 ('MetaCons "Last" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)))) :+: (C1 ('MetaCons "First" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: (C1 ('MetaCons "EveryXthElem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a))) :+: C1 ('MetaCons "Length" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Of a)))))))

sum :: Over a -> Of a -> Of a Source #

stdDev :: Over a -> Of a -> Of a Source #

mean :: Over a -> Of a -> Of a Source #

example :: StatsDef a Source #

Simple examples on how to use the types

data Unit Source #

Datatypes for the evaluation result.

Instances

Instances details
Eq Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

(==) :: Unit -> Unit -> Bool #

(/=) :: Unit -> Unit -> Bool #

Ord Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Read Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Show Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

Generic Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep Unit :: Type -> Type #

Methods

from :: Unit -> Rep Unit x #

to :: Rep Unit x -> Unit #

Serialize Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

put :: Putter Unit #

get :: Get Unit #

NFData Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: Unit -> () #

type Rep Unit Source # 
Instance details

Defined in Experimenter.Eval.Type

type Rep Unit = D1 ('MetaData "Unit" "Experimenter.Eval.Type" "experimenter-0.1.0.8-JmXKSiy6msa8YAuqhdPgpO" 'False) ((C1 ('MetaCons "UnitPeriods" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnitReplications" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnitExperimentRepetition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnitScalar" 'PrefixI 'False) (U1 :: Type -> Type)))

data EvalResults a Source #

Constructors

EvalVector 

Fields

EvalValue 

Fields

EvalReducedValue 

Fields

Instances

Instances details
Show (EvalResults a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Generic (EvalResults a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep (EvalResults a) :: Type -> Type #

Methods

from :: EvalResults a -> Rep (EvalResults a) x #

to :: Rep (EvalResults a) x -> EvalResults a #

Serialize (EvalResults a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

put :: Putter (EvalResults a) #

get :: Get (EvalResults a) #

NFData (EvalResults a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: EvalResults a -> () #

type Rep (EvalResults a) Source # 
Instance details

Defined in Experimenter.Eval.Type

evalType :: forall a. Lens' (EvalResults a) (StatsDef a) Source #

data ExperimentEval a Source #

Instances

Instances details
Show (ExperimentEval a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Generic (ExperimentEval a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep (ExperimentEval a) :: Type -> Type #

ExperimentDef a => NFData (ExperimentEval a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: ExperimentEval a -> () #

type Rep (ExperimentEval a) Source # 
Instance details

Defined in Experimenter.Eval.Type

type Rep (ExperimentEval a) = D1 ('MetaData "ExperimentEval" "Experimenter.Eval.Type" "experimenter-0.1.0.8-JmXKSiy6msa8YAuqhdPgpO" 'False) (C1 ('MetaCons "ExperimentEval" 'PrefixI 'True) (S1 ('MetaSel ('Just "_evalExperimentNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "_evalExperimentResults") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Availability IO (EvalResults a)]) :*: S1 ('MetaSel ('Just "_evalExperiment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Experiment a)))))

data Evals a Source #

Constructors

Evals 

Instances

Instances details
Generic (Evals a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Associated Types

type Rep (Evals a) :: Type -> Type #

Methods

from :: Evals a -> Rep (Evals a) x #

to :: Rep (Evals a) x -> Evals a #

ExperimentDef a => NFData (Evals a) Source # 
Instance details

Defined in Experimenter.Eval.Type

Methods

rnf :: Evals a -> () #

type Rep (Evals a) Source # 
Instance details

Defined in Experimenter.Eval.Type

type Rep (Evals a) = D1 ('MetaData "Evals" "Experimenter.Eval.Type" "experimenter-0.1.0.8-JmXKSiy6msa8YAuqhdPgpO" 'False) (C1 ('MetaCons "Evals" 'PrefixI 'True) (S1 ('MetaSel ('Just "_evalsExperiments") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Experiments a)) :*: S1 ('MetaSel ('Just "_evalsResults") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExperimentEval a])))

getEvalType :: (Over a -> Of a -> StatsDef a) -> EvalResults a -> StatsDef a Source #

demoteUnit :: Unit -> Maybe Unit Source #

Demotes the unit by 1 degree. Thus this calculates the unit of a vector over which it was reduced.