[project @ 2001-07-03 14:13:32 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/core/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  portable
11 --
12 -- $Id: Dynamic.hs,v 1.3 2001/07/03 14:13:32 simonmar Exp $
13 --
14 -- The Dynamic interface provides basic support for dynamic types.
15 -- 
16 -- Operations for injecting values of arbitrary type into
17 -- a dynamically typed value, Dynamic, are provided, together
18 -- with operations for converting dynamic values into a concrete
19 -- (monomorphic) type.
20 -- 
21 -- The Dynamic implementation provided is closely based on code
22 -- contained in Hugs library of the same name.
23 -- 
24 -----------------------------------------------------------------------------
25
26 module Data.Dynamic
27         (
28         -- dynamic type
29           Dynamic       -- abstract, instance of: Show, Typeable
30         , toDyn         -- :: Typeable a => a -> Dynamic
31         , fromDyn       -- :: Typeable a => Dynamic -> a -> a
32         , fromDynamic   -- :: Typeable a => Dynamic -> Maybe a
33         
34         -- type representation
35
36         , Typeable(
37              typeOf)    -- :: a -> TypeRep
38
39           -- Dynamic defines Typeable instances for the following
40         -- Prelude types: [a], (), (a,b), (a,b,c), (a,b,c,d),
41         -- (a,b,c,d,e), (a->b), (Array a b), Bool, Char,
42         -- (Complex a), Double, (Either a b), Float, Handle,
43         -- Int, Integer, (IO a), (Maybe a), Ordering
44
45         , TypeRep       -- abstract, instance of: Eq, Show, Typeable
46         , TyCon         -- abstract, instance of: Eq, Show, Typeable
47
48         -- type representation constructors/operators:
49         , mkTyCon       -- :: String  -> TyCon
50         , mkAppTy       -- :: TyCon   -> [TypeRep] -> TypeRep
51         , mkFunTy       -- :: TypeRep -> TypeRep   -> TypeRep
52         , applyTy       -- :: TypeRep -> TypeRep   -> Maybe TypeRep
53
54         -- 
55         -- let fTy = mkTyCon "Foo" in show (mkAppTy (mkTyCon ",,")
56         --                                 [fTy,fTy,fTy])
57         -- 
58         -- returns "(Foo,Foo,Foo)"
59         --
60         -- The TypeRep Show instance promises to print tuple types
61         -- correctly. Tuple type constructors are specified by a 
62         -- sequence of commas, e.g., (mkTyCon ",,,,") returns
63         -- the 5-tuple tycon.
64         ) where
65
66
67 import Data.Maybe
68 import Data.Either
69
70 #ifdef __GLASGOW_HASKELL__
71 import GHC.Base
72 import GHC.Show
73 import GHC.Err
74 import GHC.Num
75 import GHC.Float
76 import GHC.IOBase
77 import GHC.Dynamic
78 #endif
79
80 #ifdef __GLASGOW_HASKELL__
81 import GHC.Prim                 ( unsafeCoerce# )
82
83 unsafeCoerce :: a -> b
84 unsafeCoerce = unsafeCoerce#
85 #endif
86
87 #include "Dynamic.h"
88
89 -- The dynamic type is represented by Dynamic, carrying
90 -- the dynamic value along with its type representation:
91
92 -- the instance just prints the type representation.
93 instance Show Dynamic where
94    showsPrec _ (Dynamic t _) = 
95           showString "<<" . 
96           showsPrec 0 t   . 
97           showString ">>"
98
99 -- Operations for going to and from Dynamic:
100
101 toDyn :: Typeable a => a -> Dynamic
102 toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
103
104 fromDyn :: Typeable a => Dynamic -> a -> a
105 fromDyn (Dynamic t v) def
106   | typeOf def == t = unsafeCoerce v
107   | otherwise       = def
108
109 fromDynamic :: Typeable a => Dynamic -> Maybe a
110 fromDynamic (Dynamic t v) =
111   case unsafeCoerce v of 
112     r | t == typeOf r -> Just r
113       | otherwise     -> Nothing
114
115 -- (Abstract) universal datatype:
116
117 instance Show TypeRep where
118   showsPrec p (App tycon tys) =
119     case tys of
120       [] -> showsPrec p tycon
121       [x] | tycon == listTc    -> showChar '[' . shows x . showChar ']'
122       xs  
123         | isTupleTyCon tycon -> showTuple tycon xs
124         | otherwise          ->
125             showParen (p > 9) $
126             showsPrec p tycon . 
127             showChar ' '      . 
128             showArgs tys
129
130   showsPrec p (Fun f a) =
131      showParen (p > 8) $
132      showsPrec 9 f . showString " -> " . showsPrec 8 a
133
134 -- To make it possible to convert values with user-defined types
135 -- into type Dynamic, we need a systematic way of getting
136 -- the type representation of an arbitrary type. A type
137 -- class provides just the ticket,
138
139 class Typeable a where
140   typeOf :: a -> TypeRep
141
142 -- NOTE: The argument to the overloaded `typeOf' is only
143 -- used to carry type information, and Typeable instances
144 -- should *never* *ever* look at its value.
145
146 isTupleTyCon :: TyCon -> Bool
147 isTupleTyCon (TyCon _ (',':_)) = True
148 isTupleTyCon _                 = False
149
150 instance Show TyCon where
151   showsPrec _ (TyCon _ s) = showString s
152
153 -- If we enforce the restriction that there is only one
154 -- @TyCon@ for a type & it is shared among all its uses,
155 -- we can map them onto Ints very simply. The benefit is,
156 -- of course, that @TyCon@s can then be compared efficiently.
157
158 -- Provided the implementor of other @Typeable@ instances
159 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
160 -- this will work. 
161
162 -- If this constraint does turn out to be a sore thumb, changing
163 -- the Eq instance for TyCons is trivial.
164
165 mkTyCon :: String -> TyCon
166 mkTyCon str = unsafePerformIO $ do
167    v <- readIORef uni
168    writeIORef uni (v+1)
169    return (TyCon v str)
170
171 {-# NOINLINE uni #-}
172 uni :: IORef Int
173 uni = unsafePerformIO ( newIORef 0 )
174
175 -- Some (Show.TypeRep) helpers:
176
177 showArgs :: Show a => [a] -> ShowS
178 showArgs [] = id
179 showArgs [a] = showsPrec 10 a
180 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
181
182 showTuple :: TyCon -> [TypeRep] -> ShowS
183 showTuple (TyCon _ str) args = showChar '(' . go str args
184  where
185   go [] [a] = showsPrec 10 a . showChar ')'
186   go _  []  = showChar ')' -- a failure condition, really.
187   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
188   go _ _   = showChar ')'
189
190
191 mkAppTy  :: TyCon   -> [TypeRep] -> TypeRep
192 mkAppTy tyc args = App tyc args
193
194 mkFunTy  :: TypeRep -> TypeRep   -> TypeRep
195 mkFunTy f a = Fun f a
196
197 -- Auxillary functions
198
199 -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
200 dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
201 dynApply (Dynamic t1 f) (Dynamic t2 x) =
202   case applyTy t1 t2 of
203     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
204     Nothing -> Nothing
205
206 dynApp :: Dynamic -> Dynamic -> Dynamic
207 dynApp f x = case dynApply f x of 
208              Just r -> r
209              Nothing -> error ("Type error in dynamic application.\n" ++
210                                "Can't apply function " ++ show f ++
211                                " to argument " ++ show x)
212
213 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
214 applyTy (Fun t1 t2) t3
215   | t1 == t3    = Just t2
216 applyTy _ _     = Nothing
217
218 -- Prelude types
219
220 listTc :: TyCon
221 listTc = mkTyCon "[]"
222
223 instance Typeable a => Typeable [a] where
224   typeOf ls = mkAppTy listTc [typeOf ((undefined:: [a] -> a) ls)]
225
226 unitTc :: TyCon
227 unitTc = mkTyCon "()"
228
229 instance Typeable () where
230   typeOf _ = mkAppTy unitTc []
231
232 tup2Tc :: TyCon
233 tup2Tc = mkTyCon ","
234
235 instance (Typeable a, Typeable b) => Typeable (a,b) where
236   typeOf tu = mkAppTy tup2Tc [typeOf ((undefined :: (a,b) -> a) tu),
237                               typeOf ((undefined :: (a,b) -> b) tu)]
238
239 tup3Tc :: TyCon
240 tup3Tc = mkTyCon ",,"
241
242 instance ( Typeable a , Typeable b , Typeable c) => Typeable (a,b,c) where
243   typeOf tu = mkAppTy tup3Tc [typeOf ((undefined :: (a,b,c) -> a) tu),
244                               typeOf ((undefined :: (a,b,c) -> b) tu),
245                               typeOf ((undefined :: (a,b,c) -> c) tu)]
246
247 tup4Tc :: TyCon
248 tup4Tc = mkTyCon ",,,"
249
250 instance ( Typeable a
251          , Typeable b
252          , Typeable c
253          , Typeable d) => Typeable (a,b,c,d) where
254   typeOf tu = mkAppTy tup4Tc [typeOf ((undefined :: (a,b,c,d) -> a) tu),
255                               typeOf ((undefined :: (a,b,c,d) -> b) tu),
256                               typeOf ((undefined :: (a,b,c,d) -> c) tu),
257                               typeOf ((undefined :: (a,b,c,d) -> d) tu)]
258
259 tup5Tc :: TyCon
260 tup5Tc = mkTyCon ",,,,"
261
262 instance ( Typeable a
263          , Typeable b
264          , Typeable c
265          , Typeable d
266          , Typeable e) => Typeable (a,b,c,d,e) where
267   typeOf tu = mkAppTy tup5Tc [typeOf ((undefined :: (a,b,c,d,e) -> a) tu),
268                               typeOf ((undefined :: (a,b,c,d,e) -> b) tu),
269                               typeOf ((undefined :: (a,b,c,d,e) -> c) tu),
270                               typeOf ((undefined :: (a,b,c,d,e) -> d) tu),
271                               typeOf ((undefined :: (a,b,c,d,e) -> e) tu)]
272
273 instance (Typeable a, Typeable b) => Typeable (a -> b) where
274   typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f))
275                      (typeOf ((undefined :: (a -> b) -> b) f))
276
277 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
278 INSTANCE_TYPEABLE0(Char,charTc,"Char")
279 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
280 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
281 INSTANCE_TYPEABLE0(Int,intTc,"Int")
282 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
283 INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
284 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
285 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
286 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
287
288 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
289 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
290 INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")