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