[project @ 2003-07-22 14:38:02 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         cast,                   -- :: (Typeable a, Typeable b) => a -> Maybe b
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 qualified Data.HashTable as HT
66 import Data.Maybe
67 import Data.Either
68 import Data.Int
69 import Data.Word
70 import Data.List( foldl )
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.Real( rem )
79 import GHC.IOBase
80 import GHC.Ptr          -- So we can give Typeable instance for Ptr
81 import GHC.Stable       -- So we can give Typeable instance for StablePtr
82 #endif
83
84 #ifdef __HUGS__
85 import Hugs.Prelude
86 import Hugs.IO
87 import Hugs.IORef
88 import Hugs.IOExts
89 #endif
90
91 #ifdef __GLASGOW_HASKELL__
92 unsafeCoerce :: a -> b
93 unsafeCoerce = unsafeCoerce#
94 #endif
95
96 #ifdef __NHC__
97 import NonStdUnsafeCoerce (unsafeCoerce)
98 import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
99 #else
100 #include "Dynamic.h"
101 #endif
102
103 -------------------------------------------------------------
104 --
105 --              The type Dynamic
106 --
107 -------------------------------------------------------------
108
109 {-|
110   A value of type 'Dynamic' is an object encapsulated together with its type.
111
112   A 'Dynamic' may only represent a monomorphic value; an attempt to
113   create a value of type 'Dynamic' from a polymorphically-typed
114   expression will result in an ambiguity error (see 'toDyn').
115
116   'Show'ing a value of type 'Dynamic' returns a pretty-printed representation
117   of the object\'s type; useful for debugging.
118 -}
119 #ifndef __HUGS__
120 data Dynamic = Dynamic TypeRep Obj
121 #endif
122
123 instance Show Dynamic where
124    -- the instance just prints the type representation.
125    showsPrec _ (Dynamic t _) = 
126           showString "<<" . 
127           showsPrec 0 t   . 
128           showString ">>"
129
130 #ifdef __GLASGOW_HASKELL__
131 type Obj = forall a . a
132  -- Dummy type to hold the dynamically typed value.
133  --
134  -- In GHC's new eval/apply execution model this type must
135  -- be polymorphic.  It can't be a constructor, because then
136  -- GHC will use the constructor convention when evaluating it,
137  -- and this will go wrong if the object is really a function.  On
138  -- the other hand, if we use a polymorphic type, GHC will use
139  -- a fallback convention for evaluating it that works for all types.
140  -- (using a function type here would also work).
141 #elif !defined(__HUGS__)
142 data Obj = Obj
143 #endif
144
145 -- | Converts an arbitrary value into an object of type 'Dynamic'.  
146 --
147 -- The type of the object must be an instance of 'Typeable', which
148 -- ensures that only monomorphically-typed objects may be converted to
149 -- 'Dynamic'.  To convert a polymorphic object into 'Dynamic', give it
150 -- a monomorphic type signature.  For example:
151 --
152 -- >    toDyn (id :: Int -> Int)
153 --
154 toDyn :: Typeable a => a -> Dynamic
155 toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
156
157 -- | Converts a 'Dynamic' object back into an ordinary Haskell value of
158 -- the correct type.  See also 'fromDynamic'.
159 fromDyn :: Typeable a
160         => Dynamic      -- ^ the dynamically-typed object
161         -> a            -- ^ a default value 
162         -> a            -- ^ returns: the value of the first argument, if
163                         -- it has the correct type, otherwise the value of
164                         -- the second argument.
165 fromDyn (Dynamic t v) def
166   | typeOf def == t = unsafeCoerce v
167   | otherwise       = def
168
169 -- | Converts a 'Dynamic' object back into an ordinary Haskell value of
170 -- the correct type.  See also 'fromDyn'.
171 fromDynamic
172         :: Typeable a
173         => Dynamic      -- ^ the dynamically-typed object
174         -> Maybe a      -- ^ returns: @'Just' a@, if the dyanmically-typed
175                         -- object has the correct type (and @a@ is its value), 
176                         -- or 'Nothing' otherwise.
177 fromDynamic (Dynamic t v) =
178   case unsafeCoerce v of 
179     r | t == typeOf r -> Just r
180       | otherwise     -> Nothing
181
182 -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
183 dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
184 dynApply (Dynamic t1 f) (Dynamic t2 x) =
185   case applyTy t1 t2 of
186     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
187     Nothing -> Nothing
188
189 dynApp :: Dynamic -> Dynamic -> Dynamic
190 dynApp f x = case dynApply f x of 
191              Just r -> r
192              Nothing -> error ("Type error in dynamic application.\n" ++
193                                "Can't apply function " ++ show f ++
194                                " to argument " ++ show x)
195
196 #ifndef __HUGS__
197 -------------------------------------------------------------
198 --
199 --              Type representations
200 --
201 -------------------------------------------------------------
202
203 -- | A concrete representation of a (monomorphic) type.  'TypeRep'
204 -- supports reasonably efficient equality.
205 data TypeRep = TypeRep !Key TyCon [TypeRep] 
206
207 -- Compare keys for equality
208 instance Eq TypeRep where
209   (TypeRep k1 _ _) == (TypeRep k2 _ _) = k1 == k2
210
211 -- | An abstract representation of a type constructor.  'TyCon' objects can
212 -- be built using 'mkTyCon'.
213 data TyCon = TyCon !Key String
214
215 instance Eq TyCon where
216   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
217 #endif
218
219 ----------------- Type-safe cast ------------------
220
221 -- | The type-safe cast operation
222 cast :: (Typeable a, Typeable b) => a -> Maybe b
223 cast x = r
224        where
225          r = if typeOf x == typeOf (fromJust r) then
226                         Just (unsafeCoerce x)
227              else
228                         Nothing
229
230 ----------------- Construction --------------------
231
232 -- | Applies a type constructor to a sequence of types
233 mkAppTy  :: TyCon -> [TypeRep] -> TypeRep
234 mkAppTy tc@(TyCon tc_k _) args 
235   = TypeRep (appKeys tc_k arg_ks) tc args
236   where
237     arg_ks = [k | TypeRep k _ _ <- args]
238
239 funTc :: TyCon
240 funTc = mkTyCon "->"
241
242 -- | A special case of 'mkAppTy', which applies the function 
243 -- type constructor to a pair of types.
244 mkFunTy  :: TypeRep -> TypeRep -> TypeRep
245 mkFunTy f a = mkAppTy funTc [f,a]
246
247 -- | Applies a type to a function type.  Returns: @'Just' u@ if the
248 -- first argument represents a function of type @t -> u@ and the
249 -- second argument represents a function of type @t@.  Otherwise,
250 -- returns 'Nothing'.
251 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
252 applyTy (TypeRep _ tc [t1,t2]) t3
253   | tc == funTc && t1 == t3     = Just t2
254 applyTy _ _                     = Nothing
255
256 -- If we enforce the restriction that there is only one
257 -- @TyCon@ for a type & it is shared among all its uses,
258 -- we can map them onto Ints very simply. The benefit is,
259 -- of course, that @TyCon@s can then be compared efficiently.
260
261 -- Provided the implementor of other @Typeable@ instances
262 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
263 -- this will work. 
264
265 -- If this constraint does turn out to be a sore thumb, changing
266 -- the Eq instance for TyCons is trivial.
267
268 -- | Builds a 'TyCon' object representing a type constructor.  An
269 -- implementation of "Data.Dynamic" should ensure that the following holds:
270 --
271 -- >  mkTyCon "a" == mkTyCon "a"
272 --
273 mkTyCon :: String       -- ^ the name of the type constructor (should be unique
274                         -- in the program, so it might be wise to use the
275                         -- fully qualified name).
276         -> TyCon        -- ^ A unique 'TyCon' object
277 mkTyCon str = TyCon (mkTyConKey str) str
278
279
280 ----------------- Showing TypeReps --------------------
281
282 instance Show TypeRep where
283   showsPrec p (TypeRep _ tycon tys) =
284     case tys of
285       [] -> showsPrec p tycon
286       [x]   | tycon == listTc -> showChar '[' . shows x . showChar ']'
287       [a,r] | tycon == funTc  -> showParen (p > 8) $
288                                  showsPrec 9 a . showString " -> " . showsPrec 8 r
289       xs | isTupleTyCon tycon -> showTuple tycon xs
290          | otherwise         ->
291             showParen (p > 9) $
292             showsPrec p tycon . 
293             showChar ' '      . 
294             showArgs tys
295
296 instance Show TyCon where
297   showsPrec _ (TyCon _ s) = showString s
298
299 isTupleTyCon :: TyCon -> Bool
300 isTupleTyCon (TyCon _ (',':_)) = True
301 isTupleTyCon _                 = False
302
303 -- Some (Show.TypeRep) helpers:
304
305 showArgs :: Show a => [a] -> ShowS
306 showArgs [] = id
307 showArgs [a] = showsPrec 10 a
308 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
309
310 showTuple :: TyCon -> [TypeRep] -> ShowS
311 showTuple (TyCon _ str) args = showChar '(' . go str args
312  where
313   go [] [a] = showsPrec 10 a . showChar ')'
314   go _  []  = showChar ')' -- a failure condition, really.
315   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
316   go _ _   = showChar ')'
317
318
319
320 -------------------------------------------------------------
321 --
322 --      The Typeable class and some instances
323 --
324 -------------------------------------------------------------
325
326 -- | The class 'Typeable' allows a concrete representation of a type to
327 -- be calculated.
328 class Typeable a where
329   typeOf :: a -> TypeRep
330   -- ^ Takes a value of type @a@ and returns a concrete representation
331   -- of that type.  The /value/ of the argument should be ignored by
332   -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
333   -- the argument.
334
335 -- Prelude types
336 listTc :: TyCon
337 listTc = mkTyCon "[]"
338
339 instance Typeable a => Typeable [a] where
340   typeOf ls = mkAppTy listTc [typeOf ((undefined :: [a] -> a) ls)]
341         -- In GHC we can say
342         --      typeOf (undefined :: a)
343         -- using scoped type variables, but we use the 
344         -- more verbose form here, for compatibility with Hugs
345
346 unitTc :: TyCon
347 unitTc = mkTyCon "()"
348
349 instance Typeable () where
350   typeOf _ = mkAppTy unitTc []
351
352 tup2Tc :: TyCon
353 tup2Tc = mkTyCon ","
354
355 instance (Typeable a, Typeable b) => Typeable (a,b) where
356   typeOf tu = mkAppTy tup2Tc [typeOf ((undefined :: (a,b) -> a) tu),
357                               typeOf ((undefined :: (a,b) -> b) tu)]
358
359 tup3Tc :: TyCon
360 tup3Tc = mkTyCon ",,"
361
362 instance ( Typeable a , Typeable b , Typeable c) => Typeable (a,b,c) where
363   typeOf tu = mkAppTy tup3Tc [typeOf ((undefined :: (a,b,c) -> a) tu),
364                               typeOf ((undefined :: (a,b,c) -> b) tu),
365                               typeOf ((undefined :: (a,b,c) -> c) tu)]
366
367 tup4Tc :: TyCon
368 tup4Tc = mkTyCon ",,,"
369
370 instance ( Typeable a
371          , Typeable b
372          , Typeable c
373          , Typeable d) => Typeable (a,b,c,d) where
374   typeOf tu = mkAppTy tup4Tc [typeOf ((undefined :: (a,b,c,d) -> a) tu),
375                               typeOf ((undefined :: (a,b,c,d) -> b) tu),
376                               typeOf ((undefined :: (a,b,c,d) -> c) tu),
377                               typeOf ((undefined :: (a,b,c,d) -> d) tu)]
378 tup5Tc :: TyCon
379 tup5Tc = mkTyCon ",,,,"
380
381 instance ( Typeable a
382          , Typeable b
383          , Typeable c
384          , Typeable d
385          , Typeable e) => Typeable (a,b,c,d,e) where
386   typeOf tu = mkAppTy tup5Tc [typeOf ((undefined :: (a,b,c,d,e) -> a) tu),
387                               typeOf ((undefined :: (a,b,c,d,e) -> b) tu),
388                               typeOf ((undefined :: (a,b,c,d,e) -> c) tu),
389                               typeOf ((undefined :: (a,b,c,d,e) -> d) tu),
390                               typeOf ((undefined :: (a,b,c,d,e) -> e) tu)]
391
392 instance (Typeable a, Typeable b) => Typeable (a -> b) where
393   typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f))
394                      (typeOf ((undefined :: (a -> b) -> b) f))
395
396 #ifndef __NHC__
397 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
398 INSTANCE_TYPEABLE0(Char,charTc,"Char")
399 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
400 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
401 INSTANCE_TYPEABLE0(Int,intTc,"Int")
402 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
403 INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
404 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
405 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
406 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
407 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
408 INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
409 INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
410
411 INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
412 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
413 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
414 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
415
416 INSTANCE_TYPEABLE0(Word8,word8Tc, "Word8" )
417 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
418 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
419 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
420
421 INSTANCE_TYPEABLE0(TyCon,tyconTc,    "TyCon")
422 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
423 INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")
424
425 #include "Dynamic.h"
426 INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
427 #endif
428
429 ---------------------------------------------
430 --
431 --              Internals 
432 --
433 ---------------------------------------------
434
435 #ifndef __HUGS__
436 newtype Key = Key Int deriving( Eq )
437 #endif
438
439 data KeyPr = KeyPr !Key !Key deriving( Eq )
440
441 hashKP :: KeyPr -> Int32
442 hashKP (KeyPr (Key k1) (Key k2)) = (HT.hashInt k1 + HT.hashInt k2) `rem` HT.prime
443
444 data Cache = Cache { next_key :: !(IORef Key),
445                      tc_tbl   :: !(HT.HashTable String Key),
446                      ap_tbl   :: !(HT.HashTable KeyPr Key) }
447
448 {-# NOINLINE cache #-}
449 cache :: Cache
450 cache = unsafePerformIO $ do
451                 empty_tc_tbl <- HT.new (==) HT.hashString
452                 empty_ap_tbl <- HT.new (==) hashKP
453                 key_loc      <- newIORef (Key 1) 
454                 return (Cache { next_key = key_loc,
455                                 tc_tbl = empty_tc_tbl, 
456                                 ap_tbl = empty_ap_tbl })
457
458 newKey :: IORef Key -> IO Key
459 newKey kloc = do { k@(Key i) <- readIORef kloc ;
460                    writeIORef kloc (Key (i+1)) ;
461                    return k }
462
463 mkTyConKey :: String -> Key
464 mkTyConKey str 
465   = unsafePerformIO $ do
466         let Cache {next_key = kloc, tc_tbl = tbl} = cache
467         mb_k <- HT.lookup tbl str
468         case mb_k of
469           Just k  -> return k
470           Nothing -> do { k <- newKey kloc ;
471                           HT.insert tbl str k ;
472                           return k }
473
474 appKey :: Key -> Key -> Key
475 appKey k1 k2
476   = unsafePerformIO $ do
477         let Cache {next_key = kloc, ap_tbl = tbl} = cache
478         mb_k <- HT.lookup tbl kpr
479         case mb_k of
480           Just k  -> return k
481           Nothing -> do { k <- newKey kloc ;
482                           HT.insert tbl kpr k ;
483                           return k }
484   where
485     kpr = KeyPr k1 k2
486
487 appKeys :: Key -> [Key] -> Key
488 appKeys k ks = foldl appKey k ks
489
490
491
492
493