{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generic.HKD.Labels where
import Data.Barbie (ProductB (..), TraversableB (..))
import Data.Functor.Const (Const (..))
import Data.Functor.Product (Product (..))
import Data.Generic.HKD.Types (HKD (..), GHKD_)
import Data.Kind (Type)
import Data.Proxy (Proxy (..))
import GHC.Generics
import GHC.TypeLits (ErrorMessage (..), KnownSymbol, TypeError, symbolVal)
class Label (structure :: Type) where
label :: HKD structure f -> HKD structure (Const String)
class GLabels (rep :: Type -> Type) where
glabel :: GHKD_ f rep p -> GHKD_ (Const String) rep p
instance GLabels inner => GLabels (D1 meta inner) where
glabel = M1 . glabel . unM1
instance GLabels inner
=> GLabels (C1 ('MetaCons name fixity 'True) inner) where
glabel = M1 . glabel . unM1
instance TypeError ('Text "You can't collect labels for a non-record type!")
=> GLabels (C1 ('MetaCons name fixity 'False) inner) where
glabel = undefined
instance KnownSymbol name
=> GLabels (S1 ('MetaSel ('Just name) i d c) (K1 index inner)) where
glabel _ = M1 (K1 (Const (symbolVal (Proxy @name))))
instance (GLabels left, GLabels right) => GLabels (left :*: right) where
glabel (left :*: right) = glabel left :*: glabel right
instance (Generic structure, GLabels (Rep structure)) => Label structure where
label = HKD . glabel . runHKD
labelsWhere
:: forall structure f
. ( Label structure
, ProductB (HKD structure)
, TraversableB (HKD structure)
)
=> (forall a. f a -> Bool)
-> HKD structure f
-> [String]
labelsWhere p xs
= getConst (btraverse go (label xs `bprod` xs))
where
go :: Product (Const String) f a -> (Const [String]) (Maybe a)
go (Pair (Const key) value) = Const if p value then [key] else []