{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
module Features.Featureable (
Featureable(..)
, packFeature
, getFeatureableAttrs
) where
import Features.Compose ( Feature
, makeFeature
)
import Features.Output ( ShapeOutput(..), OutputShape )
import Features.Attributes ( HasAttributes(..), Attributes )
import GHC.TypeLits ( KnownSymbol )
import Data.Aeson ( ToJSON(toJSON) )
import Data.Typeable ( Typeable )
data Featureable = forall d . (Show d, ToJSON d, ShapeOutput d) => MkFeatureable d Attributes
packFeature ::
( KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) =>
Feature n d -> Featureable
packFeature :: Feature n d -> Featureable
packFeature Feature n d
x = Feature n d -> Attributes -> Featureable
forall d.
(Show d, ToJSON d, ShapeOutput d) =>
d -> Attributes -> Featureable
MkFeatureable Feature n d
x (Feature n d -> Attributes
forall (name :: Symbol) d (f :: Symbol -> * -> *).
HasAttributes name d =>
f name d -> Attributes
getAttributes Feature n d
x)
instance Show Featureable where
show :: Featureable -> String
show (MkFeatureable d
x Attributes
_ ) = d -> String
forall a. Show a => a -> String
show d
x
instance ToJSON Featureable where
toJSON :: Featureable -> Value
toJSON (MkFeatureable d
x Attributes
_ ) = d -> Value
forall a. ToJSON a => a -> Value
toJSON d
x
instance ShapeOutput Featureable where
dataOnly :: Featureable -> OutputShape b
dataOnly (MkFeatureable d
x Attributes
_ ) = d -> OutputShape b
forall a b. ShapeOutput a => a -> OutputShape b
dataOnly d
x
nameOnly :: Featureable -> OutputShape b
nameOnly (MkFeatureable d
x Attributes
_ ) = d -> OutputShape b
forall a b. ShapeOutput a => a -> OutputShape b
nameOnly d
x
attrOnly :: Featureable -> OutputShape b
attrOnly (MkFeatureable d
x Attributes
_ ) = d -> OutputShape b
forall a b. ShapeOutput a => a -> OutputShape b
attrOnly d
x
nameData :: Featureable -> OutputShape b
nameData (MkFeatureable d
x Attributes
_ ) = d -> OutputShape b
forall a b. ShapeOutput a => a -> OutputShape b
nameData d
x
nameAttr :: Featureable -> OutputShape b
nameAttr (MkFeatureable d
x Attributes
_ ) = d -> OutputShape b
forall a b. ShapeOutput a => a -> OutputShape b
nameAttr d
x
getFeatureableAttrs :: Featureable -> Attributes
getFeatureableAttrs :: Featureable -> Attributes
getFeatureableAttrs (MkFeatureable d
_ Attributes
a) = Attributes
a