{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Features.Featureable
( Featureable(..)
, packFeature
, getFeatureableAttrs
) where
import Data.Aeson (ToJSON (toJSON))
import Data.Typeable (Typeable)
import Features.Attributes (Attributes, HasAttributes (..))
import Features.Core (Feature, makeFeature)
import Features.Output (OutputShape, ShapeOutput (..))
import GHC.TypeLits (KnownSymbol)
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
packFeature :: forall (n :: Symbol) d.
(KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) =>
Feature n d -> Featureable
packFeature Feature n d
x = forall d.
(Show d, ToJSON d, ShapeOutput d) =>
d -> Attributes -> Featureable
MkFeatureable Feature n d
x (forall (name :: Symbol) d name1. HasAttributes name d => Attributes
getAttributes @n)
instance Show Featureable where
show :: Featureable -> String
show (MkFeatureable d
x Attributes
_) = forall a. Show a => a -> String
show d
x
instance ToJSON Featureable where
toJSON :: Featureable -> Value
toJSON (MkFeatureable d
x Attributes
_) = forall a. ToJSON a => a -> Value
toJSON d
x
instance ShapeOutput Featureable where
dataOnly :: forall b. Featureable -> OutputShape b
dataOnly (MkFeatureable d
x Attributes
_) = forall a b. ShapeOutput a => a -> OutputShape b
dataOnly d
x
nameOnly :: forall b. Featureable -> OutputShape b
nameOnly (MkFeatureable d
x Attributes
_) = forall a b. ShapeOutput a => a -> OutputShape b
nameOnly d
x
attrOnly :: forall b. Featureable -> OutputShape b
attrOnly (MkFeatureable d
x Attributes
_) = forall a b. ShapeOutput a => a -> OutputShape b
attrOnly d
x
nameData :: forall b. Featureable -> OutputShape b
nameData (MkFeatureable d
x Attributes
_) = forall a b. ShapeOutput a => a -> OutputShape b
nameData d
x
nameAttr :: forall b. Featureable -> OutputShape b
nameAttr (MkFeatureable d
x Attributes
_) = forall a b. ShapeOutput a => a -> OutputShape b
nameAttr d
x
getFeatureableAttrs :: Featureable -> Attributes
getFeatureableAttrs :: Featureable -> Attributes
getFeatureableAttrs (MkFeatureable d
_ Attributes
a) = Attributes
a
eqFeatureableData :: Featureable -> Featureable -> Bool
eqFeatureableData :: Featureable -> Featureable -> Bool
eqFeatureableData Featureable
f1 Featureable
f2 = forall a. ToJSON a => a -> Value
toJSON (forall a b. ShapeOutput a => a -> OutputShape b
dataOnly Featureable
f1) forall a. Eq a => a -> a -> Bool
== forall a. ToJSON a => a -> Value
toJSON (forall a b. ShapeOutput a => a -> OutputShape b
dataOnly Featureable
f2)