1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
4 -- Module : Data.Dynamic
5 -- Copyright : (c) The University of Glasgow 2001
6 -- License : BSD-style (see the file libraries/core/LICENSE)
8 -- Maintainer : libraries@haskell.org
9 -- Stability : experimental
10 -- Portability : non-portable
12 -- $Id: Dynamic.hs,v 1.1 2001/06/28 14:15:02 simonmar Exp $
14 -- The Dynamic interface provides basic support for dynamic types.
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.
21 -- The Dynamic implementation provided is closely based on code
22 -- contained in Hugs library of the same name.
24 -----------------------------------------------------------------------------
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
34 -- type representation
37 typeOf
) -- :: a -> TypeRep
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
45 , TypeRep
-- abstract, instance of: Eq, Show, Typeable
46 , TyCon
-- abstract, instance of: Eq, Show, Typeable
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
55 -- let fTy = mkTyCon "Foo" in show (mkAppTy (mkTyCon ",,")
58 -- returns "(Foo,Foo,Foo)"
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
67 #ifdef __GLASGOW_HASKELL__
78 #ifdef __GLASGOW_HASKELL__
79 import GHC
.Prim
( unsafeCoerce
# )
81 unsafeCoerce
:: a
-> b
82 unsafeCoerce
= unsafeCoerce
#
87 -- The dynamic type is represented by Dynamic, carrying
88 -- the dynamic value along with its type representation:
90 -- the instance just prints the type representation.
91 instance Show Dynamic
where
92 showsPrec _
(Dynamic t _
) =
97 -- Operations for going to and from Dynamic:
99 toDyn
:: Typeable a
=> a
-> Dynamic
100 toDyn v
= Dynamic
(typeOf v
) (unsafeCoerce v
)
102 fromDyn
:: Typeable a
=> Dynamic
-> a
-> a
103 fromDyn
(Dynamic t v
) def
104 | typeOf def
== t
= unsafeCoerce v
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
113 -- (Abstract) universal datatype:
115 instance Show TypeRep
where
116 showsPrec p
(App tycon tys
) =
118 [] -> showsPrec p tycon
119 [x
] | tycon
== listTc
-> showChar '[' . shows x
. showChar ']'
121 | isTupleTyCon tycon
-> showTuple tycon xs
128 showsPrec p
(Fun f a
) =
130 showsPrec 9 f
. showString " -> " . showsPrec 8 a
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,
137 class Typeable a
where
138 typeOf
:: a
-> TypeRep
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.
144 isTupleTyCon
:: TyCon
-> Bool
145 isTupleTyCon
(TyCon _
(',':_
)) = True
146 isTupleTyCon _
= False
148 instance Show TyCon
where
149 showsPrec _
(TyCon _ s
) = showString s
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.
156 -- Provided the implementor of other @Typeable@ instances
157 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
160 -- If this constraint does turn out to be a sore thumb, changing
161 -- the Eq instance for TyCons is trivial.
163 mkTyCon
:: String -> TyCon
164 mkTyCon str
= unsafePerformIO
$ do
171 uni
= unsafePerformIO
( newIORef
0 )
173 -- Some (Show.TypeRep) helpers:
175 showArgs
:: Show a
=> [a
] -> ShowS
177 showArgs
[a
] = showsPrec 10 a
178 showArgs
(a
:as) = showsPrec 10 a
. showString " " . showArgs
as
180 showTuple
:: TyCon
-> [TypeRep
] -> ShowS
181 showTuple
(TyCon _ str
) args
= showChar '(' . go str args
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 ')'
189 mkAppTy
:: TyCon
-> [TypeRep
] -> TypeRep
190 mkAppTy tyc args
= App tyc args
192 mkFunTy
:: TypeRep
-> TypeRep
-> TypeRep
193 mkFunTy f a
= Fun f a
195 -- Auxillary functions
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
))
204 dynApp
:: Dynamic
-> Dynamic
-> Dynamic
205 dynApp f x
= case dynApply f x
of
207 Nothing
-> error ("Type error in dynamic application.\n" ++
208 "Can't apply function " ++ show f
++
209 " to argument " ++ show x
)
211 applyTy
:: TypeRep
-> TypeRep
-> Maybe TypeRep
212 applyTy
(Fun t1 t2
) t3
214 applyTy _ _
= Nothing
219 listTc
= mkTyCon
"[]"
221 instance Typeable a
=> Typeable
[a
] where
222 typeOf ls
= mkAppTy listTc
[typeOf
((undefined:: [a
] -> a
) ls
)]
225 unitTc
= mkTyCon
"()"
227 instance Typeable
() where
228 typeOf _
= mkAppTy unitTc
[]
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
)]
238 tup3Tc
= mkTyCon
",,"
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
)]
246 tup4Tc
= mkTyCon
",,,"
248 instance ( Typeable a
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
)]
258 tup5Tc
= mkTyCon
",,,,"
260 instance ( Typeable a
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
)]
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
))
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")
286 INSTANCE_TYPEABLE0
(TyCon
,tyconTc
,"TyCon")
287 INSTANCE_TYPEABLE0
(TypeRep
,typeRepTc
,"TypeRep")
288 INSTANCE_TYPEABLE0
(Dynamic
,dynamicTc
,"Dynamic")