{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generics.Product.Typed
(
HasType (..)
) where
import Data.Generics.Internal.Families
import Data.Generics.Internal.VL.Lens as VL
import Data.Generics.Internal.Void
import Data.Generics.Product.Internal.GLens
import Data.Kind (Constraint, Type)
import GHC.Generics (Generic (Rep))
import GHC.TypeLits (TypeError, ErrorMessage (..))
import Data.Generics.Internal.Profunctor.Lens
class HasType a s where
typed :: VL.Lens s s a a
typed
= VL.lens (getTyped @a) (uncurry (setTyped @a) . swap)
{-# INLINE typed #-}
getTyped :: s -> a
getTyped s = s ^. typed @a
setTyped :: a -> s -> s
setTyped = VL.set (typed @a)
{-# MINIMAL typed | setTyped, getTyped #-}
instance
( Generic s
, ErrorUnlessOne a s (CollectTotalType a (Rep s))
, GLens (HasTotalTypePSym a) (Rep s) (Rep s) a a
) => HasType a s where
typed f s = VL.ravel (repLens . glens @(HasTotalTypePSym a)) f s
instance {-# OVERLAPPING #-} HasType a Void where
typed = undefined
type family ErrorUnlessOne (a :: Type) (s :: Type) (stat :: TypeStat) :: Constraint where
ErrorUnlessOne a s ('TypeStat '[_] '[] '[])
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " does not contain a value of type "
':<>: 'ShowType a
)
ErrorUnlessOne a s ('TypeStat (n ': ns) _ _)
= TypeError
( 'Text "Not all constructors of the type "
':<>: 'ShowType s
':<>: 'Text " contain a field of type "
':<>: 'ShowType a ':<>: 'Text "."
':$$: 'Text "The offending constructors are:"
':$$: ShowSymbols (n ': ns)
)
ErrorUnlessOne a s ('TypeStat _ (m ': ms) _)
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " contains multiple values of type "
':<>: 'ShowType a ':<>: 'Text "."
':$$: 'Text "The choice of value is thus ambiguous. The offending constructors are:"
':$$: ShowSymbols (m ': ms)
)
ErrorUnlessOne _ _ ('TypeStat '[] '[] _)
= ()
data HasTotalTypePSym :: Type -> (TyFun (Type -> Type) (Maybe Type))
type instance Eval (HasTotalTypePSym t) tt = HasTotalTypeP t tt