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