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, Typeable instance Show Dynamic 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.
There's two ways of going from a dynamic value to one with a concrete type: 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.
The 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, Typeable data TyCon -- abstract, instance of: Eq, Show, Typeable 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.
Type constructors are represented by the abstract type, TyCon.
Most importantly, TypeReps 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.
To allow comparisons between TypeReps to be implemented efficiently, the abstract TyCon type is used, with the constructor function mkTyCon provided:
mkTyCon :: String -> TyCon |
mkTyCon "a" == mkTyCon "a" |
Both 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 TypeReps:
class Typeable a where typeOf :: a -> TypeRep |
The typeOf function is overloaded to return the type representation associated with a type.
Important: The argument to typeOf is only used to carry type information around so that overloading can be resolved. Typeable instances should never, ever look at this argument.
The Dynamic library provides Typeable instances for all Prelude types and all types from the lang package (given that their component types are themselves Typeable). They are:
Prelude types: [a], (), (a,b), (a,b,c), (a,b,c,d), (a,b,c,d,e), (a->b), (Array a b), Bool, Char, (Complex a), Double, (Either a b), Float, Handle, Int, Integer, (IO a), (Maybe a), Ordering Hugs/GHC types: Addr, AddrOff, Dynamic, ForeignObj, (IORef a), Int8, Int16, Int32, Int64, (ST s a), (StablePtr a), TyCon, TypeRep, Word8, Word16, Word32, Word64 GHC types: ArithException, AsyncException, (ByteArray i), CChar, CClock, CDouble, CFile, CFloat, CFpos, CInt, CJmpbuf, CLDouble, CLLong, CLong, CPtrdiff, CSChar, CShort, CSigAtomic, CSize, CTime, CUChar, CUInt, CULLong, CULong, CUShort, CWchar, Exception, (IOArray i e), (IOUArray i e), (MutableByteArray s i), PackedString, (STArray s i e), (STUArray s i e), (StableName a), (UArray i e), (Weak a) |
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 |