Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides a container type similar to Data.Dynamic but which retains information about a typeclass (or other constraint) that is known to be available for the type of the object contained inside.
- data ClassConstraint cs = ClassConstraint
- data ConstrainedDynamic cs
- toDyn :: (Typeable a, cs a, Typeable cs) => a -> ConstrainedDynamic cs
- fromDynamic :: (Typeable a, cs a) => ConstrainedDynamic cs -> Maybe a
- fromDyn :: (Typeable a, cs a) => ConstrainedDynamic cs -> a -> a
- dynTypeRep :: ConstrainedDynamic cs -> TypeRep
- dynConstraintType :: forall a. Typeable a => ConstrainedDynamic a -> TypeRep
- applyClassFn :: ConstrainedDynamic cs -> (forall a. cs a => a -> b) -> b
- classCast :: forall a b. (Typeable a, Typeable b) => ConstrainedDynamic a -> Maybe (ConstrainedDynamic b)
Types
data ClassConstraint cs Source #
A type used to represent class constraints as values. This exists
primarily so that typeOf (ClassConstraint :: ClassConstraint cs)
can be
used to obtain a TypeRep
that uniquely identifies a typeclass.
data ConstrainedDynamic cs Source #
A type that contains a value whose type is unknown at compile time,
except that it satisfies a given constraint. For example, a value of
ConstrainedDynamic Show
could contain a value of any type for which an
instance of the typeclass Show
is available.
Typeable (* -> Constraint) cs => Show (ConstrainedDynamic cs) Source # | An instance of |
Functions that mirror functions in Data.Dynamic
toDyn :: (Typeable a, cs a, Typeable cs) => a -> ConstrainedDynamic cs Source #
Create a ConstrainedDynamic
for a given value. Note that this
function must be used in a context where the required constraint
type can be determined, for example by explicitly identifying the
required type using the form toDyn value :: ConstrainedDynamic TypeClass
.
fromDynamic :: (Typeable a, cs a) => ConstrainedDynamic cs -> Maybe a Source #
Extract a value ConstrainedDynamic
to a particular type if and only if
the value contained with in it has that type, returning
if the
value Just
vv
has the correct type or
otherwise,Nothing
fromDyn :: (Typeable a, cs a) => ConstrainedDynamic cs -> a -> a Source #
Extract a value ConstrainedDynamic
to a particular type if and only if
the value contained with in it has that type, returning the value if it has
the correct type or a default value otherwise.
dynTypeRep :: ConstrainedDynamic cs -> TypeRep Source #
Return the TypeRep
for the type of value contained within a
ConstrainedDynamic
.
Extended API for managing and using class constraints
dynConstraintType :: forall a. Typeable a => ConstrainedDynamic a -> TypeRep Source #
Return a TypeRep
that uniquely identifies the type of constraint
used in the ConstrainedDynamic
. The actual type whose representation
is returned is ClassConstraint c
where c
is the constraint.
applyClassFn :: ConstrainedDynamic cs -> (forall a. cs a => a -> b) -> b Source #
Apply a polymorphic function that accepts all values matching the
appropriate constraint to the value stored inside a ConstrainedDynamic
and return its result. Note that this *must* be a polymorphic function
with only a single argument that is constrained by the constrain, so
for example the function show
from the typeclass Show
is allowable,
but ==
from the typeclass Eq
would not work as it requires a
second argument that has the same type as the first, and it is not
possible to safely return the partially-applied function as its type is
not known in the calling context.
classCast :: forall a b. (Typeable a, Typeable b) => ConstrainedDynamic a -> Maybe (ConstrainedDynamic b) Source #
If a ConstrainedDynamic
has an unknown constraint variable, classCast
can be used to convert it to a ConstrainedDynamic
with a known constraint.
For example, classCast d :: Maybe (ConstrainedDynamic Show)
returns
if Just
d :: Maybe (ConstrainedDynamic Show)d
s constraint was Show
or Nothing
if it was any other constraint.