b83bbfa89c649ce0da0636776960eaccaf242b41
[ghc-base.git] / Data / Dynamic.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.Dynamic
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  experimental
11 -- Portability :  portable
12 --
13 -- The Dynamic interface provides basic support for dynamic types.
14 -- 
15 -- Operations for injecting values of arbitrary type into
16 -- a dynamically typed value, Dynamic, are provided, together
17 -- with operations for converting dynamic values into a concrete
18 -- (monomorphic) type.
19 -- 
20 -----------------------------------------------------------------------------
21
22 module Data.Dynamic
23   (
24
25         -- Module Data.Typeable re-exported for convenience
26         module Data.Typeable,
27
28         -- * The @Dynamic@ type
29         Dynamic,        -- abstract, instance of: Show, Typeable
30
31         -- * Converting to and from @Dynamic@
32         toDyn,          -- :: Typeable a => a -> Dynamic
33         fromDyn,        -- :: Typeable a => Dynamic -> a -> a
34         fromDynamic,    -- :: Typeable a => Dynamic -> Maybe a
35         
36         -- * Applying functions of dynamic type
37         dynApply,
38         dynApp,
39         dynTypeRep
40
41   ) where
42
43
44 import Data.Typeable
45 import Data.Maybe
46 import Unsafe.Coerce
47
48 #ifdef __GLASGOW_HASKELL__
49 import GHC.Base
50 import GHC.Show
51 import GHC.Exception
52 #endif
53
54 #ifdef __HUGS__
55 import Hugs.Prelude
56 import Hugs.IO
57 import Hugs.IORef
58 import Hugs.IOExts
59 #endif
60
61 #ifdef __NHC__
62 import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
63 #endif
64
65 #include "Typeable.h"
66
67 -------------------------------------------------------------
68 --
69 --              The type Dynamic
70 --
71 -------------------------------------------------------------
72
73 {-|
74   A value of type 'Dynamic' is an object encapsulated together with its type.
75
76   A 'Dynamic' may only represent a monomorphic value; an attempt to
77   create a value of type 'Dynamic' from a polymorphically-typed
78   expression will result in an ambiguity error (see 'toDyn').
79
80   'Show'ing a value of type 'Dynamic' returns a pretty-printed representation
81   of the object\'s type; useful for debugging.
82 -}
83 #ifndef __HUGS__
84 data Dynamic = Dynamic TypeRep Obj
85 #endif
86
87 INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")
88
89 instance Show Dynamic where
90    -- the instance just prints the type representation.
91    showsPrec _ (Dynamic t _) = 
92           showString "<<" . 
93           showsPrec 0 t   . 
94           showString ">>"
95
96 #ifdef __GLASGOW_HASKELL__
97 -- here so that it isn't an orphan:
98 instance Exception Dynamic
99 #endif
100
101 #ifdef __GLASGOW_HASKELL__
102 type Obj = Any
103  -- Use GHC's primitive 'Any' type to hold the dynamically typed value.
104  --
105  -- In GHC's new eval/apply execution model this type must not look
106  -- like a data type.  If it did, GHC would use the constructor convention 
107  -- when evaluating it, and this will go wrong if the object is really a 
108  -- function.  Using Any forces GHC to use
109  -- a fallback convention for evaluating it that works for all types.
110 #elif !defined(__HUGS__)
111 data Obj = Obj
112 #endif
113
114 -- | Converts an arbitrary value into an object of type 'Dynamic'.  
115 --
116 -- The type of the object must be an instance of 'Typeable', which
117 -- ensures that only monomorphically-typed objects may be converted to
118 -- 'Dynamic'.  To convert a polymorphic object into 'Dynamic', give it
119 -- a monomorphic type signature.  For example:
120 --
121 -- >    toDyn (id :: Int -> Int)
122 --
123 toDyn :: Typeable a => a -> Dynamic
124 toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
125
126 -- | Converts a 'Dynamic' object back into an ordinary Haskell value of
127 -- the correct type.  See also 'fromDynamic'.
128 fromDyn :: Typeable a
129         => Dynamic      -- ^ the dynamically-typed object
130         -> a            -- ^ a default value 
131         -> a            -- ^ returns: the value of the first argument, if
132                         -- it has the correct type, otherwise the value of
133                         -- the second argument.
134 fromDyn (Dynamic t v) def
135   | typeOf def == t = unsafeCoerce v
136   | otherwise       = def
137
138 -- | Converts a 'Dynamic' object back into an ordinary Haskell value of
139 -- the correct type.  See also 'fromDyn'.
140 fromDynamic
141         :: Typeable a
142         => Dynamic      -- ^ the dynamically-typed object
143         -> Maybe a      -- ^ returns: @'Just' a@, if the dynamically-typed
144                         -- object has the correct type (and @a@ is its value), 
145                         -- or 'Nothing' otherwise.
146 fromDynamic (Dynamic t v) =
147   case unsafeCoerce v of 
148     r | t == typeOf r -> Just r
149       | otherwise     -> Nothing
150
151 -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
152 dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
153 dynApply (Dynamic t1 f) (Dynamic t2 x) =
154   case funResultTy t1 t2 of
155     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
156     Nothing -> Nothing
157
158 dynApp :: Dynamic -> Dynamic -> Dynamic
159 dynApp f x = case dynApply f x of 
160              Just r -> r
161              Nothing -> error ("Type error in dynamic application.\n" ++
162                                "Can't apply function " ++ show f ++
163                                " to argument " ++ show x)
164
165 dynTypeRep :: Dynamic -> TypeRep
166 dynTypeRep (Dynamic tr _) = tr