Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides a container type similar to Data.Dynamic but which retains information about a list of typeclass (or other constraint) that are known to be available for the type of the object contained inside.
- data ClassConstraint cs = ClassConstraint
- data MCDynamic cs
- toDyn :: (Typeable a, Typeable cs, LTDictBuilder LTDict cs a) => a -> MCDynamic (cs :: [* -> Constraint])
- fromDynamic :: Typeable a => MCDynamic css -> Maybe a
- fromDyn :: Typeable a => MCDynamic cs -> a -> a
- dynTypeRep :: MCDynamic cs -> TypeRep
- dynConstraintTypes :: LTDictConstraintLister a => MCDynamic a -> [TypeRep]
- dynAllConstraintTypes :: LTDictConstraintLister a => MCDynamic a -> [TypeRep]
- dynUnmatchedConstraintTypes :: LTDictConstraintLister a => MCDynamic a -> [TypeRep]
- applyClassFn :: LTDictSearch css cs => MCDynamic css -> ClassConstraint cs -> (forall a. (cs a, Typeable a) => a -> b) -> Maybe 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.
A type that contains a value whose type is unknown at compile time, but for which it is known whether or not it satisfies any of a list of constraints, thus allowing operations to be performed when those constraints are satisfied.
LTDictSearch css Eq => Eq (MCDynamic css) Source # | An instance of |
(LTDictSearch css Show, LTDictConstraintLister css) => Show (MCDynamic css) Source # | An instance of |
Functions that mirror functions in Data.Dynamic
toDyn :: (Typeable a, Typeable cs, LTDictBuilder LTDict cs a) => a -> MCDynamic (cs :: [* -> Constraint]) Source #
Create an MCDynamic
for a given value. Note that this
function must be used in a context where the required list of constraint
types can be determined, for example by explicitly identifying the
required type using the form toDyn value :: MCDynamic [TypeClass,...]
.
Additionally, there must be appropriate instances of the type class HasClass
that describe instances available for type classes that are to be used
with the dynamic object and the type to be included in it. In most
circumstances you should at least import Data.Type.HasClassPreludeInstances
to allow the use of instances of standard Prelude classes and types.
fromDyn :: Typeable a => MCDynamic cs -> a -> a Source #
Extract a value MCDynamic
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 :: MCDynamic cs -> TypeRep Source #
Extended API for managing and using class constraints
dynConstraintTypes :: LTDictConstraintLister a => MCDynamic a -> [TypeRep] Source #
dynAllConstraintTypes :: LTDictConstraintLister a => MCDynamic a -> [TypeRep] Source #
dynUnmatchedConstraintTypes :: LTDictConstraintLister a => MCDynamic a -> [TypeRep] Source #
applyClassFn :: LTDictSearch css cs => MCDynamic css -> ClassConstraint cs -> (forall a. (cs a, Typeable a) => a -> b) -> Maybe b Source #
Apply a polymorphic function that accepts all values matching a
constraint to the value stored inside an MCDynamic
wherever possible.
If the constraint is satisfied, returns
, where r is the result
of the function. If the constraint is not satisfied, returns Just
rNothing
.
Note that the function *must* be a polymorphic function
with only a single argument that is constrained by the constraint, 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.