Safe Haskell | None |
---|---|
Language | Haskell2010 |
Helpers for dealing with overladed properties, signals and methods.
Synopsis
- type family ParentTypes a :: [*]
- class HasParentTypes (o :: *)
- type family IsDescendantOf (parent :: *) (descendant :: *) :: Constraint where ...
- asA :: (ManagedPtrNewtype a, ManagedPtrNewtype b, HasParentTypes b, IsDescendantOf a b) => b -> (ManagedPtr a -> a) -> a
- type family AttributeList a :: [(Symbol, *)]
- class HasAttributeList a
- type family ResolveAttribute (s :: Symbol) (o :: *) :: * where ...
- type family HasAttribute (attr :: Symbol) (o :: *) :: Constraint where ...
- class HasAttr (attr :: Symbol) (o :: *)
- type family SignalList a :: [(Symbol, *)]
- type family ResolveSignal (s :: Symbol) (o :: *) :: * where ...
- type family HasSignal (s :: Symbol) (o :: *) :: Constraint where ...
- type family MethodResolutionFailed (method :: Symbol) (o :: *) where ...
- type family UnsupportedMethodError (s :: Symbol) (o :: *) :: * where ...
- class MethodInfo i o s where
- overloadedMethod :: o -> s
Type level inheritance
type family ParentTypes a :: [*] Source #
All the types that are ascendants of this type, including interfaces that the type implements.
Instances
type ParentTypes GValue Source # | There are no types in the bindings that a |
Defined in Data.GI.Base.GValue | |
type ParentTypes GError Source # | There are no types in the bindings that a |
Defined in Data.GI.Base.GError | |
type ParentTypes (GClosure a) Source # | There are no types in the bindings that a closure can be safely cast to. |
Defined in Data.GI.Base.GClosure |
class HasParentTypes (o :: *) Source #
A constraint on a type, to be fulfilled whenever it has a type
instance for ParentTypes
. This leads to nicer errors, thanks to
the overlappable instance below.
Instances
(TypeError (('Text "Type \8216" :<>: 'ShowType a) :<>: 'Text "\8217 does not have any known parent types.") :: Constraint) => HasParentTypes a Source # | Default instance, which will give rise to an error for types
without an associated |
Defined in Data.GI.Base.Overloading | |
HasParentTypes GValue Source # | |
Defined in Data.GI.Base.GValue | |
HasParentTypes GError Source # | |
Defined in Data.GI.Base.GError | |
HasParentTypes (GClosure a) Source # | |
Defined in Data.GI.Base.GClosure |
type family IsDescendantOf (parent :: *) (descendant :: *) :: Constraint where ... Source #
Check that a type is in the list of ParentTypes
of another
type.
IsDescendantOf d d = () | |
IsDescendantOf p d = CheckForAncestorType d p (ParentTypes d) |
asA :: (ManagedPtrNewtype a, ManagedPtrNewtype b, HasParentTypes b, IsDescendantOf a b) => b -> (ManagedPtr a -> a) -> a Source #
Safe coercions to a parent class. For instance:
#show $ label `asA` Gtk.Widget
Looking up attributes in parent types
type family AttributeList a :: [(Symbol, *)] Source #
The list of attributes defined for a given type. Each element of
the list is a tuple, with the first element of the tuple the name
of the attribute, and the second the type encoding the information
of the attribute. This type will be an instance of
AttrInfo
.
class HasAttributeList a Source #
A constraint on a type, to be fulfilled whenever it has a type
instance for AttributeList
. This is here for nicer error
reporting.
Instances
(TypeError (('Text "Type \8216" :<>: 'ShowType a) :<>: 'Text "\8217 does not have any known attributes.") :: Constraint) => HasAttributeList (a :: k) Source # | Default instance, which will give rise to an error for types
without an associated |
Defined in Data.GI.Base.Overloading |
type family ResolveAttribute (s :: Symbol) (o :: *) :: * where ... Source #
Return the type encoding the attribute information for a given type and attribute.
ResolveAttribute s o = FindElement s (AttributeList o) (((('Text "Unknown attribute \8216" :<>: 'Text s) :<>: 'Text "\8217 for object \8216") :<>: 'ShowType o) :<>: 'Text "\8217.") |
type family HasAttribute (attr :: Symbol) (o :: *) :: Constraint where ... Source #
A constraint imposing that the given object has the given attribute.
HasAttribute attr o = IsElem attr (AttributeList o) (() :: Constraint) (((('Text "Attribute \8216" :<>: 'Text attr) :<>: 'Text "\8217 not found for type \8216") :<>: 'ShowType o) :<>: 'Text "\8217.") |
class HasAttr (attr :: Symbol) (o :: *) Source #
A constraint that enforces that the given type has a given attribute.
Instances
HasAttribute attr o => HasAttr attr o Source # | |
Defined in Data.GI.Base.Overloading |
Looking up signals in parent types
type family SignalList a :: [(Symbol, *)] Source #
The list of signals defined for a given type. Each element of the
list is a tuple, with the first element of the tuple the name of
the signal, and the second the type encoding the information of the
signal. This type will be an instance of
SignalInfo
.
type family ResolveSignal (s :: Symbol) (o :: *) :: * where ... Source #
Return the type encoding the signal information for a given type and signal.
ResolveSignal s o = FindElement s (SignalList o) (((('Text "Unknown signal \8216" :<>: 'Text s) :<>: 'Text "\8217 for object \8216") :<>: 'ShowType o) :<>: 'Text "\8217.") |
type family HasSignal (s :: Symbol) (o :: *) :: Constraint where ... Source #
A constraint enforcing that the signal exists for the given object, or one of its ancestors.
HasSignal s o = IsElem s (SignalList o) (() :: Constraint) (((('Text "Signal \8216" :<>: 'Text s) :<>: 'Text "\8217 not found for type \8216") :<>: 'ShowType o) :<>: 'Text "\8217.") |
Looking up methods in parent types
type family MethodResolutionFailed (method :: Symbol) (o :: *) where ... Source #
Returned when the method is not found, hopefully making the resulting error messages somewhat clearer.
MethodResolutionFailed m o = TypeError (((('Text "Unknown method \8216" :<>: 'Text m) :<>: 'Text "\8217 for type \8216") :<>: 'ShowType o) :<>: 'Text "\8217.") |
type family UnsupportedMethodError (s :: Symbol) (o :: *) :: * where ... Source #
A constraint that always fails with a type error, for documentation purposes.
UnsupportedMethodError s o = TypeError (((('Text "Unsupported method \8216" :<>: 'Text s) :<>: 'Text "\8217 for object \8216") :<>: 'ShowType o) :<>: 'Text "\8217.") |
class MethodInfo i o s where Source #
Class for types containing the information about an overloaded
method of type o -> s
.
overloadedMethod :: o -> s Source #