[project @ 2003-01-23 17:45:40 by ross]
[ghc-base.git] / Data / Dynamic.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
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         -- * The @Dynamic@ type
24         Dynamic,        -- abstract, instance of: Show, Typeable
25
26         -- * Converting to and from @Dynamic@
27         toDyn,          -- :: Typeable a => a -> Dynamic
28         fromDyn,        -- :: Typeable a => Dynamic -> a -> a
29         fromDynamic,    -- :: Typeable a => Dynamic -> Maybe a
30         
31         -- * Applying functions of dynamic type
32         dynApply,
33         dynApp,
34
35         -- * Concrete Type Representations
36         
37         -- | This section is useful if you need to define your own
38         -- instances of 'Typeable'.
39
40         Typeable(
41              typeOf),   -- :: a -> TypeRep
42
43         -- ** Building concrete type representations
44         TypeRep,        -- abstract, instance of: Eq, Show, Typeable
45         TyCon,          -- abstract, instance of: Eq, Show, Typeable
46
47         mkTyCon,        -- :: String  -> TyCon
48         mkAppTy,        -- :: TyCon   -> [TypeRep] -> TypeRep
49         mkFunTy,        -- :: TypeRep -> TypeRep   -> TypeRep
50         applyTy,        -- :: TypeRep -> TypeRep   -> Maybe TypeRep
51
52         -- 
53         -- let fTy = mkTyCon "Foo" in show (mkAppTy (mkTyCon ",,")
54         --                                 [fTy,fTy,fTy])
55         -- 
56         -- returns "(Foo,Foo,Foo)"
57         --
58         -- The TypeRep Show instance promises to print tuple types
59         -- correctly. Tuple type constructors are specified by a 
60         -- sequence of commas, e.g., (mkTyCon ",,,,") returns
61         -- the 5-tuple tycon.
62         ) where
63
64
65 import Data.Maybe
66 import Data.Either
67 import Data.Int
68 import Data.Word
69 import Foreign.Ptr
70 import Foreign.StablePtr
71
72 #ifdef __GLASGOW_HASKELL__
73 import GHC.Base
74 import GHC.Show
75 import GHC.Err
76 import GHC.Num
77 import GHC.Float
78 import GHC.IOBase
79 #endif
80
81 #ifdef __HUGS__
82 import Hugs.Prelude
83 import Hugs.IO
84 import Hugs.IORef
85 import Hugs.IOExts
86 #endif
87
88 #ifdef __GLASGOW_HASKELL__
89 unsafeCoerce :: a -> b
90 unsafeCoerce = unsafeCoerce#
91 #endif
92
93 #ifdef __NHC__
94 import NonStdUnsafeCoerce (unsafeCoerce)
95 import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
96 #else
97 #include "Dynamic.h"
98 #endif
99
100 {-|
101   A value of type 'Dynamic' is an object encapsulated together with its type.
102
103   A 'Dynamic' may only represent a monomorphic value; an attempt to
104   create a value of type 'Dynamic' from a polymorphically-typed
105   expression will result in an ambiguity error (see 'toDyn').
106
107   'Show'ing a value of type 'Dynamic' returns a pretty-printed representation
108   of the object\'s type; useful for debugging.
109 -}
110 #ifndef __HUGS__
111 data Dynamic = Dynamic TypeRep Obj
112 #endif
113
114 instance Show Dynamic where
115    -- the instance just prints the type representation.
116    showsPrec _ (Dynamic t _) = 
117           showString "<<" . 
118           showsPrec 0 t   . 
119           showString ">>"
120
121 #ifdef __GLASGOW_HASKELL__
122 type Obj = forall a . a
123  -- Dummy type to hold the dynamically typed value.
124  --
125  -- In GHC's new eval/apply execution model this type must
126  -- be polymorphic.  It can't be a constructor, because then
127  -- GHC will use the constructor convention when evaluating it,
128  -- and this will go wrong if the object is really a function.  On
129  -- the other hand, if we use a polymorphic type, GHC will use
130  -- a fallback convention for evaluating it that works for all types.
131  -- (using a function type here would also work).
132 #elif !defined(__HUGS__)
133 data Obj = Obj
134 #endif
135
136 -- | A concrete representation of a (monomorphic) type.  'TypeRep'
137 -- supports reasonably efficient equality.
138 #ifndef __HUGS__
139 data TypeRep
140  = App TyCon   [TypeRep] 
141  | Fun TypeRep TypeRep
142    deriving ( Eq )
143 #endif
144
145 instance Show TypeRep where
146   showsPrec p (App tycon tys) =
147     case tys of
148       [] -> showsPrec p tycon
149       [x] | tycon == listTc    -> showChar '[' . shows x . showChar ']'
150       xs  
151         | isTupleTyCon tycon -> showTuple tycon xs
152         | otherwise          ->
153             showParen (p > 9) $
154             showsPrec p tycon . 
155             showChar ' '      . 
156             showArgs tys
157
158   showsPrec p (Fun f a) =
159      showParen (p > 8) $
160      showsPrec 9 f . showString " -> " . showsPrec 8 a
161
162 -- | An abstract representation of a type constructor.  'TyCon' objects can
163 -- be built using 'mkTyCon'.
164 #ifndef __HUGS__
165 data TyCon = TyCon Int String
166
167 instance Eq TyCon where
168   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
169 #endif
170
171 instance Show TyCon where
172   showsPrec _ (TyCon _ s) = showString s
173
174
175 -- | Converts an arbitrary value into an object of type 'Dynamic'.  
176 --
177 -- The type of the object must be an instance of 'Typeable', which
178 -- ensures that only monomorphically-typed objects may be converted to
179 -- 'Dynamic'.  To convert a polymorphic object into 'Dynamic', give it
180 -- a monomorphic type signature.  For example:
181 --
182 -- >    toDyn (id :: Int -> Int)
183 --
184 toDyn :: Typeable a => a -> Dynamic
185 toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
186
187 -- | Converts a 'Dynamic' object back into an ordinary Haskell value of
188 -- the correct type.  See also 'fromDynamic'.
189 fromDyn :: Typeable a
190         => Dynamic      -- ^ the dynamically-typed object
191         -> a            -- ^ a default value 
192         -> a            -- ^ returns: the value of the first argument, if
193                         -- it has the correct type, otherwise the value of
194                         -- the second argument.
195 fromDyn (Dynamic t v) def
196   | typeOf def == t = unsafeCoerce v
197   | otherwise       = def
198
199 -- | Converts a 'Dynamic' object back into an ordinary Haskell value of
200 -- the correct type.  See also 'fromDyn'.
201 fromDynamic
202         :: Typeable a
203         => Dynamic      -- ^ the dynamically-typed object
204         -> Maybe a      -- ^ returns: @'Just' a@, if the dyanmically-typed
205                         -- object has the correct type (and @a@ is its value), 
206                         -- or 'Nothing' otherwise.
207 fromDynamic (Dynamic t v) =
208   case unsafeCoerce v of 
209     r | t == typeOf r -> Just r
210       | otherwise     -> Nothing
211
212 -- | The class 'Typeable' allows a concrete representation of a type to
213 -- be calculated.
214 class Typeable a where
215   typeOf :: a -> TypeRep
216   -- ^ Takes a value of type @a@ and returns a concrete representation
217   -- of that type.  The /value/ of the argument should be ignored by
218   -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
219   -- the argument.
220
221 isTupleTyCon :: TyCon -> Bool
222 isTupleTyCon (TyCon _ (',':_)) = True
223 isTupleTyCon _                 = False
224
225 -- If we enforce the restriction that there is only one
226 -- @TyCon@ for a type & it is shared among all its uses,
227 -- we can map them onto Ints very simply. The benefit is,
228 -- of course, that @TyCon@s can then be compared efficiently.
229
230 -- Provided the implementor of other @Typeable@ instances
231 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
232 -- this will work. 
233
234 -- If this constraint does turn out to be a sore thumb, changing
235 -- the Eq instance for TyCons is trivial.
236
237 -- | Builds a 'TyCon' object representing a type constructor.  An
238 -- implementation of "Data.Dynamic" should ensure that the following holds:
239 --
240 -- >  mkTyCon "a" == mkTyCon "a"
241 --
242 -- NOTE: GHC\'s implementation is quite hacky, and the above equation
243 -- does not necessarily hold.  For defining your own instances of
244 -- 'Typeable', try to ensure that only one call to 'mkTyCon' exists
245 -- for each type constructor (put it at the top level, and annotate the
246 -- corresponding definition with a @NOINLINE@ pragma).
247 mkTyCon
248         :: String       -- ^ the name of the type constructor (should be unique
249                         -- in the program, so it might be wise to use the
250                         -- fully qualified name).
251         -> TyCon        -- ^ A unique 'TyCon' object
252 mkTyCon str = unsafePerformIO $ do
253    v <- readIORef uni
254    writeIORef uni (v+1)
255    return (TyCon v str)
256
257 {-# NOINLINE uni #-}
258 uni :: IORef Int
259 uni = unsafePerformIO ( newIORef 0 )
260
261 -- Some (Show.TypeRep) helpers:
262
263 showArgs :: Show a => [a] -> ShowS
264 showArgs [] = id
265 showArgs [a] = showsPrec 10 a
266 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
267
268 showTuple :: TyCon -> [TypeRep] -> ShowS
269 showTuple (TyCon _ str) args = showChar '(' . go str args
270  where
271   go [] [a] = showsPrec 10 a . showChar ')'
272   go _  []  = showChar ')' -- a failure condition, really.
273   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
274   go _ _   = showChar ')'
275
276
277 -- | Applies a type constructor to a sequence of types
278 mkAppTy  :: TyCon   -> [TypeRep] -> TypeRep
279 mkAppTy tyc args = App tyc args
280
281 -- | A special case of 'mkAppTy', which applies the function type constructor to
282 -- a pair of types.
283 mkFunTy  :: TypeRep -> TypeRep   -> TypeRep
284 mkFunTy f a = Fun f a
285
286 -- Auxillary functions
287
288 -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
289 dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
290 dynApply (Dynamic t1 f) (Dynamic t2 x) =
291   case applyTy t1 t2 of
292     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
293     Nothing -> Nothing
294
295 dynApp :: Dynamic -> Dynamic -> Dynamic
296 dynApp f x = case dynApply f x of 
297              Just r -> r
298              Nothing -> error ("Type error in dynamic application.\n" ++
299                                "Can't apply function " ++ show f ++
300                                " to argument " ++ show x)
301
302 -- | Applies a type to a function type.  Returns: @'Just' u@ if the
303 -- first argument represents a function of type @t -> u@ and the
304 -- second argument represents a function of type @t@.  Otherwise,
305 -- returns 'Nothing'.
306 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
307 applyTy (Fun t1 t2) t3
308   | t1 == t3    = Just t2
309 applyTy _ _     = Nothing
310
311 -- Prelude types
312
313 listTc :: TyCon
314 listTc = mkTyCon "[]"
315
316 instance Typeable a => Typeable [a] where
317   typeOf ls = mkAppTy listTc [typeOf ((undefined:: [a] -> a) ls)]
318
319 unitTc :: TyCon
320 unitTc = mkTyCon "()"
321
322 instance Typeable () where
323   typeOf _ = mkAppTy unitTc []
324
325 tup2Tc :: TyCon
326 tup2Tc = mkTyCon ","
327
328 instance (Typeable a, Typeable b) => Typeable (a,b) where
329   typeOf tu = mkAppTy tup2Tc [typeOf ((undefined :: (a,b) -> a) tu),
330                               typeOf ((undefined :: (a,b) -> b) tu)]
331
332 tup3Tc :: TyCon
333 tup3Tc = mkTyCon ",,"
334
335 instance ( Typeable a , Typeable b , Typeable c) => Typeable (a,b,c) where
336   typeOf tu = mkAppTy tup3Tc [typeOf ((undefined :: (a,b,c) -> a) tu),
337                               typeOf ((undefined :: (a,b,c) -> b) tu),
338                               typeOf ((undefined :: (a,b,c) -> c) tu)]
339
340 tup4Tc :: TyCon
341 tup4Tc = mkTyCon ",,,"
342
343 instance ( Typeable a
344          , Typeable b
345          , Typeable c
346          , Typeable d) => Typeable (a,b,c,d) where
347   typeOf tu = mkAppTy tup4Tc [typeOf ((undefined :: (a,b,c,d) -> a) tu),
348                               typeOf ((undefined :: (a,b,c,d) -> b) tu),
349                               typeOf ((undefined :: (a,b,c,d) -> c) tu),
350                               typeOf ((undefined :: (a,b,c,d) -> d) tu)]
351
352 tup5Tc :: TyCon
353 tup5Tc = mkTyCon ",,,,"
354
355 instance ( Typeable a
356          , Typeable b
357          , Typeable c
358          , Typeable d
359          , Typeable e) => Typeable (a,b,c,d,e) where
360   typeOf tu = mkAppTy tup5Tc [typeOf ((undefined :: (a,b,c,d,e) -> a) tu),
361                               typeOf ((undefined :: (a,b,c,d,e) -> b) tu),
362                               typeOf ((undefined :: (a,b,c,d,e) -> c) tu),
363                               typeOf ((undefined :: (a,b,c,d,e) -> d) tu),
364                               typeOf ((undefined :: (a,b,c,d,e) -> e) tu)]
365
366 instance (Typeable a, Typeable b) => Typeable (a -> b) where
367   typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f))
368                      (typeOf ((undefined :: (a -> b) -> b) f))
369
370 #ifndef __NHC__
371 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
372 INSTANCE_TYPEABLE0(Char,charTc,"Char")
373 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
374 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
375 INSTANCE_TYPEABLE0(Int,intTc,"Int")
376 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
377 INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
378 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
379 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
380 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
381 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
382 INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
383 INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
384
385 INSTANCE_TYPEABLE0(Int8,int8Tc, "Int8")
386 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
387 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
388 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
389
390 INSTANCE_TYPEABLE0(Word8,word8Tc, "Word8" )
391 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
392 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
393 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
394
395 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
396 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
397 INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")
398
399 #include "Dynamic.h"
400 INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
401 #endif