{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Features.Featureset
( Featureset
, FeaturesetList(..)
, featureset
, getFeatureset
, getFeaturesetAttrs
, getFeaturesetList
, tpose
, allEqFeatureableData
) where
import Data.Aeson (ToJSON (toJSON), object, (.=))
import Data.Function ((.))
import Data.Functor (Functor (fmap))
import Data.List.NonEmpty (NonEmpty (..), head, transpose)
import qualified Data.List.NonEmpty as NE
import Features.Attributes (Attributes)
import Features.Featureable (Featureable, getFeatureableAttrs)
import Features.Output (ShapeOutput (dataOnly))
import GHC.Generics (Generic)
import GHC.Show (Show)
import Prelude (($), (==))
import qualified Prelude
newtype Featureset
= MkFeatureset (NE.NonEmpty Featureable)
deriving (Int -> Featureset -> ShowS
[Featureset] -> ShowS
Featureset -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Featureset] -> ShowS
$cshowList :: [Featureset] -> ShowS
show :: Featureset -> String
$cshow :: Featureset -> String
showsPrec :: Int -> Featureset -> ShowS
$cshowsPrec :: Int -> Featureset -> ShowS
Show)
featureset :: NE.NonEmpty Featureable -> Featureset
featureset :: NonEmpty Featureable -> Featureset
featureset = NonEmpty Featureable -> Featureset
MkFeatureset
getFeatureset :: Featureset -> NE.NonEmpty Featureable
getFeatureset :: Featureset -> NonEmpty Featureable
getFeatureset (MkFeatureset NonEmpty Featureable
x) = NonEmpty Featureable
x
getFeaturesetAttrs :: Featureset -> NE.NonEmpty Attributes
getFeaturesetAttrs :: Featureset -> NonEmpty Attributes
getFeaturesetAttrs (MkFeatureset NonEmpty Featureable
l) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Featureable -> Attributes
getFeatureableAttrs NonEmpty Featureable
l
instance ToJSON Featureset where
toJSON :: Featureset -> Value
toJSON (MkFeatureset NonEmpty Featureable
x) = forall a. ToJSON a => a -> Value
toJSON NonEmpty Featureable
x
newtype FeaturesetList
= MkFeaturesetList (NE.NonEmpty Featureset)
deriving (Int -> FeaturesetList -> ShowS
[FeaturesetList] -> ShowS
FeaturesetList -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FeaturesetList] -> ShowS
$cshowList :: [FeaturesetList] -> ShowS
show :: FeaturesetList -> String
$cshow :: FeaturesetList -> String
showsPrec :: Int -> FeaturesetList -> ShowS
$cshowsPrec :: Int -> FeaturesetList -> ShowS
Show)
getFeaturesetList :: FeaturesetList -> NE.NonEmpty Featureset
getFeaturesetList :: FeaturesetList -> NonEmpty Featureset
getFeaturesetList (MkFeaturesetList NonEmpty Featureset
x) = NonEmpty Featureset
x
tpose :: FeaturesetList -> FeaturesetList
tpose :: FeaturesetList -> FeaturesetList
tpose (MkFeaturesetList NonEmpty Featureset
x) =
NonEmpty Featureset -> FeaturesetList
MkFeaturesetList (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonEmpty Featureable -> Featureset
featureset (forall a. NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
transpose (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Featureset -> NonEmpty Featureable
getFeatureset NonEmpty Featureset
x)))
allEqFeatureableData :: Featureset -> Featureset -> Prelude.Bool
allEqFeatureableData :: Featureset -> Featureset -> Bool
allEqFeatureableData (MkFeatureset NonEmpty Featureable
f1) (MkFeatureset NonEmpty Featureable
f2) = NonEmpty Value
s1 forall a. Eq a => a -> a -> Bool
== NonEmpty Value
s2
where s1 :: NonEmpty Value
s1 = forall a. Ord a => NonEmpty a -> NonEmpty a
NE.sort forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. ShapeOutput a => a -> OutputShape b
dataOnly) NonEmpty Featureable
f1
s2 :: NonEmpty Value
s2 = forall a. Ord a => NonEmpty a -> NonEmpty a
NE.sort forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. ShapeOutput a => a -> OutputShape b
dataOnly) NonEmpty Featureable
f2