|
Data.Dynamic | Portability | portable | Stability | experimental | Maintainer | libraries@haskell.org |
|
|
|
|
Contents |
- The Dynamic type
- Converting to and from Dynamic
- Applying functions of dynamic type
- Concrete Type Representations
- Building concrete type representations
|
|
Description |
The Dynamic interface provides basic support for dynamic types. Operations for injecting values of arbitrary type into
a dynamically typed value, Dynamic, are provided, together
with operations for converting dynamic values into a concrete
(monomorphic) type.
|
|
Synopsis |
|
|
|
|
The Dynamic type |
|
data Dynamic |
A value of type Dynamic is an object encapsulated together with its type. A Dynamic may only represent a monomorphic value; an attempt to
create a value of type Dynamic from a polymorphically-typed
expression will result in an ambiguity error (see toDyn). Showing a value of type Dynamic returns a pretty-printed representation
of the object's type; useful for debugging.
| Instances | |
|
|
Converting to and from Dynamic |
|
toDyn :: (Typeable a) => a -> Dynamic |
Converts an arbitrary value into an object of type Dynamic. The type of the object must be an instance of Typeable, which
ensures that only monomorphically-typed objects may be converted to
Dynamic. To convert a polymorphic object into Dynamic, give it
a monomorphic type signature. For example: toDyn (id :: Int -> Int)
|
|
fromDyn |
:: (Typeable a) | | => Dynamic | the dynamically-typed object | -> a | a default value | -> a | returns: the value of the first argument, if
it has the correct type, otherwise the value of
the second argument. | Converts a Dynamic object back into an ordinary Haskell value of
the correct type. See also fromDynamic. |
|
|
fromDynamic |
:: (Typeable a) | | => Dynamic | the dynamically-typed object | -> Maybe a | returns: Just a, if the dyanmically-typed
object has the correct type (and a is its value),
or Nothing otherwise. | Converts a Dynamic object back into an ordinary Haskell value of
the correct type. See also fromDyn. |
|
|
Applying functions of dynamic type |
|
dynApply :: Dynamic -> Dynamic -> Maybe Dynamic |
|
dynApp :: Dynamic -> Dynamic -> Dynamic |
|
Concrete Type Representations |
|
This section is useful if you need to define your own
instances of Typeable. |
|
class Typeable a where |
The class Typeable allows a concrete representation of a type to
be calculated. | | Methods | typeOf :: a -> TypeRep | Takes a value of type a and returns a concrete representation
of that type. The value of the argument should be ignored by
any instance of Typeable, so that it is safe to pass undefined as
the argument. |
| | Instances | Typeable Exception | Typeable IOException | Typeable ArithException | Typeable ArrayException | Typeable AsyncException | (Typeable a, Typeable b) => Typeable (ST a b) | (Typeable a, Typeable b) => Typeable (Array a b) | (Typeable a, Typeable b) => Typeable (UArray a b) | (Typeable a, Typeable b, Typeable c) => Typeable (STArray a b c) | (Typeable a, Typeable b, Typeable c) => Typeable (STUArray a b c) | (Typeable a, Typeable b) => Typeable (IOArray a b) | (Typeable a, Typeable b) => Typeable (IOUArray a b) | (Typeable a) => Typeable (Complex a) | (Typeable a) => Typeable [a] | Typeable () | (Typeable a, Typeable b) => Typeable (a, b) | (Typeable a, Typeable b, Typeable c) => Typeable (a, b, c) | (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (a, b, c, d) | (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (a, b, c, d, e) | (Typeable a, Typeable b) => Typeable (a -> b) | Typeable Bool | Typeable Char | Typeable Float | Typeable Double | Typeable Int | Typeable Integer | (Typeable a, Typeable b) => Typeable (Either a b) | (Typeable a) => Typeable (IO a) | (Typeable a) => Typeable (Maybe a) | Typeable Ordering | Typeable Handle | (Typeable a) => Typeable (Ptr a) | (Typeable a) => Typeable (StablePtr a) | Typeable Int8 | Typeable Int16 | Typeable Int32 | Typeable Int64 | Typeable Word8 | Typeable Word16 | Typeable Word32 | Typeable Word64 | Typeable TyCon | Typeable TypeRep | Typeable Dynamic | (Typeable a) => Typeable (IORef a) | Typeable PackedString | (Typeable a, Typeable b) => Typeable (STRef a b) | Typeable CChar | Typeable CSChar | Typeable CUChar | Typeable CShort | Typeable CUShort | Typeable CInt | Typeable CUInt | Typeable CLong | Typeable CULong | Typeable CLLong | Typeable CULLong | Typeable CFloat | Typeable CDouble | Typeable CLDouble | Typeable CPtrdiff | Typeable CSize | Typeable CWchar | Typeable CSigAtomic | Typeable CClock | Typeable CTime | (Typeable a) => Typeable (ForeignPtr a) | (Typeable a) => Typeable (StableName a) | (Typeable a) => Typeable (Weak a) | Typeable CDev | Typeable CIno | Typeable CMode | Typeable COff | Typeable CPid | Typeable CSsize | Typeable CGid | Typeable CNlink | Typeable CUid | Typeable CCc | Typeable CSpeed | Typeable CTcflag | Typeable CRLim | Typeable Fd |
|
|
|
cast :: (Typeable a, Typeable b) => a -> Maybe b |
The type-safe cast operation |
|
Building concrete type representations |
|
data TypeRep |
A concrete representation of a (monomorphic) type. TypeRep
supports reasonably efficient equality. | Instances | |
|
|
data TyCon |
An abstract representation of a type constructor. TyCon objects can
be built using mkTyCon. | Instances | |
|
|
mkTyCon |
:: String | the name of the type constructor (should be unique
in the program, so it might be wise to use the
fully qualified name). | -> TyCon | A unique TyCon object | Builds a TyCon object representing a type constructor. An
implementation of Data.Dynamic should ensure that the following holds: mkTyCon "a" == mkTyCon "a"
|
|
|
mkAppTy :: TyCon -> [TypeRep] -> TypeRep |
Applies a type constructor to a sequence of types |
|
mkFunTy :: TypeRep -> TypeRep -> TypeRep |
A special case of mkAppTy, which applies the function
type constructor to a pair of types. |
|
applyTy :: TypeRep -> TypeRep -> Maybe TypeRep |
Applies a type to a function type. Returns: Just u if the
first argument represents a function of type t -> u and the
second argument represents a function of type t. Otherwise,
returns Nothing. |
|
Produced by Haddock version 0.4 |