{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generic.HKD.Field
( HasField' (..)
) where
import Data.Coerce (coerce)
import Data.Generic.HKD.Types (HKD (..), HKD_)
import Data.Kind (Constraint, Type)
import Data.Void (Void)
import GHC.TypeLits (ErrorMessage (..), Symbol, TypeError)
import qualified Data.GenericLens.Internal as G
import qualified Data.Generics.Internal.VL.Lens as G
class HasField'
(field :: Symbol)
(f :: Type -> Type)
(structure :: Type)
(focus :: Type)
| field f structure -> focus where
field :: G.Lens' (HKD structure f) (f focus)
data HasTotalFieldPSym :: Symbol -> (G.TyFun (Type -> Type) (Maybe Type))
type instance G.Eval (HasTotalFieldPSym sym) tt = G.HasTotalFieldP sym tt
instance
( ErrorUnless field structure (G.CollectField field (HKD_ f structure))
, G.GLens' (HasTotalFieldPSym field) (HKD_ f structure) (f focus)
) => HasField' field f structure focus where
field = coerced . G.ravel (G.glens @(HasTotalFieldPSym field))
where
coerced :: G.Lens' (HKD structure f) (HKD_ f structure Void)
coerced f = fmap coerce . f . coerce
type family ErrorUnless (field :: Symbol) (s :: Type) (stat :: G.TypeStat) :: Constraint where
ErrorUnless field s ('G.TypeStat _ _ '[])
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " does not contain a field named '"
':<>: 'Text field ':<>: 'Text "'."
)
ErrorUnless field s ('G.TypeStat (n ': ns) _ _)
= TypeError
( 'Text "Not all constructors of the type "
':<>: 'ShowType s
':$$: 'Text " contain a field named '"
':<>: 'Text field ':<>: 'Text "'."
':$$: 'Text "The offending constructors are:"
':$$: G.ShowSymbols (n ': ns)
)
ErrorUnless _ _ ('G.TypeStat '[] '[] _)
= ()