hasklepias-0.5.0: Define features from events
Copyright(c) NoviSci Inc 2020
LicenseBSD3
Maintainerbsaul@novisci.com
Safe HaskellSafe
LanguageHaskell2010

Hasklepias.Types.Feature

Contents

Description

 
Synopsis

Types

data Show b => FeatureSpec b f e a d Source #

A FeatureSpec contains all the information needed to derive a Feature: * its name * its attributes * the function needed to derive a feature (i.e. the FeatureDefinition)

Constructors

FeatureSpec 

data Show b => Feature b d Source #

A Feature contains the following: * a name * its attributes * FeatureData

Constructors

Feature 

Fields

Instances

Instances details
(Show b, ToJSON b, ToJSON d) => ToJSON (Feature b d) Source # 
Instance details

Defined in Hasklepias.Types.Feature.Aeson

newtype FeatureData d Source #

FeatureData is Either MissingReason d, where d can be any type of data derivable from Events.

Instances

Instances details
Functor FeatureData Source # 
Instance details

Defined in Hasklepias.Types.Feature

Methods

fmap :: (a -> b) -> FeatureData a -> FeatureData b #

(<$) :: a -> FeatureData b -> FeatureData a #

Eq d => Eq (FeatureData d) Source # 
Instance details

Defined in Hasklepias.Types.Feature

Show d => Show (FeatureData d) Source # 
Instance details

Defined in Hasklepias.Types.Feature

Generic (FeatureData d) Source # 
Instance details

Defined in Hasklepias.Types.Feature

Associated Types

type Rep (FeatureData d) :: Type -> Type #

Methods

from :: FeatureData d -> Rep (FeatureData d) x #

to :: Rep (FeatureData d) x -> FeatureData d #

ToJSON d => ToJSON (FeatureData d) Source # 
Instance details

Defined in Hasklepias.Types.Feature.Aeson

type Rep (FeatureData d) Source # 
Instance details

Defined in Hasklepias.Types.Feature

type Rep (FeatureData d) = D1 ('MetaData "FeatureData" "Hasklepias.Types.Feature" "hasklepias-0.5.0-inplace" 'True) (C1 ('MetaCons "FeatureData" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFeatureData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either MissingReason d))))

data MissingReason Source #

A Feature may be missing for any number of reasons.

Instances

Instances details
Eq MissingReason Source # 
Instance details

Defined in Hasklepias.Types.Feature

Read MissingReason Source # 
Instance details

Defined in Hasklepias.Types.Feature

Show MissingReason Source # 
Instance details

Defined in Hasklepias.Types.Feature

Generic MissingReason Source # 
Instance details

Defined in Hasklepias.Types.Feature

Associated Types

type Rep MissingReason :: Type -> Type #

ToJSON MissingReason Source # 
Instance details

Defined in Hasklepias.Types.Feature.Aeson

type Rep MissingReason Source # 
Instance details

Defined in Hasklepias.Types.Feature

type Rep MissingReason = D1 ('MetaData "MissingReason" "Hasklepias.Types.Feature" "hasklepias-0.5.0-inplace" 'False) ((C1 ('MetaCons "InsufficientData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Excluded" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Other" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Unknown" 'PrefixI 'False) (U1 :: Type -> Type)))

data FeatureDefinition f e a d Source #

A type to hold common FeatureData definitions; i.e. functions that return features.

Constructors

EF (Events a -> FeatureData d) 
FEF (FeatureData e -> Events a -> FeatureData d) 
FFF (FeatureData f -> FeatureData e -> FeatureData d) 

defineEF Source #

Arguments

:: Intervallic Interval a 
=> MissingReason

The reason if f returns Nothing

-> (Events a -> Maybe c)

A function that maps events to an some intermediary Maybe type. In the case that this function returns Nothing, you get a Left FeatureData with the provided MissingReason. Otherwise, the Just result is passed to the next function for final transformation to the desired Feature type.

-> (c -> d)

A function that transforms the intermediary data to the desired type.

-> FeatureDefinition * e a d 

Define an EF FeatureDefinition

defineFEF Source #

Arguments

:: Intervallic Interval a 
=> MissingReason

The reason if the input Feature is a Left.

-> (e -> Events a -> d)

A function that tranforms the data of a Right input Feature and a collection of events into the desired type.

-> FeatureDefinition * e a d 

TODO

defineFEF2 Source #

Arguments

:: Intervallic Interval a 
=> MissingReason

The reason if the input Feature is a Left.

-> (e -> Events a -> FeatureData d)

A function that tranforms the data of a Right input Feature and a collection of events into the desired type.

-> FeatureDefinition * e a d 

TODO

defineFFF :: MissingReason -> MissingReason -> (f -> e -> d) -> FeatureDefinition f e * d Source #

TODO

applyEF :: FeatureDefinition * * a d -> Events a -> FeatureData d Source #

Extract an EF FeatureDefinition.

applyFEF :: FeatureDefinition * e a d -> FeatureData e -> Events a -> FeatureData d Source #

Extract a FEF FeatureDefinition

applyFFF :: FeatureDefinition f e * d -> FeatureData f -> FeatureData e -> FeatureData d Source #

Extract a FFF FeatureDefinition

featureR :: d -> FeatureData d Source #

Create the Right side of a Feature.

featureL :: MissingReason -> FeatureData d Source #

Create the Left side of a Feature.

evalEFFeature :: Show b => FeatureSpec b * * a d -> Events a -> Feature b d Source #

TODO

evalFEFFeature :: Show b => FeatureSpec b * e a d -> Feature b e -> Events a -> Feature b d Source #

TODO

evalFFFFeature :: Show b => FeatureSpec b f e * d -> Feature b f -> Feature b e -> Feature b d Source #

TODO