[project @ 2001-12-21 15:07:20 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.4 2001/12/21 15:07:21 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 unsafeCoerce :: a -> b
82 unsafeCoerce = unsafeCoerce#
83 #endif
84
85 #include "Dynamic.h"
86
87 -- The dynamic type is represented by Dynamic, carrying
88 -- the dynamic value along with its type representation:
89
90 -- the instance just prints the type representation.
91 instance Show Dynamic where
92    showsPrec _ (Dynamic t _) = 
93           showString "<<" . 
94           showsPrec 0 t   . 
95           showString ">>"
96
97 -- Operations for going to and from Dynamic:
98
99 toDyn :: Typeable a => a -> Dynamic
100 toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
101
102 fromDyn :: Typeable a => Dynamic -> a -> a
103 fromDyn (Dynamic t v) def
104   | typeOf def == t = unsafeCoerce v
105   | otherwise       = def
106
107 fromDynamic :: Typeable a => Dynamic -> Maybe a
108 fromDynamic (Dynamic t v) =
109   case unsafeCoerce v of 
110     r | t == typeOf r -> Just r
111       | otherwise     -> Nothing
112
113 -- (Abstract) universal datatype:
114
115 instance Show TypeRep where
116   showsPrec p (App tycon tys) =
117     case tys of
118       [] -> showsPrec p tycon
119       [x] | tycon == listTc    -> showChar '[' . shows x . showChar ']'
120       xs  
121         | isTupleTyCon tycon -> showTuple tycon xs
122         | otherwise          ->
123             showParen (p > 9) $
124             showsPrec p tycon . 
125             showChar ' '      . 
126             showArgs tys
127
128   showsPrec p (Fun f a) =
129      showParen (p > 8) $
130      showsPrec 9 f . showString " -> " . showsPrec 8 a
131
132 -- To make it possible to convert values with user-defined types
133 -- into type Dynamic, we need a systematic way of getting
134 -- the type representation of an arbitrary type. A type
135 -- class provides just the ticket,
136
137 class Typeable a where
138   typeOf :: a -> TypeRep
139
140 -- NOTE: The argument to the overloaded `typeOf' is only
141 -- used to carry type information, and Typeable instances
142 -- should *never* *ever* look at its value.
143
144 isTupleTyCon :: TyCon -> Bool
145 isTupleTyCon (TyCon _ (',':_)) = True
146 isTupleTyCon _                 = False
147
148 instance Show TyCon where
149   showsPrec _ (TyCon _ s) = showString s
150
151 -- If we enforce the restriction that there is only one
152 -- @TyCon@ for a type & it is shared among all its uses,
153 -- we can map them onto Ints very simply. The benefit is,
154 -- of course, that @TyCon@s can then be compared efficiently.
155
156 -- Provided the implementor of other @Typeable@ instances
157 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
158 -- this will work. 
159
160 -- If this constraint does turn out to be a sore thumb, changing
161 -- the Eq instance for TyCons is trivial.
162
163 mkTyCon :: String -> TyCon
164 mkTyCon str = unsafePerformIO $ do
165    v <- readIORef uni
166    writeIORef uni (v+1)
167    return (TyCon v str)
168
169 {-# NOINLINE uni #-}
170 uni :: IORef Int
171 uni = unsafePerformIO ( newIORef 0 )
172
173 -- Some (Show.TypeRep) helpers:
174
175 showArgs :: Show a => [a] -> ShowS
176 showArgs [] = id
177 showArgs [a] = showsPrec 10 a
178 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
179
180 showTuple :: TyCon -> [TypeRep] -> ShowS
181 showTuple (TyCon _ str) args = showChar '(' . go str args
182  where
183   go [] [a] = showsPrec 10 a . showChar ')'
184   go _  []  = showChar ')' -- a failure condition, really.
185   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
186   go _ _   = showChar ')'
187
188
189 mkAppTy  :: TyCon   -> [TypeRep] -> TypeRep
190 mkAppTy tyc args = App tyc args
191
192 mkFunTy  :: TypeRep -> TypeRep   -> TypeRep
193 mkFunTy f a = Fun f a
194
195 -- Auxillary functions
196
197 -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
198 dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
199 dynApply (Dynamic t1 f) (Dynamic t2 x) =
200   case applyTy t1 t2 of
201     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
202     Nothing -> Nothing
203
204 dynApp :: Dynamic -> Dynamic -> Dynamic
205 dynApp f x = case dynApply f x of 
206              Just r -> r
207              Nothing -> error ("Type error in dynamic application.\n" ++
208                                "Can't apply function " ++ show f ++
209                                " to argument " ++ show x)
210
211 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
212 applyTy (Fun t1 t2) t3
213   | t1 == t3    = Just t2
214 applyTy _ _     = Nothing
215
216 -- Prelude types
217
218 listTc :: TyCon
219 listTc = mkTyCon "[]"
220
221 instance Typeable a => Typeable [a] where
222   typeOf ls = mkAppTy listTc [typeOf ((undefined:: [a] -> a) ls)]
223
224 unitTc :: TyCon
225 unitTc = mkTyCon "()"
226
227 instance Typeable () where
228   typeOf _ = mkAppTy unitTc []
229
230 tup2Tc :: TyCon
231 tup2Tc = mkTyCon ","
232
233 instance (Typeable a, Typeable b) => Typeable (a,b) where
234   typeOf tu = mkAppTy tup2Tc [typeOf ((undefined :: (a,b) -> a) tu),
235                               typeOf ((undefined :: (a,b) -> b) tu)]
236
237 tup3Tc :: TyCon
238 tup3Tc = mkTyCon ",,"
239
240 instance ( Typeable a , Typeable b , Typeable c) => Typeable (a,b,c) where
241   typeOf tu = mkAppTy tup3Tc [typeOf ((undefined :: (a,b,c) -> a) tu),
242                               typeOf ((undefined :: (a,b,c) -> b) tu),
243                               typeOf ((undefined :: (a,b,c) -> c) tu)]
244
245 tup4Tc :: TyCon
246 tup4Tc = mkTyCon ",,,"
247
248 instance ( Typeable a
249          , Typeable b
250          , Typeable c
251          , Typeable d) => Typeable (a,b,c,d) where
252   typeOf tu = mkAppTy tup4Tc [typeOf ((undefined :: (a,b,c,d) -> a) tu),
253                               typeOf ((undefined :: (a,b,c,d) -> b) tu),
254                               typeOf ((undefined :: (a,b,c,d) -> c) tu),
255                               typeOf ((undefined :: (a,b,c,d) -> d) tu)]
256
257 tup5Tc :: TyCon
258 tup5Tc = mkTyCon ",,,,"
259
260 instance ( Typeable a
261          , Typeable b
262          , Typeable c
263          , Typeable d
264          , Typeable e) => Typeable (a,b,c,d,e) where
265   typeOf tu = mkAppTy tup5Tc [typeOf ((undefined :: (a,b,c,d,e) -> a) tu),
266                               typeOf ((undefined :: (a,b,c,d,e) -> b) tu),
267                               typeOf ((undefined :: (a,b,c,d,e) -> c) tu),
268                               typeOf ((undefined :: (a,b,c,d,e) -> d) tu),
269                               typeOf ((undefined :: (a,b,c,d,e) -> e) tu)]
270
271 instance (Typeable a, Typeable b) => Typeable (a -> b) where
272   typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f))
273                      (typeOf ((undefined :: (a -> b) -> b) f))
274
275 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
276 INSTANCE_TYPEABLE0(Char,charTc,"Char")
277 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
278 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
279 INSTANCE_TYPEABLE0(Int,intTc,"Int")
280 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
281 INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
282 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
283 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
284 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
285
286 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
287 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
288 INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")