13e3550ebc115da2a0dee51080368bbd82618b98
[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 -- 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 -- The Dynamic implementation provided is closely based on code
20 -- contained in Hugs library of the same name.
21 -- 
22 -----------------------------------------------------------------------------
23
24 module Data.Dynamic
25         (
26         -- dynamic type
27           Dynamic       -- abstract, instance of: Show, Typeable
28         , toDyn         -- :: Typeable a => a -> Dynamic
29         , fromDyn       -- :: Typeable a => Dynamic -> a -> a
30         , fromDynamic   -- :: Typeable a => Dynamic -> Maybe a
31         
32         -- type representation
33
34         , Typeable(
35              typeOf)    -- :: a -> TypeRep
36
37           -- Dynamic defines Typeable instances for the following
38         -- Prelude types: [a], (), (a,b), (a,b,c), (a,b,c,d),
39         -- (a,b,c,d,e), (a->b), (Array a b), Bool, Char,
40         -- (Complex a), Double, (Either a b), Float, Handle,
41         -- Int, Integer, (IO a), (Maybe a), Ordering
42
43         , TypeRep       -- abstract, instance of: Eq, Show, Typeable
44         , TyCon         -- abstract, instance of: Eq, Show, Typeable
45
46         -- type representation constructors/operators:
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 Data.Maybe
66 import Data.Either
67 import Data.Int
68 import Data.Word
69 import Foreign.Ptr
70 import Foreign.StablePtr
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.IOBase
79 #endif
80
81 #ifdef __GLASGOW_HASKELL__
82 unsafeCoerce :: a -> b
83 unsafeCoerce = unsafeCoerce#
84 #endif
85
86 #include "Dynamic.h"
87
88 -- The dynamic type is represented by Dynamic, carrying
89 -- the dynamic value along with its type representation:
90
91 data Dynamic = Dynamic TypeRep Obj
92
93 instance Show Dynamic where
94    -- the instance just prints the type representation.
95    showsPrec _ (Dynamic t _) = 
96           showString "<<" . 
97           showsPrec 0 t   . 
98           showString ">>"
99
100 data Obj = Obj  
101  -- dummy type to hold the dynamically typed value.
102
103 data TypeRep
104  = App TyCon   [TypeRep]
105  | Fun TypeRep TypeRep
106    deriving ( Eq )
107
108 instance Show TypeRep where
109   showsPrec p (App tycon tys) =
110     case tys of
111       [] -> showsPrec p tycon
112       [x] | tycon == listTc    -> showChar '[' . shows x . showChar ']'
113       xs  
114         | isTupleTyCon tycon -> showTuple tycon xs
115         | otherwise          ->
116             showParen (p > 9) $
117             showsPrec p tycon . 
118             showChar ' '      . 
119             showArgs tys
120
121   showsPrec p (Fun f a) =
122      showParen (p > 8) $
123      showsPrec 9 f . showString " -> " . showsPrec 8 a
124
125 -- type constructors are 
126 data TyCon = TyCon Int String
127
128 instance Eq TyCon where
129   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
130
131 instance Show TyCon where
132   showsPrec _ (TyCon _ s) = showString s
133
134 -- Operations for going to and from Dynamic:
135
136 toDyn :: Typeable a => a -> Dynamic
137 toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
138
139 fromDyn :: Typeable a => Dynamic -> a -> a
140 fromDyn (Dynamic t v) def
141   | typeOf def == t = unsafeCoerce v
142   | otherwise       = def
143
144 fromDynamic :: Typeable a => Dynamic -> Maybe a
145 fromDynamic (Dynamic t v) =
146   case unsafeCoerce v of 
147     r | t == typeOf r -> Just r
148       | otherwise     -> Nothing
149
150 -- To make it possible to convert values with user-defined types
151 -- into type Dynamic, we need a systematic way of getting
152 -- the type representation of an arbitrary type. A type
153 -- class provides just the ticket,
154
155 class Typeable a where
156   typeOf :: a -> TypeRep
157
158 -- NOTE: The argument to the overloaded `typeOf' is only
159 -- used to carry type information, and Typeable instances
160 -- should *never* *ever* look at its value.
161
162 isTupleTyCon :: TyCon -> Bool
163 isTupleTyCon (TyCon _ (',':_)) = True
164 isTupleTyCon _                 = False
165
166 -- If we enforce the restriction that there is only one
167 -- @TyCon@ for a type & it is shared among all its uses,
168 -- we can map them onto Ints very simply. The benefit is,
169 -- of course, that @TyCon@s can then be compared efficiently.
170
171 -- Provided the implementor of other @Typeable@ instances
172 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
173 -- this will work. 
174
175 -- If this constraint does turn out to be a sore thumb, changing
176 -- the Eq instance for TyCons is trivial.
177
178 mkTyCon :: String -> TyCon
179 mkTyCon str = unsafePerformIO $ do
180    v <- readIORef uni
181    writeIORef uni (v+1)
182    return (TyCon v str)
183
184 {-# NOINLINE uni #-}
185 uni :: IORef Int
186 uni = unsafePerformIO ( newIORef 0 )
187
188 -- Some (Show.TypeRep) helpers:
189
190 showArgs :: Show a => [a] -> ShowS
191 showArgs [] = id
192 showArgs [a] = showsPrec 10 a
193 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
194
195 showTuple :: TyCon -> [TypeRep] -> ShowS
196 showTuple (TyCon _ str) args = showChar '(' . go str args
197  where
198   go [] [a] = showsPrec 10 a . showChar ')'
199   go _  []  = showChar ')' -- a failure condition, really.
200   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
201   go _ _   = showChar ')'
202
203
204 mkAppTy  :: TyCon   -> [TypeRep] -> TypeRep
205 mkAppTy tyc args = App tyc args
206
207 mkFunTy  :: TypeRep -> TypeRep   -> TypeRep
208 mkFunTy f a = Fun f a
209
210 -- Auxillary functions
211
212 -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
213 dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
214 dynApply (Dynamic t1 f) (Dynamic t2 x) =
215   case applyTy t1 t2 of
216     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
217     Nothing -> Nothing
218
219 dynApp :: Dynamic -> Dynamic -> Dynamic
220 dynApp f x = case dynApply f x of 
221              Just r -> r
222              Nothing -> error ("Type error in dynamic application.\n" ++
223                                "Can't apply function " ++ show f ++
224                                " to argument " ++ show x)
225
226 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
227 applyTy (Fun t1 t2) t3
228   | t1 == t3    = Just t2
229 applyTy _ _     = Nothing
230
231 -- Prelude types
232
233 listTc :: TyCon
234 listTc = mkTyCon "[]"
235
236 instance Typeable a => Typeable [a] where
237   typeOf ls = mkAppTy listTc [typeOf ((undefined:: [a] -> a) ls)]
238
239 unitTc :: TyCon
240 unitTc = mkTyCon "()"
241
242 instance Typeable () where
243   typeOf _ = mkAppTy unitTc []
244
245 tup2Tc :: TyCon
246 tup2Tc = mkTyCon ","
247
248 instance (Typeable a, Typeable b) => Typeable (a,b) where
249   typeOf tu = mkAppTy tup2Tc [typeOf ((undefined :: (a,b) -> a) tu),
250                               typeOf ((undefined :: (a,b) -> b) tu)]
251
252 tup3Tc :: TyCon
253 tup3Tc = mkTyCon ",,"
254
255 instance ( Typeable a , Typeable b , Typeable c) => Typeable (a,b,c) where
256   typeOf tu = mkAppTy tup3Tc [typeOf ((undefined :: (a,b,c) -> a) tu),
257                               typeOf ((undefined :: (a,b,c) -> b) tu),
258                               typeOf ((undefined :: (a,b,c) -> c) tu)]
259
260 tup4Tc :: TyCon
261 tup4Tc = mkTyCon ",,,"
262
263 instance ( Typeable a
264          , Typeable b
265          , Typeable c
266          , Typeable d) => Typeable (a,b,c,d) where
267   typeOf tu = mkAppTy tup4Tc [typeOf ((undefined :: (a,b,c,d) -> a) tu),
268                               typeOf ((undefined :: (a,b,c,d) -> b) tu),
269                               typeOf ((undefined :: (a,b,c,d) -> c) tu),
270                               typeOf ((undefined :: (a,b,c,d) -> d) tu)]
271
272 tup5Tc :: TyCon
273 tup5Tc = mkTyCon ",,,,"
274
275 instance ( Typeable a
276          , Typeable b
277          , Typeable c
278          , Typeable d
279          , Typeable e) => Typeable (a,b,c,d,e) where
280   typeOf tu = mkAppTy tup5Tc [typeOf ((undefined :: (a,b,c,d,e) -> a) tu),
281                               typeOf ((undefined :: (a,b,c,d,e) -> b) tu),
282                               typeOf ((undefined :: (a,b,c,d,e) -> c) tu),
283                               typeOf ((undefined :: (a,b,c,d,e) -> d) tu),
284                               typeOf ((undefined :: (a,b,c,d,e) -> e) tu)]
285
286 instance (Typeable a, Typeable b) => Typeable (a -> b) where
287   typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f))
288                      (typeOf ((undefined :: (a -> b) -> b) f))
289
290 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
291 INSTANCE_TYPEABLE0(Char,charTc,"Char")
292 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
293 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
294 INSTANCE_TYPEABLE0(Int,intTc,"Int")
295 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
296 INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
297 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
298 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
299 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
300 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
301 INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
302 INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
303
304 INSTANCE_TYPEABLE0(Int8,int8Tc, "Int8")
305 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
306 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
307 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
308
309 INSTANCE_TYPEABLE0(Word8,word8Tc, "Word8" )
310 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
311 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
312 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
313
314 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
315 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
316 INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")