[project @ 2004-03-19 20:31:50 by panne]
[ghc-base.git] / Data / Typeable.hs
index 4c8050a..7e4a518 100644 (file)
@@ -2,7 +2,7 @@
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Typeable
--- Copyright   :  (c) The University of Glasgow 2001
+-- Copyright   :  (c) The University of Glasgow, CWI 2001--2004
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
 -- 
 -- Maintainer  :  libraries@haskell.org
@@ -28,8 +28,7 @@ module Data.Typeable
 
        -- * Type-safe cast
        cast,                   -- :: (Typeable a, Typeable b) => a -> Maybe b
-       castss,                 -- a cast for kind "* -> *"
-       castarr,                -- another convenient variation
+       gcast,                  -- a generalisation of cast
 
        -- * Type representations
        TypeRep,        -- abstract, instance of: Eq, Show, Typeable
@@ -40,12 +39,23 @@ module Data.Typeable
        mkAppTy,        -- :: TyCon   -> [TypeRep] -> TypeRep
        mkFunTy,        -- :: TypeRep -> TypeRep   -> TypeRep
        applyTy,        -- :: TypeRep -> TypeRep   -> Maybe TypeRep
+       popStarTy,      -- :: TypeRep -> TypeRep   -> TypeRep
 
        -- * Observation of type representations
        typerepTyCon,   -- :: TypeRep -> TyCon
        typerepArgs,    -- :: TypeRep -> [TypeRep]
-       tyconString     -- :: TyCon   -> String
-
+       tyconString,    -- :: TyCon   -> String
+
+       -- * The other Typeable classes
+       Typeable1( typeOf1 ),   -- :: t a -> TypeRep
+       Typeable2( typeOf2 ),   -- :: t a b -> TypeRep
+       Typeable3( typeOf3 ),   -- :: t a b c -> TypeRep
+       Typeable4( typeOf4 ),   -- :: t a b c d -> TypeRep
+       Typeable5( typeOf5 ),   -- :: t a b c d e -> TypeRep
+       Typeable6( typeOf6 ),   -- :: t a b c d e f -> TypeRep
+       Typeable7( typeOf7 ),   -- :: t a b c d e f g -> TypeRep
+       gcast1,                 -- :: ... => c (t a) -> Maybe (c (t' a))
+       gcast2                  -- :: ... => c (t a b) -> Maybe (c (t' a b))
 
   ) where
 
@@ -65,8 +75,8 @@ import GHC.Num
 import GHC.Float
 import GHC.Real( rem, Ratio )
 import GHC.IOBase
-import GHC.Ptr         -- So we can give Typeable instance for Ptr
-import GHC.Stable      -- So we can give Typeable instance for StablePtr
+import GHC.Ptr          -- So we can give Typeable instance for Ptr
+import GHC.Stable       -- So we can give Typeable instance for StablePtr
 #endif
 
 #ifdef __HUGS__
@@ -90,6 +100,7 @@ import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
 
 
 #ifndef __HUGS__
+
 -------------------------------------------------------------
 --
 --             Type representations
@@ -125,6 +136,7 @@ instance Eq TyCon where
        -- sequence of commas, e.g., (mkTyCon ",,,,") returns
        -- the 5-tuple tycon.
 
+
 ----------------- Construction --------------------
 
 -- | Applies a type constructor to a sequence of types
@@ -134,14 +146,18 @@ mkAppTy tc@(TyCon tc_k _) args
   where
     arg_ks = [k | TypeRep k _ _ <- args]
 
+
+-- The function type constructor
 funTc :: TyCon
 funTc = mkTyCon "->"
 
+
 -- | A special case of 'mkAppTy', which applies the function 
 -- type constructor to a pair of types.
 mkFunTy  :: TypeRep -> TypeRep -> TypeRep
 mkFunTy f a = mkAppTy funTc [f,a]
 
+
 -- | Applies a type to a function type.  Returns: @'Just' u@ if the
 -- first argument represents a function of type @t -> u@ and the
 -- second argument represents a function of type @t@.  Otherwise,
@@ -151,6 +167,14 @@ applyTy (TypeRep _ tc [t1,t2]) t3
   | tc == funTc && t1 == t3    = Just t2
 applyTy _ _                    = Nothing
 
+
+-- | Adds a TypeRep argument to a TypeRep.
+popStarTy :: TypeRep -> TypeRep -> TypeRep
+popStarTy (TypeRep tr_k tc trs) arg_tr
+  = let (TypeRep arg_k _ _) = arg_tr
+     in  TypeRep (appKey tr_k arg_k) tc (trs++[arg_tr])
+
+
 -- If we enforce the restriction that there is only one
 -- @TyCon@ for a type & it is shared among all its uses,
 -- we can map them onto Ints very simply. The benefit is,
@@ -203,7 +227,9 @@ instance Show TypeRep where
       [] -> showsPrec p tycon
       [x]   | tycon == listTc -> showChar '[' . shows x . showChar ']'
       [a,r] | tycon == funTc  -> showParen (p > 8) $
-                                showsPrec 9 a . showString " -> " . showsPrec 8 r
+                                showsPrec 9 a .
+                                 showString " -> " .
+                                 showsPrec 8 r
       xs | isTupleTyCon tycon -> showTuple tycon xs
         | otherwise         ->
            showParen (p > 9) $
@@ -218,6 +244,7 @@ isTupleTyCon :: TyCon -> Bool
 isTupleTyCon (TyCon _ (',':_)) = True
 isTupleTyCon _                = False
 
+
 -- Some (Show.TypeRep) helpers:
 
 showArgs :: Show a => [a] -> ShowS
@@ -236,10 +263,11 @@ showTuple (TyCon _ str) args = showChar '(' . go str args
 
 -------------------------------------------------------------
 --
---     The Typeable class
+--     The Typeable class and friends
 --
 -------------------------------------------------------------
 
+
 -- | The class 'Typeable' allows a concrete representation of a type to
 -- be calculated.
 class Typeable a where
@@ -249,6 +277,137 @@ class Typeable a where
   -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
   -- the argument.
 
+-- HACK HACK HACK
+#ifdef __HUGS__
+#define INSTANCE_TYPEABLE1x(tycon,tcname,str) \
+instance Typeable a => Typeable (tycon a) where { \
+  typeOf x = mkAppTy tcname [typeOf ((undefined :: tycon a -> a) x) ] }
+#define INSTANCE_TYPEABLE2x(tycon,tcname,str) \
+instance (Typeable a, Typeable b) => Typeable (tycon a b) where { \
+  typeOf x = mkAppTy tcname [typeOf ((undefined :: tycon a b -> a) x), \
+                            typeOf ((undefined :: tycon a b -> b) x)] }
+
+INSTANCE_TYPEABLE1x(Ratio,ratioTc,"Ratio")
+INSTANCE_TYPEABLE2x(Either,eitherTc,"Either")
+INSTANCE_TYPEABLE1(IO,ioTc,"IO")
+INSTANCE_TYPEABLE1x(Maybe,maybeTc,"Maybe")
+INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
+INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
+INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
+#endif
+
+-- | Variant for unary type constructors
+class Typeable1 t where
+  typeOf1 :: t a -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable instance for all Typeable1 instances
+instance (Typeable1 s, Typeable a)
+       => Typeable (s a) where
+  typeOf x = typeOf1 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x -> x
+     argType =  undefined
+#endif
+
+
+-- | Variant for binary type constructors
+class Typeable2 t where
+  typeOf2 :: t a b -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable1 instance for all Typeable2 instances
+instance (Typeable2 s, Typeable a)
+       => Typeable1 (s a) where
+  typeOf1 x = typeOf2 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x y -> x
+     argType =  undefined
+#endif
+
+
+-- | Variant for 3-ary type constructors
+class Typeable3 t where
+  typeOf3 :: t a b c -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable2 instance for all Typeable3 instances
+instance (Typeable3 s, Typeable a)
+       => Typeable2 (s a) where
+  typeOf2 x = typeOf3 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x y z -> x
+     argType =  undefined
+#endif
+
+
+-- | Variant for 4-ary type constructors
+class Typeable4 t where
+  typeOf4 :: t a b c d -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable3 instance for all Typeable4 instances
+instance (Typeable4 s, Typeable a)
+       => Typeable3 (s a) where
+  typeOf3 x = typeOf4 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x y z z' -> x
+     argType =  undefined
+#endif
+
+
+-- | Variant for 5-ary type constructors
+class Typeable5 t where
+  typeOf5 :: t a b c d e -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable4 instance for all Typeable5 instances
+instance (Typeable5 s, Typeable a)
+       => Typeable4 (s a) where
+  typeOf4 x = typeOf5 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x y z z' z'' -> x
+     argType =  undefined
+#endif
+
+
+-- | Variant for 6-ary type constructors
+class Typeable6 t where
+  typeOf6 :: t a b c d e f -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable5 instance for all Typeable6 instances
+instance (Typeable6 s, Typeable a)
+       => Typeable5 (s a) where
+  typeOf5 x = typeOf6 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x y z z' z'' z''' -> x
+     argType =  undefined
+#endif
+
+
+-- | Variant for 7-ary type constructors
+class Typeable7 t where
+  typeOf7 :: t a b c d e f g -> TypeRep
+
+
+#ifndef __HUGS__
+-- | One Typeable6 instance for all Typeable7 instances
+instance (Typeable7 s, Typeable a)
+       => Typeable6 (s a) where
+  typeOf6 x = typeOf7 x `popStarTy` typeOf (argType x)
+   where
+     argType :: t x y z z' z'' z''' z'''' -> x
+     argType =  undefined
+#endif
+
+
 
 -------------------------------------------------------------
 --
@@ -265,106 +424,164 @@ cast x = r
               else Nothing
 
 
--- | A convenient variation for kind \"* -> *\"
-castss :: (Typeable a, Typeable b) => t a -> Maybe (t b)
-castss x = r
-       where
-        r = if typeOf (get x) == typeOf (get (fromJust r))
-               then Just $ unsafeCoerce x
-              else Nothing
-         get :: t c -> c
-        get = undefined
+-- | A flexible variation parameterised in a type constructor
+gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
+gcast x = r
+ where
+  r = if typeOf (getArg x) == typeOf (getArg (fromJust r))
+        then Just $ unsafeCoerce x
+        else Nothing
+  getArg :: c x -> x 
+  getArg = undefined
 
 
--- | Another variation
-castarr :: (Typeable a, Typeable b, Typeable c, Typeable d)
-        => (a -> t b) -> Maybe (c -> t d)
-castarr x = r
-       where
-        r = if typeOf (get x) == typeOf (get (fromJust r))
-               then Just $ unsafeCoerce x
-              else Nothing
-         get :: (e -> t f) -> (e, f)
-        get = undefined
 
-{-
+-- | Cast for * -> *
+gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a)) 
+gcast1 x = r
+ where
+  r = if typeOf1 (getArg x) == typeOf1 (getArg (fromJust r))
+       then Just $ unsafeCoerce x
+       else Nothing
+  getArg :: c x -> x 
+  getArg = undefined
+
 
-The variations castss and castarr are arguably not really needed.
-Let's discuss castss in some detail. To get rid of castss, we can
-require "Typeable (t a)" and "Typeable (t b)" rather than just
-"Typeable a" and "Typeable b". In that case, the ordinary cast would
-work. Eventually, all kinds of library instances should become
-Typeable. (There is another potential use of variations as those given
-above. It allows quantification on type constructors.
+-- | Cast for * -> * -> *
+gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b)) 
+gcast2 x = r
+ where
+  r = if typeOf2 (getArg x) == typeOf2 (getArg (fromJust r))
+       then Just $ unsafeCoerce x
+       else Nothing
+  getArg :: c x -> x 
+  getArg = undefined
 
--}
 
 
 -------------------------------------------------------------
 --
---     Instances of the Typeable class for Prelude types
+--     Instances of the Typeable classes for Prelude types
 --
 -------------------------------------------------------------
 
-listTc :: TyCon
-listTc = mkTyCon "[]"
-
-instance Typeable a => Typeable [a] where
-  typeOf ls = mkAppTy listTc [typeOf ((undefined :: [a] -> a) ls)]
-       -- In GHC we can say
-       --      typeOf (undefined :: a)
-       -- using scoped type variables, but we use the 
-       -- more verbose form here, for compatibility with Hugs
-
 unitTc :: TyCon
 unitTc = mkTyCon "()"
 
 instance Typeable () where
   typeOf _ = mkAppTy unitTc []
 
-tup2Tc :: TyCon
-tup2Tc = mkTyCon ","
-
-instance (Typeable a, Typeable b) => Typeable (a,b) where
-  typeOf tu = mkAppTy tup2Tc [typeOf ((undefined :: (a,b) -> a) tu),
-                             typeOf ((undefined :: (a,b) -> b) tu)]
 
 tup3Tc :: TyCon
 tup3Tc = mkTyCon ",,"
 
-instance ( Typeable a , Typeable b , Typeable c) => Typeable (a,b,c) where
-  typeOf tu = mkAppTy tup3Tc [typeOf ((undefined :: (a,b,c) -> a) tu),
-                             typeOf ((undefined :: (a,b,c) -> b) tu),
-                             typeOf ((undefined :: (a,b,c) -> c) tu)]
+instance Typeable3 (,,) where
+  typeOf3 tu = mkAppTy tup3Tc []
+
 
 tup4Tc :: TyCon
 tup4Tc = mkTyCon ",,,"
 
-instance ( Typeable a
-        , Typeable b
-        , Typeable c
-        , Typeable d) => Typeable (a,b,c,d) where
-  typeOf tu = mkAppTy tup4Tc [typeOf ((undefined :: (a,b,c,d) -> a) tu),
-                             typeOf ((undefined :: (a,b,c,d) -> b) tu),
-                             typeOf ((undefined :: (a,b,c,d) -> c) tu),
-                             typeOf ((undefined :: (a,b,c,d) -> d) tu)]
+instance Typeable4 (,,,) where
+  typeOf4 tu = mkAppTy tup4Tc []
+
+
 tup5Tc :: TyCon
 tup5Tc = mkTyCon ",,,,"
 
-instance ( Typeable a
-        , Typeable b
-        , Typeable c
-        , Typeable d
-        , Typeable e) => Typeable (a,b,c,d,e) where
-  typeOf tu = mkAppTy tup5Tc [typeOf ((undefined :: (a,b,c,d,e) -> a) tu),
-                             typeOf ((undefined :: (a,b,c,d,e) -> b) tu),
-                             typeOf ((undefined :: (a,b,c,d,e) -> c) tu),
-                             typeOf ((undefined :: (a,b,c,d,e) -> d) tu),
-                             typeOf ((undefined :: (a,b,c,d,e) -> e) tu)]
+instance Typeable5 (,,,,) where
+  typeOf5 tu = mkAppTy tup5Tc []
+
+
+tup6Tc :: TyCon
+tup6Tc = mkTyCon ",,,,,"
+
+instance Typeable6 (,,,,,) where
+  typeOf6 tu = mkAppTy tup6Tc []
+
+
+tup7Tc :: TyCon
+tup7Tc = mkTyCon ",,,,,"
+
+instance Typeable7 (,,,,,,) where
+  typeOf7 tu = mkAppTy tup7Tc []
+
+
+listTc :: TyCon
+listTc = mkTyCon "[]"
+
+-- | Instance for lists
+instance Typeable1 [] where
+  typeOf1 _ = mkAppTy listTc []
+
+
+maybeTc :: TyCon
+maybeTc = mkTyCon "Maybe"
+
+-- | Instance for maybes
+instance Typeable1 Maybe where
+  typeOf1 _ = mkAppTy maybeTc []
+
 
-instance (Typeable a, Typeable b) => Typeable (a -> b) where
-  typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f))
-                    (typeOf ((undefined :: (a -> b) -> b) f))
+ratioTc :: TyCon
+ratioTc = mkTyCon "Ratio"
+
+-- | Instance for ratios
+instance Typeable1 Ratio where
+  typeOf1 _ = mkAppTy ratioTc []
+
+
+pairTc :: TyCon
+pairTc = mkTyCon "(,)"
+
+-- | Instance for products
+instance Typeable2 (,) where
+  typeOf2 _ = mkAppTy pairTc []
+
+
+eitherTc :: TyCon
+eitherTc = mkTyCon "Either"
+
+-- | Instance for sums
+instance Typeable2 Either where
+  typeOf2 _ = mkAppTy eitherTc []
+
+
+-- | Instance for functions
+instance Typeable2 (->) where
+  typeOf2 _ = mkAppTy funTc []
+
+
+#ifdef __GLASGOW_HASKELL__
+
+ioTc :: TyCon
+ioTc = mkTyCon "GHC.IOBase.IO"
+
+instance Typeable1 IO where
+  typeOf1 _ = mkAppTy ioTc []
+
+
+ptrTc :: TyCon
+ptrTc = mkTyCon "GHC.Ptr.Ptr"
+
+instance Typeable1 Ptr where
+  typeOf1 _ = mkAppTy ptrTc []
+
+
+stableptrTc :: TyCon
+stableptrTc = mkTyCon "GHC.Stable.StablePtr"
+
+instance Typeable1 StablePtr where
+  typeOf1 _ = mkAppTy stableptrTc []
+
+
+iorefTc :: TyCon
+iorefTc = mkTyCon "GHC.IOBase.IORef"
+
+instance Typeable1 IORef where
+  typeOf1 _ = mkAppTy iorefTc []
+
+#endif
 
 
 
@@ -381,14 +598,8 @@ INSTANCE_TYPEABLE0(Float,floatTc,"Float")
 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
 INSTANCE_TYPEABLE0(Int,intTc,"Int")
 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
-INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio")
-INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
-INSTANCE_TYPEABLE1(IO,ioTc,"IO")
-INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
-INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
-INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
 
 INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
@@ -402,8 +613,10 @@ INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
 
 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
+#endif
 
-INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
+#ifdef __GLASGOW_HASKELL__
+INSTANCE_TYPEABLE0(Word,wordTc,"Word" )
 #endif