hasklepias-0.7.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 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

MkFeatureSpec 

data Show b => Feature b d Source #

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

Constructors

MkFeature 

Fields

Instances

Instances details
Show b => Functor (Feature b) Source # 
Instance details

Defined in Hasklepias.Types.Feature

Methods

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

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

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

Defined in Hasklepias.Types.Feature

Methods

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

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

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

Defined in Hasklepias.Types.Feature

Methods

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

show :: Feature d b -> String #

showList :: [Feature d b] -> ShowS #

(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
Monad FeatureData Source # 
Instance details

Defined in Hasklepias.Types.Feature

Methods

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

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

return :: a -> FeatureData a #

Functor FeatureData Source # 
Instance details

Defined in Hasklepias.Types.Feature

Methods

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

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

Applicative FeatureData Source # 
Instance details

Defined in Hasklepias.Types.Feature

Methods

pure :: a -> FeatureData a #

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

liftA2 :: (a -> b -> c) -> FeatureData a -> FeatureData b -> FeatureData c #

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

(<*) :: FeatureData 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.7.0-F91SPt9e5i9JpvYNTsnmsC" 'True) (C1 ('MetaCons "MkFeatureData" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFeatureData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either MissingReason d))))

data MissingReason Source #

FeatureData 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.7.0-F91SPt9e5i9JpvYNTsnmsC" '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 d Source #

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

Constructors

FD0 (e -> FeatureData d) 
FD1 (FeatureData e -> FeatureData d) 
FD2 (FeatureData f -> FeatureData e -> FeatureData d) 

makeFeatureSpec :: Show b => Text -> b -> FeatureDefinition f e d -> FeatureSpec b f e d Source #

TODO

featureDataR :: d -> FeatureData d Source #

Create the Right side of FeatureData.

define1 :: (e -> d) -> FeatureDefinition * e d Source #

define2 :: (f -> e -> d) -> FeatureDefinition f e d Source #

define2d :: (f -> e -> FeatureData d) -> FeatureDefinition f e d Source #

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

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

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