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

Hasklepias.Types.Feature

Contents

Description

 
Synopsis

Types

newtype Feature d Source #

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

Constructors

Feature 

Instances

Instances details
Functor Feature Source # 
Instance details

Defined in Hasklepias.Types.Feature

Methods

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

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

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

Defined in Hasklepias.Types.Feature

Methods

(==) :: Feature d -> Feature d -> Bool #

(/=) :: Feature d -> Feature d -> Bool #

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

Defined in Hasklepias.Types.Feature

Methods

showsPrec :: Int -> Feature d -> ShowS #

show :: Feature d -> String #

showList :: [Feature d] -> ShowS #

Generic (Feature d) Source # 
Instance details

Defined in Hasklepias.Types.Feature

Associated Types

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

Methods

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

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

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

Defined in Hasklepias.Types.Feature.Aeson

type Rep (Feature d) Source # 
Instance details

Defined in Hasklepias.Types.Feature

type Rep (Feature d) = D1 ('MetaData "Feature" "Hasklepias.Types.Feature" "hasklepias-0.4.3-6vKfYAsEvQiGredrPyh3Vx" 'True) (C1 ('MetaCons "Feature" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFeature") '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.4.3-6vKfYAsEvQiGredrPyh3Vx" '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 String)) :+: C1 ('MetaCons "Unknown" 'PrefixI 'False) (U1 :: Type -> Type)))

data FeatureDefinition e a d Source #

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

Constructors

EF (Events a -> Feature d) 
FEF (Feature e -> Events a -> Feature d) 

applyEF :: FeatureDefinition e a d -> Events a -> Feature d Source #

Extract an EF FeatureDefinition.

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 feature 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 

defineFEF2 Source #

Arguments

:: Intervallic Interval a 
=> MissingReason

The reason if the input Feature is a Left.

-> (e -> Events a -> Feature 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 

applyFEF :: FeatureDefinition e a d -> Feature e -> Events a -> Feature d Source #

Extract a FEF FeatureDefinition

featureR :: d -> Feature d Source #

Create the Right side of a Feature.

featureL :: MissingReason -> Feature d Source #

Create the Left side of a Feature.