{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Features.Attributes(
Attributes(..)
, Role(..)
, Purpose(..)
, HasAttributes(..)
, emptyAttributes
, basicAttributes
, emptyPurpose
) where
import safe Data.Eq ( Eq )
import safe Data.Ord ( Ord )
import safe Data.Set ( Set, empty, fromList )
import safe Data.Text ( Text )
import safe GHC.Show ( Show )
import safe GHC.Generics ( Generic )
import safe GHC.TypeLits ( KnownSymbol )
data Role =
Outcome
| Covariate
| Exposure
| Competing
| Weight
| Intermediate
| Unspecified
deriving (Role -> Role -> Bool
(Role -> Role -> Bool) -> (Role -> Role -> Bool) -> Eq Role
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Role -> Role -> Bool
$c/= :: Role -> Role -> Bool
== :: Role -> Role -> Bool
$c== :: Role -> Role -> Bool
Eq, Eq Role
Eq Role
-> (Role -> Role -> Ordering)
-> (Role -> Role -> Bool)
-> (Role -> Role -> Bool)
-> (Role -> Role -> Bool)
-> (Role -> Role -> Bool)
-> (Role -> Role -> Role)
-> (Role -> Role -> Role)
-> Ord Role
Role -> Role -> Bool
Role -> Role -> Ordering
Role -> Role -> Role
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Role -> Role -> Role
$cmin :: Role -> Role -> Role
max :: Role -> Role -> Role
$cmax :: Role -> Role -> Role
>= :: Role -> Role -> Bool
$c>= :: Role -> Role -> Bool
> :: Role -> Role -> Bool
$c> :: Role -> Role -> Bool
<= :: Role -> Role -> Bool
$c<= :: Role -> Role -> Bool
< :: Role -> Role -> Bool
$c< :: Role -> Role -> Bool
compare :: Role -> Role -> Ordering
$ccompare :: Role -> Role -> Ordering
$cp1Ord :: Eq Role
Ord, Int -> Role -> ShowS
[Role] -> ShowS
Role -> String
(Int -> Role -> ShowS)
-> (Role -> String) -> ([Role] -> ShowS) -> Show Role
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Role] -> ShowS
$cshowList :: [Role] -> ShowS
show :: Role -> String
$cshow :: Role -> String
showsPrec :: Int -> Role -> ShowS
$cshowsPrec :: Int -> Role -> ShowS
Show, (forall x. Role -> Rep Role x)
-> (forall x. Rep Role x -> Role) -> Generic Role
forall x. Rep Role x -> Role
forall x. Role -> Rep Role x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Role x -> Role
$cfrom :: forall x. Role -> Rep Role x
Generic)
data Purpose = MkPurpose {
Purpose -> Set Role
getRole :: Set Role
, Purpose -> Set Text
getTags :: Set Text
} deriving (Purpose -> Purpose -> Bool
(Purpose -> Purpose -> Bool)
-> (Purpose -> Purpose -> Bool) -> Eq Purpose
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Purpose -> Purpose -> Bool
$c/= :: Purpose -> Purpose -> Bool
== :: Purpose -> Purpose -> Bool
$c== :: Purpose -> Purpose -> Bool
Eq, Int -> Purpose -> ShowS
[Purpose] -> ShowS
Purpose -> String
(Int -> Purpose -> ShowS)
-> (Purpose -> String) -> ([Purpose] -> ShowS) -> Show Purpose
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Purpose] -> ShowS
$cshowList :: [Purpose] -> ShowS
show :: Purpose -> String
$cshow :: Purpose -> String
showsPrec :: Int -> Purpose -> ShowS
$cshowsPrec :: Int -> Purpose -> ShowS
Show, (forall x. Purpose -> Rep Purpose x)
-> (forall x. Rep Purpose x -> Purpose) -> Generic Purpose
forall x. Rep Purpose x -> Purpose
forall x. Purpose -> Rep Purpose x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Purpose x -> Purpose
$cfrom :: forall x. Purpose -> Rep Purpose x
Generic)
data Attributes = MkAttributes {
Attributes -> Text
getShortLabel :: Text
, Attributes -> Text
getLongLabel :: Text
, Attributes -> Text
getDerivation :: Text
, Attributes -> Purpose
getPurpose :: Purpose
} deriving (Attributes -> Attributes -> Bool
(Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool) -> Eq Attributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attributes -> Attributes -> Bool
$c/= :: Attributes -> Attributes -> Bool
== :: Attributes -> Attributes -> Bool
$c== :: Attributes -> Attributes -> Bool
Eq, Int -> Attributes -> ShowS
[Attributes] -> ShowS
Attributes -> String
(Int -> Attributes -> ShowS)
-> (Attributes -> String)
-> ([Attributes] -> ShowS)
-> Show Attributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attributes] -> ShowS
$cshowList :: [Attributes] -> ShowS
show :: Attributes -> String
$cshow :: Attributes -> String
showsPrec :: Int -> Attributes -> ShowS
$cshowsPrec :: Int -> Attributes -> ShowS
Show, (forall x. Attributes -> Rep Attributes x)
-> (forall x. Rep Attributes x -> Attributes) -> Generic Attributes
forall x. Rep Attributes x -> Attributes
forall x. Attributes -> Rep Attributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Attributes x -> Attributes
$cfrom :: forall x. Attributes -> Rep Attributes x
Generic)
emptyPurpose :: Purpose
emptyPurpose :: Purpose
emptyPurpose = Set Role -> Set Text -> Purpose
MkPurpose Set Role
forall a. Set a
empty Set Text
forall a. Set a
empty
emptyAttributes :: Attributes
emptyAttributes :: Attributes
emptyAttributes = Text -> Text -> Text -> Purpose -> Attributes
MkAttributes Text
"" Text
"" Text
"" Purpose
emptyPurpose
basicAttributes ::
Text
-> Text
-> [Role]
-> [Text]
-> Attributes
basicAttributes :: Text -> Text -> [Role] -> [Text] -> Attributes
basicAttributes Text
sl Text
ll [Role]
rls [Text]
tgs =
Text -> Text -> Text -> Purpose -> Attributes
MkAttributes Text
sl Text
ll Text
""
(Set Role -> Set Text -> Purpose
MkPurpose ([Role] -> Set Role
forall a. Ord a => [a] -> Set a
fromList [Role]
rls) ([Text] -> Set Text
forall a. Ord a => [a] -> Set a
fromList [Text]
tgs))
class (KnownSymbol name) => HasAttributes name d where
getAttributes :: f name d -> Attributes
getAttributes f name d
_ = Attributes
emptyAttributes