Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
class Label (structure :: Type) where Source #
For any record type, we can extract the labels generically using the
Const
functor.
>>>
import Data.Generic.HKD
>>>
import Data.Functor.Identity (Identity (..))
>>>
data User = User { name :: String, age :: Int } deriving Generic
>>>
label (deconstruct @Identity (User "Tom" 25))
User {name = Const "name", age = Const "age"}
class GLabels (rep :: Type -> Type) where Source #
Instances
(GLabels left, GLabels right) => GLabels (left :*: right) Source # | |
GLabels inner => GLabels (D1 meta inner) Source # | |
(TypeError (Text "You can't collect labels for a non-record type!") :: Constraint) => GLabels (C1 (MetaCons name fixity False) inner) Source # | |
GLabels inner => GLabels (C1 (MetaCons name fixity True) inner) Source # | |
KnownSymbol name => GLabels (S1 (MetaSel (Just name) i d c) (K1 index inner :: Type -> Type)) Source # | |
labelsWhere :: forall structure f. (Label structure, ProductB (HKD structure), TraversableB (HKD structure)) => (forall a. f a -> Bool) -> HKD structure f -> [String] Source #
Because all HKD types are valid barbies, and we have the above mechanism for extracting field names, we can ask some pretty interesting questions.
>>>
import Control.Lens
>>>
import Data.Maybe (isNothing)
>>>
import Data.Monoid (Last (..))
>>>
import Data.Generic.HKD
Let's imagine, for example, that we're half way through filling in a user's details:
>>>
data User = User { name :: String, age :: Int } deriving Generic
>>>
test = mempty @(HKD User Last) & field @"name" .~ pure "Tom"
We want to send a JSON response back to the client containing the fields
that have yet to be finished. All we need to do is pick the fields where the
values are Last Nothing
:
>>>
labelsWhere (isNothing . getLast) test
["age"]