hasklepias-core-0.30.3: Domain-aware tools and types for constructing epidemiological cohorts
Copyright(c) NoviSci Inc 2020
LicenseBSD3
Maintainerbsaul@novisci.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Features

Description

 
Synopsis

Creating Features

Features and FeatureData

data FeatureData d Source #

The FeatureData type is a container for an (almost) arbitrary type d that can have a "failed" or "missing" state. The failure is represented by the Left of an Either, while the data d is contained in the Either's Right.

To construct a successful value, use featureDataR. A missing value can be constructed with featureDataL or its synonym missingBecause.

Instances

Instances details
Foldable FeatureData Source # 
Instance details

Defined in Features.Core

Methods

fold :: Monoid m => FeatureData m -> m #

foldMap :: Monoid m => (a -> m) -> FeatureData a -> m #

foldMap' :: Monoid m => (a -> m) -> FeatureData a -> m #

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

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

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

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

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

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

toList :: FeatureData a -> [a] #

null :: FeatureData a -> Bool #

length :: FeatureData a -> Int #

elem :: Eq a => a -> FeatureData a -> Bool #

maximum :: Ord a => FeatureData a -> a #

minimum :: Ord a => FeatureData a -> a #

sum :: Num a => FeatureData a -> a #

product :: Num a => FeatureData a -> a #

Traversable FeatureData Source # 
Instance details

Defined in Features.Core

Methods

traverse :: Applicative f => (a -> f b) -> FeatureData a -> f (FeatureData b) #

sequenceA :: Applicative f => FeatureData (f a) -> f (FeatureData a) #

mapM :: Monad m => (a -> m b) -> FeatureData a -> m (FeatureData b) #

sequence :: Monad m => FeatureData (m a) -> m (FeatureData a) #

Applicative FeatureData Source # 
Instance details

Defined in Features.Core

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 #

Functor FeatureData Source #

Transform (fmap) FeatureData of one type to another.

>>> x = featureDataR (1 :: P.Int)
>>> :type x
>>> :type ( fmap show x )
x :: FeatureData Int
( fmap show x ) :: FeatureData String

Note that Left values are carried along while the type changes:

>>> x = ( featureDataL InsufficientData ) :: FeatureData P.Int
>>> :type x
>>> x
>>> :type ( fmap show x )
>>> fmap show x
x :: FeatureData Int
MkFeatureData {getFeatureData = Left InsufficientData}
( fmap show x ) :: FeatureData String
MkFeatureData {getFeatureData = Left InsufficientData}
Instance details

Defined in Features.Core

Methods

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

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

Monad FeatureData Source # 
Instance details

Defined in Features.Core

Methods

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

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

return :: a -> FeatureData a #

ToJSON d => ToJSON (FeatureData d) 
Instance details

Defined in Features.Output

Methods

toJSON :: FeatureData d -> Value

toEncoding :: FeatureData d -> Encoding

toJSONList :: [FeatureData d] -> Value

toEncodingList :: [FeatureData d] -> Encoding

Generic (FeatureData d) Source # 
Instance details

Defined in Features.Core

Associated Types

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

Methods

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

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

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

Defined in Features.Core

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

Defined in Features.Core

type Rep (FeatureData d) Source # 
Instance details

Defined in Features.Core

type Rep (FeatureData d) = D1 ('MetaData "FeatureData" "Features.Core" "hasklepias-core-0.30.3-inplace" 'True) (C1 ('MetaCons "MkFeatureData" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFeatureData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either FeatureProblemFlag d))))

data FeatureProblemFlag Source #

Defines the reasons that a FeatureData value may be missing. Can be used to indicate the reason that a Feature's data was unable to be derived or does not need to be derived.

Constructors

InsufficientData

indicates there is insufficient data to define feature

InconsistentData Text

indicates an inconsistency in the data that should be flagged

CustomFlag Text

a means to indicate a custom problem in defining a feature

Instances

Instances details
ToJSON FeatureProblemFlag 
Instance details

Defined in Features.Output

Generic FeatureProblemFlag Source # 
Instance details

Defined in Features.Core

Associated Types

type Rep FeatureProblemFlag :: Type -> Type #

Show FeatureProblemFlag Source # 
Instance details

Defined in Features.Core

Eq FeatureProblemFlag Source # 
Instance details

Defined in Features.Core

type Rep FeatureProblemFlag Source # 
Instance details

Defined in Features.Core

type Rep FeatureProblemFlag = D1 ('MetaData "FeatureProblemFlag" "Features.Core" "hasklepias-core-0.30.3-inplace" 'False) (C1 ('MetaCons "InsufficientData" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InconsistentData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CustomFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data KnownSymbol name => Feature name d Source #

The Feature is an abstraction for named data, where the name is a *type*. Essentially, it is a container for FeatureData that assigns a name to the data.

Except when using pure to lift data into a Feature, Features can only be derived from other Feature via a Definition.

Instances

Instances details
Define a (Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: a -> Definition (Feature n0 a) Source #

Foldable (Feature name) Source # 
Instance details

Defined in Features.Core

Methods

fold :: Monoid m => Feature name m -> m #

foldMap :: Monoid m => (a -> m) -> Feature name a -> m #

foldMap' :: Monoid m => (a -> m) -> Feature name a -> m #

foldr :: (a -> b -> b) -> b -> Feature name a -> b #

foldr' :: (a -> b -> b) -> b -> Feature name a -> b #

foldl :: (b -> a -> b) -> b -> Feature name a -> b #

foldl' :: (b -> a -> b) -> b -> Feature name a -> b #

foldr1 :: (a -> a -> a) -> Feature name a -> a #

foldl1 :: (a -> a -> a) -> Feature name a -> a #

toList :: Feature name a -> [a] #

null :: Feature name a -> Bool #

length :: Feature name a -> Int #

elem :: Eq a => a -> Feature name a -> Bool #

maximum :: Ord a => Feature name a -> a #

minimum :: Ord a => Feature name a -> a #

sum :: Num a => Feature name a -> a #

product :: Num a => Feature name a -> a #

Traversable (Feature name) Source # 
Instance details

Defined in Features.Core

Methods

traverse :: Applicative f => (a -> f b) -> Feature name a -> f (Feature name b) #

sequenceA :: Applicative f => Feature name (f a) -> f (Feature name a) #

mapM :: Monad m => (a -> m b) -> Feature name a -> m (Feature name b) #

sequence :: Monad m => Feature name (m a) -> m (Feature name a) #

Applicative (Feature name) Source # 
Instance details

Defined in Features.Core

Methods

pure :: a -> Feature name a #

(<*>) :: Feature name (a -> b) -> Feature name a -> Feature name b #

liftA2 :: (a -> b -> c) -> Feature name a -> Feature name b -> Feature name c #

(*>) :: Feature name a -> Feature name b -> Feature name b #

(<*) :: Feature name a -> Feature name b -> Feature name a #

Functor (Feature name) Source # 
Instance details

Defined in Features.Core

Methods

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

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

Monad (Feature name) Source # 
Instance details

Defined in Features.Core

Methods

(>>=) :: Feature name a -> (a -> Feature name b) -> Feature name b #

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

return :: a -> Feature name a #

(Typeable d, KnownSymbol n, ToJSON d, HasAttributes n d) => ToJSON (Feature n d) 
Instance details

Defined in Features.Output

Methods

toJSON :: Feature n d -> Value

toEncoding :: Feature n d -> Encoding

toJSONList :: [Feature n d] -> Value

toEncodingList :: [Feature n d] -> Encoding

(KnownSymbol name, Show a) => Show (Feature name a) Source # 
Instance details

Defined in Features.Core

Methods

showsPrec :: Int -> Feature name a -> ShowS #

show :: Feature name a -> String #

showList :: [Feature name a] -> ShowS #

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

Defined in Features.Core

Methods

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

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

(KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => ShapeOutput (Feature n d) Source # 
Instance details

Defined in Features.Output

Define (b -> a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (b -> a) -> Definition (Feature n1 b -> Feature n0 a) Source #

Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (c -> b -> a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (d -> c -> b -> a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (e -> d -> c -> b -> a) -> Definition (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (f -> e -> d -> c -> b -> a) (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (f -> e -> d -> c -> b -> a) -> Definition (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (b -> Feature n0 a) -> Definition (Feature n1 b -> Feature n0 a) Source #

DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (c -> b -> Feature n0 a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (d -> c -> b -> Feature n0 a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (d -> c -> b -> Feature n0 a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (e -> d -> c -> b -> Feature n0 a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (e -> d -> c -> b -> Feature n0 a) -> Definition (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (f -> e -> d -> c -> b -> Feature n0 a) (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (f -> e -> d -> c -> b -> Feature n0 a) -> Definition (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

type F n a = Feature n a Source #

Type synonym for Feature.

featureDataL :: FeatureProblemFlag -> FeatureData d Source #

Creates a missing FeatureData.

>>> featureDataL (CustomFlag "no good reason") :: FeatureData P.Int
MkFeatureData (Left (CustomFlag "no good reason"))
>>> featureDataL (CustomFlag "no good reason") :: FeatureData Text
MkFeatureData (Left (CustomFlag "no good reason"))

featureDataR :: d -> FeatureData d Source #

Creates a non-missing FeatureData. Since FeatureData is an instance of Applicative, pure is also a synonym of for featureDataR.

>>> featureDataR "aString"
MkFeatureData (Right "aString")
>>> featureDataR (1 :: P.Int)
MkFeatureData (Right 1)
>>> featureDataR ("aString", (1 :: P.Int))
MkFeatureData (Right ("aString",1))

makeFeature :: forall name d. KnownSymbol name => FeatureData d -> Feature name d Source #

A utility for constructing a Feature from FeatureData. Since name is a type, you may need to annotate the type when using this function.

>>> makeFeature (pure "test") :: Feature "dummy" Text
"dummy": MkFeatureData {getFeatureData = Right "test"}

getFData :: Feature name d -> FeatureData d Source #

Gets the FeatureData from a Feature.

getData :: Feature n d -> Either FeatureProblemFlag d Source #

A utility for getting the (inner) FeatureData content of a Feature.

Feature Definitions

data Definition d where Source #

A Definition can be thought of as a lifted function. Specifically, the define function takes an arbitrary function (currently up to three arguments) and returns a Defintion where the arguments have been lifted to a new domain.

For example, here we take f and lift to to a function of Features.

f :: Int -> String -> Bool
f i s
  | 1 "yes" = True
  | otherwise = FALSE

myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool )
myFeature = define f

See eval for evaluating Defintions.

Constructors

Pure :: a -> Definition (F n0 a) 
D1 :: (b -> a) -> Definition (F n1 b -> F n0 a) 
D1A :: (b -> F n0 a) -> Definition (F n1 b -> F n0 a) 
D1C :: (a2 -> a1 -> a) -> Definition (F n1 b -> F n02 a2) -> Definition (F n1 b -> F n01 a1) -> Definition (F n1 b -> F n0 a) 
D2 :: (c -> b -> a) -> Definition (F n2 c -> F n1 b -> F n0 a) 
D2A :: (c -> b -> F n0 a) -> Definition (F n2 c -> F n1 b -> F n0 a) 
D2C :: (a2 -> a1 -> a) -> Definition (F n2 c -> F n1 b -> F n02 a2) -> Definition (F n2 c -> F n1 b -> F n01 a1) -> Definition (F n2 c -> F n1 b -> F n0 a) 
D3 :: (d -> c -> b -> a) -> Definition (F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D3A :: (d -> c -> b -> F n0 a) -> Definition (F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D3C :: (a2 -> a1 -> a) -> Definition (F n3 d -> F n2 c -> F n1 b -> F n02 a2) -> Definition (F n3 d -> F n2 c -> F n1 b -> F n01 a1) -> Definition (F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D4 :: (e -> d -> c -> b -> a) -> Definition (F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D4A :: (e -> d -> c -> b -> F n0 a) -> Definition (F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D4C :: (a2 -> a1 -> a) -> Definition (F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n02 a2) -> Definition (F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n01 a1) -> Definition (F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D5 :: (f -> e -> d -> c -> b -> a) -> Definition (F n5 f -> F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D5A :: (f -> e -> d -> c -> b -> F n0 a) -> Definition (F n5 f -> F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n0 a) 
D5C :: (a2 -> a1 -> a) -> Definition (F n5 f -> F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n02 a2) -> Definition (F n5 f -> F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n01 a1) -> Definition (F n5 f -> F n4 e -> F n3 d -> F n2 c -> F n1 b -> F n0 a) 

class Define inputs def | def -> inputs where Source #

Define (and 'DefineA) provide a means to create new Definitions via define (defineA). The define function takes a single function input and returns a lifted function. For example,

f :: Int -> String -> Bool
f i s
  | 1 "yes" = True
  | otherwise = FALSE

myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool )
myFeature = define f

The defineA function is similar, except that the return type of the input function is already lifted. In the example below, an input of Nothing is considered a missing state:

f :: Int -> Maybe String -> Feature C Bool
f i s
  | 1 (Just "yes")   = pure True
  | _ (Just _ )      = pure False -- False for any Int and any (Just String)
  | otherwise        = pure $ missingBecause InsufficientData -- missing if no string

myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool )
myFeature = defineA f

Methods

define :: inputs -> Definition def Source #

Instances

Instances details
Define a (Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: a -> Definition (Feature n0 a) Source #

Define (b -> a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (b -> a) -> Definition (Feature n1 b -> Feature n0 a) Source #

Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (c -> b -> a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (d -> c -> b -> a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (e -> d -> c -> b -> a) -> Definition (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (f -> e -> d -> c -> b -> a) (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

define :: (f -> e -> d -> c -> b -> a) -> Definition (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

class DefineA inputs def | def -> inputs where Source #

See Define.

Methods

defineA :: inputs -> Definition def Source #

Instances

Instances details
DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (b -> Feature n0 a) -> Definition (Feature n1 b -> Feature n0 a) Source #

DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (c -> b -> Feature n0 a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (d -> c -> b -> Feature n0 a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (d -> c -> b -> Feature n0 a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (e -> d -> c -> b -> Feature n0 a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (e -> d -> c -> b -> Feature n0 a) -> Definition (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (f -> e -> d -> c -> b -> Feature n0 a) (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Core

Methods

defineA :: (f -> e -> d -> c -> b -> Feature n0 a) -> Definition (Feature n5 f -> Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

type Def d = Definition d Source #

Type synonym for Definition.

eval :: Definition d -> d Source #

Evaluate a Definition. Note that (currently), the second argument of eval is a *tuple* of inputs. For example,

f :: Int -> String -> Bool
f i s
  | 1 "yes" = True
  | otherwise = FALSE

myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool )
myFeature = define f

a :: Feature A Int
a = pure 1

b :: Feature B String
b = pure "yes"

c = eval myFeature a b

Adding Attributes to Features

class KnownSymbol name => HasAttributes name d | name -> d where Source #

A typeclass providing a single method for attaching Attributes to a name and data. The type of data is determined by the name, by way of using a functional dependency.

The default method is emptyAttributes.

The setAttributes function creates a template Haskell splice, which generates a HasAttributes instance declaration. For example, instead of writing

  instance HasAttributes "foo" Bool where
    getAttributes = basicAttributes "lab" "long label" [Covariate] []

one can instead write

  setAttributes
    (basicAttributes "lab" "long label" [Covariate] [])
    "foo" ''Bool

The latter approach is useful for writing helper functions to generate Attributes.

   covariateAttrs label tag  =
       setAttributes (labeller label tag)
       where labeller = basicAttributes label label [Covariate] [tag]

   covariateAttrs "foo var" "a" "foo" ''Bool
   covariateAttrs "bar bar" "b" "bar" ''Int

Minimal complete definition

Nothing

Methods

getAttributes :: forall name. Attributes Source #

Instances

Instances details
HasAttributes "dummy" Bool Source # 
Instance details

Defined in Tests.Features.Output

Methods

getAttributes :: forall name1. Attributes Source #

HasAttributes "dummy2" Bool Source # 
Instance details

Defined in Tests.Features.Output

Methods

getAttributes :: forall name1. Attributes Source #

data Attributes Source #

A data type for holding attritbutes of features.

Attributes are not generally used with asclepias itself, and instead used to pass contextual information to downstream applications.

For example, the Attributes type directly maps to a [stype context](https:/docs.novisci.comstypereferencecontext.html).

See emptyAttributes and basicAttributes for convenience constructor functions.

Constructors

MkAttributes 

Fields

Instances

Instances details
ToJSON Attributes 
Instance details

Defined in Features.Output

Methods

toJSON :: Attributes -> Value

toEncoding :: Attributes -> Encoding

toJSONList :: [Attributes] -> Value

toEncodingList :: [Attributes] -> Encoding

Generic Attributes Source # 
Instance details

Defined in Features.Attributes

Associated Types

type Rep Attributes :: Type -> Type #

Show Attributes Source # 
Instance details

Defined in Features.Attributes

Eq Attributes Source # 
Instance details

Defined in Features.Attributes

Lift Attributes Source # 
Instance details

Defined in Features.Attributes

Methods

lift :: Quote m => Attributes -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Attributes -> Code m Attributes #

type Rep Attributes Source # 
Instance details

Defined in Features.Attributes

type Rep Attributes = D1 ('MetaData "Attributes" "Features.Attributes" "hasklepias-core-0.30.3-inplace" 'False) (C1 ('MetaCons "MkAttributes" 'PrefixI 'True) ((S1 ('MetaSel ('Just "getShortLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "getLongLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "getDerivation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "getPurpose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Purpose))))

data Role Source #

A type to identify a feature's (i.e. variable's) role in a research study. In a Purpose, multiple roles can be specified.

Instances

Instances details
ToJSON Role 
Instance details

Defined in Features.Output

Methods

toJSON :: Role -> Value

toEncoding :: Role -> Encoding

toJSONList :: [Role] -> Value

toEncodingList :: [Role] -> Encoding

Generic Role Source # 
Instance details

Defined in Features.Attributes

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Show Role Source # 
Instance details

Defined in Features.Attributes

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Eq Role Source # 
Instance details

Defined in Features.Attributes

Methods

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

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

Ord Role Source # 
Instance details

Defined in Features.Attributes

Methods

compare :: Role -> Role -> Ordering #

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

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

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Lift Role Source # 
Instance details

Defined in Features.Attributes

Methods

lift :: Quote m => Role -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Role -> Code m Role #

type Rep Role Source # 
Instance details

Defined in Features.Attributes

type Rep Role = D1 ('MetaData "Role" "Features.Attributes" "hasklepias-core-0.30.3-inplace" 'False) (((C1 ('MetaCons "Outcome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Censoring" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Covariate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exposure" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Competing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Weight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Intermediate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unspecified" 'PrefixI 'False) (U1 :: Type -> Type))))

data Purpose Source #

A type to identify a feature's purpose. The Role type enumerates many common purposes, and the getTags field can be used for additional information.

Constructors

MkPurpose 

Fields

Instances

Instances details
ToJSON Purpose 
Instance details

Defined in Features.Output

Methods

toJSON :: Purpose -> Value

toEncoding :: Purpose -> Encoding

toJSONList :: [Purpose] -> Value

toEncodingList :: [Purpose] -> Encoding

Generic Purpose Source # 
Instance details

Defined in Features.Attributes

Associated Types

type Rep Purpose :: Type -> Type #

Methods

from :: Purpose -> Rep Purpose x #

to :: Rep Purpose x -> Purpose #

Show Purpose Source # 
Instance details

Defined in Features.Attributes

Eq Purpose Source # 
Instance details

Defined in Features.Attributes

Methods

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

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

Lift Purpose Source # 
Instance details

Defined in Features.Attributes

Methods

lift :: Quote m => Purpose -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Purpose -> Code m Purpose #

type Rep Purpose Source # 
Instance details

Defined in Features.Attributes

type Rep Purpose = D1 ('MetaData "Purpose" "Features.Attributes" "hasklepias-core-0.30.3-inplace" 'False) (C1 ('MetaCons "MkPurpose" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRole") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role]) :*: S1 ('MetaSel ('Just "getTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

emptyAttributes :: Attributes Source #

An empty attributes value.

basicAttributes Source #

Arguments

:: Text

short label

-> Text

long label

-> [Role]

Purpose roles

-> [Text]

Purpose tags

-> Attributes 

Create attributes with just short label, long label, roles, and tags.

emptyPurpose :: Purpose Source #

An empty purpose value.

Template Haskell Utilities

setAttributes Source #

Arguments

:: Attributes

an Attributes value

-> String

The name the feature as a String. This refers to the KnownSymbol name in the HasAttributes class declaration.

-> Name

The type of data. Use double ticks as in ''Bool. This is template haskell's quotation syntax. See Name in template haskell documentation for other ways to create a Name.

-> Q [Dec] 

Creates a template haskell splice for HasAttributes instance. See HasAttributes for an example.

Usage requires the template haskell language extension.

setAttributesEmpty :: String -> Name -> Q [Dec] Source #

A convenience function for declaring a HasAttributes instance as emptyAttributes.

setManyAttributes :: [(String, Name, Attributes)] -> Q [Dec] Source #

A convenience function for declaring many HasAttributes instances given a list of inputs to setAttributes.

Exporting Features

data Featureable Source #

Existential type to hold features, which allows for Features to be put into a homogeneous list.

Constructors

forall d.(Show d, ToJSON d, ShapeOutput d) => MkFeatureable d Attributes 

packFeature :: forall n d. (KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => Feature n d -> Featureable Source #

Pack a feature into a Featurable.

getFeatureableAttrs :: Featureable -> Attributes Source #

Get the Attributes from a Featureable.

data Featureset Source #

A Featureset is a (non-empty) list of Featureable.

Instances

Instances details
ToJSON Featureset Source # 
Instance details

Defined in Features.Featureset

Methods

toJSON :: Featureset -> Value

toEncoding :: Featureset -> Encoding

toJSONList :: [Featureset] -> Value

toEncodingList :: [Featureset] -> Encoding

Show Featureset Source # 
Instance details

Defined in Features.Featureset

newtype FeaturesetList Source #

A newtype wrapper for a NonEmpty Featureset.

Instances

Instances details
Show FeaturesetList Source # 
Instance details

Defined in Features.Featureset

featureset :: NonEmpty Featureable -> Featureset Source #

Constructor of a Featureset.

getFeatureset :: Featureset -> NonEmpty Featureable Source #

Constructor of a Featureset.

getFeaturesetAttrs :: Featureset -> NonEmpty Attributes Source #

Gets a list of Attributes from a Featureset, one Attributes per Featureable.

getFeaturesetList :: FeaturesetList -> NonEmpty Featureset Source #

Constructor of a Featureset.

tpose :: FeaturesetList -> FeaturesetList Source #

Transpose a FeaturesetList

allEqFeatureableData :: Featureset -> Featureset -> Bool Source #

Compare two Featuresets via their ShapeOutput and ToJSON implementations. They cannot be compared directly because an existential type cannot be Eq. Comparing by JSON at the moment makes the most sense because that is the output format and thus how downstream applications will understand "equality". Still, this should be revisited.

class ToJSON a => ShapeOutput a where Source #

A class that provides methods for transforming some type to an OutputShape.

data OutputShape d Source #

A type used to determine the output shape of a Feature.

Instances

Instances details
ToJSON (OutputShape a) Source # 
Instance details

Defined in Features.Output

Methods

toJSON :: OutputShape a -> Value

toEncoding :: OutputShape a -> Encoding

toJSONList :: [OutputShape a] -> Value

toEncodingList :: [OutputShape a] -> Encoding

Show (OutputShape a) Source # 
Instance details

Defined in Features.Output