{-# LANGUAGE TypeOperators, KindSignatures, DataKinds, PolyKinds,
TypeFamilies, UndecidableInstances, EmptyDataDecls,
MultiParamTypeClasses, FlexibleInstances, ConstraintKinds #-}
module Data.GI.Base.Overloading
(
ParentTypes
, IsDescendantOf
#if MIN_VERSION_base(4,9,0)
, UnknownAncestorError
#endif
, AttributeList
, HasAttributeList
, ResolveAttribute
, HasAttribute
, HasAttr
, SignalList
, ResolveSignal
, HasSignal
, MethodInfo(..)
, MethodProxy(..)
, MethodResolutionFailed
, IsLabelProxy(..)
#if MIN_VERSION_base(4,9,0)
, module GHC.OverloadedLabels
#endif
) where
import GHC.Exts (Constraint)
import GHC.TypeLits
import Data.Proxy (Proxy)
#if MIN_VERSION_base(4,9,0)
import GHC.OverloadedLabels (IsLabel(..))
#endif
class IsLabelProxy (x :: Symbol) a where
fromLabelProxy :: Proxy x -> a
type family JoinLists (as :: [a]) (bs :: [a]) :: [a] where
JoinLists '[] bs = bs
JoinLists (a ': as) bs = a ': JoinLists as bs
type family FindElement (m :: Symbol) (ms :: [(Symbol, *)])
#if !MIN_VERSION_base(4,9,0)
(typeError :: *)
#else
(typeError :: ErrorMessage)
#endif
:: * where
FindElement m '[] typeError =
#if !MIN_VERSION_base(4,9,0)
typeError
#else
TypeError typeError
#endif
FindElement m ('(m, o) ': ms) typeError = o
FindElement m ('(m', o) ': ms) typeError = FindElement m ms typeError
data AncestorCheck t a = HasAncestor a t
#if !MIN_VERSION_base(4,9,0)
| DoesNotHaveRequiredAncestor Symbol t Symbol a
#endif
#if MIN_VERSION_base(4,9,0)
type family UnknownAncestorError (a :: *) (t :: *) where
UnknownAncestorError a t =
TypeError ('Text "Required ancestor ‘" ':<>: 'ShowType a
':<>: 'Text "’ not found for type ‘"
':<>: 'ShowType t ':<>: 'Text "’.")
#endif
type family CheckForAncestorType t (a :: *) (as :: [*]) :: AncestorCheck * * where
CheckForAncestorType t a '[] =
#if !MIN_VERSION_base(4,9,0)
'DoesNotHaveRequiredAncestor "Error: Required ancestor" a "not found for type" t
#else
UnknownAncestorError a t
#endif
CheckForAncestorType t a (a ': as) = 'HasAncestor a t
CheckForAncestorType t a (b ': as) = CheckForAncestorType t a as
type family IsDescendantOf (parent :: *) (descendant :: *) :: Constraint where
IsDescendantOf d d = () ~ ()
IsDescendantOf p d = CheckForAncestorType d p (ParentTypes d) ~ 'HasAncestor p d
type family ParentTypes a :: [*]
type family AttributeList a :: [(Symbol, *)]
class HasAttributeList a
#if MIN_VERSION_base(4,9,0)
instance {-# OVERLAPPABLE #-}
TypeError ('Text "Type ‘" ':<>: 'ShowType a ':<>:
'Text "’ does not have any known attributes.")
=> HasAttributeList a
#endif
#if !MIN_VERSION_base(4,9,0)
data UnknownAttribute (msg1 :: Symbol) (s :: Symbol) (msg2 :: Symbol) (o :: *)
#endif
type family ResolveAttribute (s :: Symbol) (o :: *) :: * where
ResolveAttribute s o = FindElement s (AttributeList o)
#if !MIN_VERSION_base(4,9,0)
(UnknownAttribute "Error: could not find attribute" s "for object" o)
#else
('Text "Unknown attribute ‘" ':<>:
'Text s ':<>: 'Text "’ for object ‘" ':<>:
'ShowType o ':<>: 'Text "’.")
#endif
type family IsElem (e :: Symbol) (es :: [(Symbol, *)]) (success :: k)
#if !MIN_VERSION_base(4,9,0)
(failure :: k)
#else
(failure :: ErrorMessage)
#endif
:: k where
IsElem e '[] success failure =
#if !MIN_VERSION_base(4,9,0)
failure
#else
TypeError failure
#endif
IsElem e ( '(e, t) ': es) success failure = success
IsElem e ( '(other, t) ': es) s f = IsElem e es s f
data AttributeCheck a t = HasAttribute
#if !MIN_VERSION_base(4,9,0)
| DoesNotHaveAttribute Symbol a Symbol t
#endif
type family HasAttribute (attr :: Symbol) (o :: *) where
HasAttribute attr o = IsElem attr (AttributeList o)
'HasAttribute
#if !MIN_VERSION_base(4,9,0)
('DoesNotHaveAttribute "Error: attribute" attr "not found for type" o)
#else
('Text "Attribute ‘" ':<>: 'Text attr ':<>:
'Text "’ not found for type ‘" ':<>:
'ShowType o ':<>: 'Text "’.")
#endif
~ 'HasAttribute
class HasAttr (attr :: Symbol) (o :: *)
instance HasAttribute attr o => HasAttr attr o
type family SignalList a :: [(Symbol, *)]
#if !MIN_VERSION_base(4,9,0)
data UnknownSignal (msg1 :: Symbol) (s :: Symbol) (msg2 :: Symbol) (o :: *)
#endif
type family ResolveSignal (s :: Symbol) (o :: *) :: * where
ResolveSignal s o = FindElement s (SignalList o)
#if !MIN_VERSION_base(4,9,0)
(UnknownSignal "Error: could not find signal" s "for object" o)
#else
('Text "Unknown signal ‘" ':<>:
'Text s ':<>: 'Text "’ for object ‘" ':<>:
'ShowType o ':<>: 'Text "’.")
#endif
data SignalCheck s t = HasSignal
#if !MIN_VERSION_base(4,9,0)
| DoesNotHaveSignal Symbol s Symbol t
#endif
type family HasSignal (s :: Symbol) (o :: *) where
HasSignal s o = IsElem s (SignalList o)
'HasSignal
#if !MIN_VERSION_base(4,9,0)
('DoesNotHaveSignal "Error: signal" s "not found for type" o)
#else
('Text "Signal ‘" ':<>: 'Text s ':<>:
'Text "’ not found for type ‘" ':<>:
'ShowType o ':<>: 'Text "’.")
#endif
~ 'HasSignal
class MethodInfo i o s where
overloadedMethod :: MethodProxy i -> o -> s
data MethodProxy a = MethodProxy
#if !MIN_VERSION_base(4,9,0)
data MethodResolutionFailed (label :: Symbol) (o :: *)
#else
type family MethodResolutionFailed (method :: Symbol) (o :: *) where
MethodResolutionFailed m o =
TypeError ('Text "Unknown method ‘" ':<>:
'Text m ':<>: 'Text "’ for type ‘" ':<>:
'ShowType o ':<>: 'Text "’.")
#endif