module Data.Generics.Product.Typed
(
HasType (..)
, GHasType (..)
) where
import Data.Generics.Internal.Families
import Data.Generics.Internal.Lens
import Data.Kind (Constraint, Type)
import GHC.Generics
import GHC.TypeLits (TypeError, ErrorMessage (..))
class HasType a s where
typed :: Lens' s a
typed f t
= fmap (flip (setTyped @a) t) (f (getTyped @a t))
getTyped :: s -> a
getTyped s = s ^. typed @a
setTyped :: a -> s -> s
setTyped = set (typed @a)
instance
( Generic s
, ErrorUnlessOne a s (CountTotalType a (Rep s))
, GHasType (Rep s) a
) => HasType a s where
typed = repIso . gtyped
type family ErrorUnlessOne (a :: Type) (s :: Type) (count :: Count) :: Constraint where
ErrorUnlessOne a s 'None
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " does not contain a value of type "
':<>: 'ShowType a
)
ErrorUnlessOne a s 'Multiple
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " contains multiple values of type "
':<>: 'ShowType a
':<>: 'Text "; the choice of value is thus ambiguous"
)
ErrorUnlessOne _ _ 'One
= ()
class GHasType (f :: Type -> Type) a where
gtyped :: Lens' (f x) a
instance GProductHasType l r a (HasTotalTypeP a l)
=> GHasType (l :*: r) a where
gtyped = gproductTyped @_ @_ @_ @(HasTotalTypeP a l)
instance (GHasType l a, GHasType r a) => GHasType (l :+: r) a where
gtyped = combine (gtyped @l) (gtyped @r)
instance GHasType (K1 R a) a where
gtyped f (K1 x) = fmap K1 (f x)
instance GHasType f a => GHasType (M1 m meta f) a where
gtyped = mIso . gtyped
class GProductHasType l r a (contains :: Bool) where
gproductTyped :: Lens' ((l :*: r) x) a
instance GHasType l a => GProductHasType l r a 'True where
gproductTyped = first . gtyped
instance GHasType r a => GProductHasType l r a 'False where
gproductTyped = second . gtyped