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