Copyright | (c) NoviSci Inc 2020 |
---|---|
License | BSD3 |
Maintainer | bsaul@novisci.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data FeatureData d
- data FeatureProblemFlag
- data KnownSymbol name => Feature name d
- type F n a = Feature n a
- featureDataL :: FeatureProblemFlag -> FeatureData d
- featureDataR :: d -> FeatureData d
- missingBecause :: FeatureProblemFlag -> FeatureData d
- makeFeature :: forall name d. KnownSymbol name => FeatureData d -> Feature name d
- getFeatureData :: FeatureData d -> Either FeatureProblemFlag d
- getFData :: Feature name d -> FeatureData d
- getData :: Feature n d -> Either FeatureProblemFlag d
- data Definition d where
- 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
- define :: inputs -> Definition def
- class DefineA inputs def | def -> inputs where
- defineA :: inputs -> Definition def
- type Def d = Definition d
- eval :: Definition d -> d
- class KnownSymbol name => HasAttributes name d | name -> d where
- getAttributes :: forall name. Attributes
- data Attributes = MkAttributes {}
- data Role
- data Purpose = MkPurpose {}
- emptyAttributes :: Attributes
- basicAttributes :: Text -> Text -> [Role] -> [Text] -> Attributes
- emptyPurpose :: Purpose
- setAttributes :: Attributes -> String -> Name -> Q [Dec]
- setAttributesEmpty :: String -> Name -> Q [Dec]
- setManyAttributes :: [(String, Name, Attributes)] -> Q [Dec]
- data Featureable = 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
- getFeatureableAttrs :: Featureable -> Attributes
- data Featureset
- newtype FeaturesetList = MkFeaturesetList (NonEmpty Featureset)
- featureset :: NonEmpty Featureable -> Featureset
- getFeatureset :: Featureset -> NonEmpty Featureable
- getFeaturesetAttrs :: Featureset -> NonEmpty Attributes
- getFeaturesetList :: FeaturesetList -> NonEmpty Featureset
- tpose :: FeaturesetList -> FeaturesetList
- allEqFeatureableData :: Featureset -> Featureset -> Bool
- class ToJSON a => ShapeOutput a where
- dataOnly :: a -> OutputShape b
- nameOnly :: a -> OutputShape b
- attrOnly :: a -> OutputShape b
- nameData :: a -> OutputShape b
- nameAttr :: a -> OutputShape b
- data OutputShape d
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
of
an Left
, while the data Either
d
is contained in the
's Either
.Right
To construct a successful value, use
. A missing value can be
constructed with featureDataR
or its synonym featureDataL
.missingBecause
Instances
Foldable FeatureData Source # | |
Defined in Features.Core 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 # | |
Defined in Features.Core 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 # | |
Defined in Features.Core 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 (
Note that
|
Defined in Features.Core fmap :: (a -> b) -> FeatureData a -> FeatureData b # (<$) :: a -> FeatureData b -> FeatureData a # | |
Monad FeatureData Source # | |
Defined in Features.Core (>>=) :: FeatureData a -> (a -> FeatureData b) -> FeatureData b # (>>) :: FeatureData a -> FeatureData b -> FeatureData b # return :: a -> FeatureData a # | |
ToJSON d => ToJSON (FeatureData d) | |
Defined in Features.Output toJSON :: FeatureData d -> Value toEncoding :: FeatureData d -> Encoding toJSONList :: [FeatureData d] -> Value toEncodingList :: [FeatureData d] -> Encoding | |
Generic (FeatureData d) Source # | |
Defined in Features.Core type Rep (FeatureData d) :: Type -> Type # from :: FeatureData d -> Rep (FeatureData d) x # to :: Rep (FeatureData d) x -> FeatureData d # | |
Show d => Show (FeatureData d) Source # | |
Defined in Features.Core showsPrec :: Int -> FeatureData d -> ShowS # show :: FeatureData d -> String # showList :: [FeatureData d] -> ShowS # | |
Eq d => Eq (FeatureData d) Source # | |
Defined in Features.Core (==) :: FeatureData d -> FeatureData d -> Bool # (/=) :: FeatureData d -> FeatureData d -> Bool # | |
type Rep (FeatureData d) Source # | |
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
value may be missing. Can be used to
indicate the reason that a FeatureData
's data was unable to be derived or does
not need to be derived.Feature
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
data KnownSymbol name => Feature name d Source #
The
is an abstraction for Feature
name
d d
ata, where the name
is a
*type*. Essentially, it is a container for
that assigns a FeatureData
name
to the data.
Except when using
to lift data into a pure
Feature
, Feature
s can only be
derived from other Feature
via a
.Definition
Instances
Define a (Feature n0 a) Source # | |
Defined in Features.Core define :: a -> Definition (Feature n0 a) Source # | |
Foldable (Feature name) Source # | |
Defined in Features.Core 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 # | |
Traversable (Feature name) Source # | |
Defined in Features.Core | |
Applicative (Feature name) Source # | |
Defined in Features.Core | |
Functor (Feature name) Source # | |
Monad (Feature name) Source # | |
(Typeable d, KnownSymbol n, ToJSON d, HasAttributes n d) => ToJSON (Feature n d) | |
Defined in Features.Output 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 # | |
Eq d => Eq (Feature name d) Source # | |
(KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => ShapeOutput (Feature n d) Source # | |
Defined in Features.Output dataOnly :: Feature n d -> OutputShape b Source # nameOnly :: Feature n d -> OutputShape b Source # attrOnly :: Feature n d -> OutputShape b Source # nameData :: Feature n d -> OutputShape b Source # nameAttr :: Feature n d -> OutputShape b Source # | |
Define (b -> a) (Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
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 # | |
DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
DefineA (d -> c -> b -> Feature n0 a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
DefineA (e -> d -> c -> b -> Feature n0 a) (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 # | |
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
is an instance of
FeatureData
, Applicative
is also a synonym of for pure
.featureDataR
>>>
featureDataR "aString"
MkFeatureData (Right "aString")>>>
featureDataR (1 :: P.Int)
MkFeatureData (Right 1)
>>>
featureDataR ("aString", (1 :: P.Int))
MkFeatureData (Right ("aString",1))
missingBecause :: FeatureProblemFlag -> FeatureData d Source #
A synonym for featureDataL
.
makeFeature :: forall name d. KnownSymbol name => FeatureData d -> Feature name d Source #
A utility for constructing a
from Feature
.
Since FeatureData
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"}
getFeatureData :: FeatureData d -> Either FeatureProblemFlag d Source #
Unwrap FeatureData.
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)
content of a FeatureData
.Feature
Feature Definitions
data Definition d where Source #
A Definition
can be thought of as a lifted function. Specifically, the
function takes an arbitrary function (currently up to three arguments)
and returns a define
Defintion
where the arguments have been lifted to a new domain.
For example, here we take f
and lift to to a function of Feature
s.
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
for evaluating eval
Defintions
.
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
s via
Definition
(define
). The defineA
function takes a single function input
and returns a lifted function. For example,define
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
function is similar, except that the return type of the input
function is already lifted. In the example below, an input of defineA
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
define :: inputs -> Definition def Source #
Instances
Define a (Feature n0 a) Source # | |
Defined in Features.Core define :: a -> Definition (Feature n0 a) Source # | |
Define (b -> a) (Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
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 # | |
class DefineA inputs def | def -> inputs where Source #
See
.Define
defineA :: inputs -> Definition def Source #
Instances
DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
DefineA (d -> c -> b -> Feature n0 a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Core | |
DefineA (e -> d -> c -> b -> Feature n0 a) (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 # | |
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 d
ata.
The type of d
ata 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
Nothing
getAttributes :: forall name. Attributes Source #
Instances
HasAttributes "dummy" Bool Source # | |
Defined in Tests.Features.Output getAttributes :: forall name1. Attributes Source # | |
HasAttributes "dummy2" Bool Source # | |
Defined in Tests.Features.Output 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.
MkAttributes | |
|
Instances
A type to identify a feature's (i.e. variable's) role in a research study.
In a
, multiple roles can be specified.Purpose
Instances
ToJSON Role | |
Defined in Features.Output | |
Generic Role Source # | |
Show Role Source # | |
Eq Role Source # | |
Ord Role Source # | |
Lift Role Source # | |
type Rep Role Source # | |
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)))) |
A type to identify a feature's purpose.
The
type enumerates many common purposes,
and the Role
getTags
field can be used for additional information.
Instances
ToJSON Purpose | |
Defined in Features.Output toEncoding :: Purpose -> Encoding toJSONList :: [Purpose] -> Value toEncodingList :: [Purpose] -> Encoding | |
Generic Purpose Source # | |
Show Purpose Source # | |
Eq Purpose Source # | |
Lift Purpose Source # | |
type Rep Purpose Source # | |
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.
Create attributes with just short label, long label, roles, and tags.
emptyPurpose :: Purpose Source #
An empty purpose value.
Template Haskell Utilities
:: Attributes | an |
-> String | The name the feature as a |
-> Name | The type of data.
Use double ticks as in |
-> Q [Dec] |
Creates a template haskell splice for
instance.
See HasAttributes
for an example.HasAttributes
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.
forall d.(Show d, ToJSON d, ShapeOutput d) => MkFeatureable d Attributes |
Instances
ToJSON Featureable Source # | |
Defined in Features.Featureable toJSON :: Featureable -> Value toEncoding :: Featureable -> Encoding toJSONList :: [Featureable] -> Value toEncodingList :: [Featureable] -> Encoding | |
Show Featureable Source # | |
Defined in Features.Featureable showsPrec :: Int -> Featureable -> ShowS # show :: Featureable -> String # showList :: [Featureable] -> ShowS # | |
ShapeOutput Featureable Source # | |
Defined in Features.Featureable dataOnly :: Featureable -> OutputShape b Source # nameOnly :: Featureable -> OutputShape b Source # attrOnly :: Featureable -> OutputShape b Source # nameData :: Featureable -> OutputShape b Source # nameAttr :: Featureable -> OutputShape b Source # |
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
ToJSON Featureset Source # | |
Defined in Features.Featureset toJSON :: Featureset -> Value toEncoding :: Featureset -> Encoding toJSONList :: [Featureset] -> Value toEncodingList :: [Featureset] -> Encoding | |
Show Featureset Source # | |
Defined in Features.Featureset showsPrec :: Int -> Featureset -> ShowS # show :: Featureset -> String # showList :: [Featureset] -> ShowS # |
newtype FeaturesetList Source #
A newtype wrapper for a NonEmpty
Featureset
.
Instances
Show FeaturesetList Source # | |
Defined in Features.Featureset showsPrec :: Int -> FeaturesetList -> ShowS # show :: FeaturesetList -> String # showList :: [FeaturesetList] -> ShowS # |
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
.
dataOnly :: a -> OutputShape b Source #
nameOnly :: a -> OutputShape b Source #
attrOnly :: a -> OutputShape b Source #
nameData :: a -> OutputShape b Source #
nameAttr :: a -> OutputShape b Source #
Instances
ShapeOutput Featureable Source # | |
Defined in Features.Featureable dataOnly :: Featureable -> OutputShape b Source # nameOnly :: Featureable -> OutputShape b Source # attrOnly :: Featureable -> OutputShape b Source # nameData :: Featureable -> OutputShape b Source # nameAttr :: Featureable -> OutputShape b Source # | |
(KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => ShapeOutput (Feature n d) Source # | |
Defined in Features.Output dataOnly :: Feature n d -> OutputShape b Source # nameOnly :: Feature n d -> OutputShape b Source # attrOnly :: Feature n d -> OutputShape b Source # nameData :: Feature n d -> OutputShape b Source # nameAttr :: Feature n d -> OutputShape b Source # |
data OutputShape d Source #
A type used to determine the output shape of a Feature.
Instances
ToJSON (OutputShape a) Source # | |
Defined in Features.Output toJSON :: OutputShape a -> Value toEncoding :: OutputShape a -> Encoding toJSONList :: [OutputShape a] -> Value toEncodingList :: [OutputShape a] -> Encoding | |
Show (OutputShape a) Source # | |
Defined in Features.Output showsPrec :: Int -> OutputShape a -> ShowS # show :: OutputShape a -> String # showList :: [OutputShape a] -> ShowS # |