The Dynamic
library provides cheap-and-cheerful dynamic types for
Haskell. A dynamically typed value is one which carries type
information with it at run-time, and is represented here by the
abstract type Dynamic
. Values can be converted into Dynamic
ones, which can then be combined and manipulated by the program using
the operations provided over the abstract, dynamic type. One of
these operations allows you to (try to) convert a dynamically-typed
value back into a value with the same (monomorphic) type it had before
converting it into a dynamically-typed value. If the dynamically-typed
value isn't of the desired type, the coercion will fail.
The Dynamic
library is capable of dealing with monomorphic types
only; no support for polymorphic dynamic values, but hopefully that
will be added at a later stage.
Examples where this library may come in handy (dynamic types, really - hopefully the library provided here will suffice) are: persistent programming, interpreters, distributed programming etc.
The following operations are provided over the Dynamic
type:
data Dynamic -- abstract, instance of: Show --
toDyn :: Typeable a => a -> Dynamic
fromDyn :: Typeable a => Dynamic -> a -> a
fromDynamic :: Typeable a => Dynamic -> Maybe a
toDyn
converts a value into a dynamic one, provided
toDyn
knows the (concrete) type representation of the value.
The Typeable
type class is used to encode this, overloading a
function that returns the type representation of a value. More on this
below.fromDyn
, tries to convert the dynamic value into
a value with the same type as its second argument. If this fails, the
default second argument is just returned. fromDynamic
returns a
Maybe
type instead, Nothing
coming back if the conversion
was not possible.Dynamic
type has got a Show
instance which returns
a pretty printed string of the type of the dynamic value. (Useful when
debugging).
Haskell types are represented as terms using the TypeRep
abstract type:
data TypeRep -- abstract, instance of: Eq, Show
data TyCon -- abstract, instance of: Eq, Show
mkTyCon :: String -> TyCon
mkAppTy :: TyCon -> [TypeRep] -> TypeRep
mkFunTy :: TypeRep -> TypeRep -> TypeRep
applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
mkAppTy
applies a type constructor to a sequence of types,
returning a type.mkFunTy
is a special case of mkAppTy
, applying
the function type constructor to a pair of types.applyTy
applies a type to a function type. If possible,
the result type is returned.TyCon
. TypeRep
s can be compared for equality.
Type equality is used when converting a Dynamic
value into a
value of some specific type, comparing the type representation that
the Dynamic
value embeds with equality of the type representation
of the type we're trying to convert the dynamically-typed value into.TypeRep
s to be implemented
efficiently, the abstract TyCon
type is used, with
the constructor function mkTyCon
provided:
mkTyCon :: String -> TyCon
An implementation of the Dynamic
interface guarantees the
following,
mkTyCon "a" == mkTyCon "a"
A really efficient implementation is possible if we guarantee/demand
that the strings are unique, and for a particular type constructor,
the application mkTyCon
to the string that represents the type
constructor is never duplicated. Q: Would this constraint be
unworkable in practice?TyCon
and TypeRep
are instances of the Show
type
classes. To have tuple types be shown in infix form, the Show
instance guarantees that type constructors consisting of n
-commas,
i.e., (mkTyCon ",,,,"
), is shown as an (n+1)
tuple in infix
form.
To ease the construction of Dynamic
values, we
introduce the following type class to help working with TypeRep
s:
class Typeable a where
typeOf :: a -> TypeRep
typeOf
function is overloaded to return the type
representation associated with a type. typeOf
is only used to
carry type information around so that overloading can be resolved.
Typeable
instances should never, ever look at this argument.Dynamic
library provide Typeable
instances
for all Prelude and Hugs/GHC extension library types. They are:
Prelude types:
Int, Char, Bool, Float, Double, Integer, (IO a),
[a], (Either a b), (Maybe a), (a->b),
(), (,), (,,), (,,,), (,,,,),
Ordering, Complex, Array, Handle
Hugs/GHC types:
Addr, Word8, Word16, Word32, Word64,
Int8,Int16,Int32,Int64,
ForeignObj, MVar, (ST s a), (StablePtr a)
GHC types:
Word, ByteArray, MutableByteArray
Operations for applying a dynamic function type to a dynamically typed argument are commonly useful, and also provided:
dynApply :: Dynamic -> Dynamic -> Dynamic -- unsafe.
dynApplyMb :: Dynamic -> Dynamic -> Maybe Dynamic