X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Data%2FTypeable.hs;h=ce602e4999f8d4071f61f84645fcec891fb1ef89;hb=HEAD;hp=b54f8fc9a647c759db9541eadd965127d5128eb8;hpb=5b272091fa9c22196f0c887d34f6a94d590a1398;p=ghc-base.git diff --git a/Data/Typeable.hs b/Data/Typeable.hs index b54f8fc..ce602e4 100644 --- a/Data/Typeable.hs +++ b/Data/Typeable.hs @@ -1,4 +1,21 @@ -{-# OPTIONS -fno-implicit-prelude #-} +{-# LANGUAGE CPP + , NoImplicitPrelude + , OverlappingInstances + , ScopedTypeVariables + , ForeignFunctionInterface + , FlexibleInstances + #-} +{-# OPTIONS_GHC -funbox-strict-fields #-} +#ifdef __GLASGOW_HASKELL__ +{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} +#endif + +-- The -XOverlappingInstances flag allows the user to over-ride +-- the instances for Typeable given here. In particular, we provide an instance +-- instance ... => Typeable (s a) +-- But a user might want to say +-- instance ... => Typeable (MyType a b) + ----------------------------------------------------------------------------- -- | -- Module : Data.Typeable @@ -9,12 +26,12 @@ -- Stability : experimental -- Portability : portable -- --- The Typeable class reifies types to some extent by associating type +-- The 'Typeable' class reifies types to some extent by associating type -- representations to types. These type representations can be compared, -- and one can in turn define a type-safe cast operation. To this end, -- an unsafe cast is guarded by a test for type (representation) --- equivalence. The module Data.Dynamic uses Typeable for an --- implementation of dynamics. The module Data.Generics uses Typeable +-- equivalence. The module "Data.Dynamic" uses Typeable for an +-- implementation of dynamics. The module "Data.Data" uses Typeable -- and type-safe cast (but not dynamics) to support the \"Scrap your -- boilerplate\" style of generic programming. -- @@ -23,84 +40,119 @@ module Data.Typeable ( - -- * The Typeable class - Typeable( typeOf ), -- :: a -> TypeRep - - -- * Type-safe cast - cast, -- :: (Typeable a, Typeable b) => a -> Maybe b - gcast, -- a flexible variation on cast - - -- * Type representations - TypeRep, -- abstract, instance of: Eq, Show, Typeable - TyCon, -- abstract, instance of: Eq, Show, Typeable - - -- * Construction of type representations - mkTyCon, -- :: String -> TyCon - mkAppTy, -- :: TyCon -> [TypeRep] -> TypeRep - mkFunTy, -- :: TypeRep -> TypeRep -> TypeRep - applyTy, -- :: TypeRep -> TypeRep -> Maybe TypeRep - - -- * Observation of type representations - typerepTyCon, -- :: TypeRep -> TyCon - typerepArgs, -- :: TypeRep -> [TypeRep] - tyconString, -- :: TyCon -> String - - -- * The Typeable1 class - Typeable1( typeOf1 ), -- :: t a -> TyCon - Typeable2( typeOf2 ), -- :: t a b -> TyCon - gcast1, -- :: ... => c (t a) -> Maybe (c (t' a)) - gcast2 -- :: ... => c (t a b) -> Maybe (c (t' a b)) + -- * The Typeable class + Typeable( typeOf ), -- :: a -> TypeRep + + -- * Type-safe cast + cast, -- :: (Typeable a, Typeable b) => a -> Maybe b + gcast, -- a generalisation of cast + + -- * Type representations + TypeRep, -- abstract, instance of: Eq, Show, Typeable + TyCon, -- abstract, instance of: Eq, Show, Typeable + showsTypeRep, + + -- * Construction of type representations + mkTyCon, -- :: String -> TyCon + mkTyConApp, -- :: TyCon -> [TypeRep] -> TypeRep + mkAppTy, -- :: TypeRep -> TypeRep -> TypeRep + mkFunTy, -- :: TypeRep -> TypeRep -> TypeRep + + -- * Observation of type representations + splitTyConApp, -- :: TypeRep -> (TyCon, [TypeRep]) + funResultTy, -- :: TypeRep -> TypeRep -> Maybe TypeRep + typeRepTyCon, -- :: TypeRep -> TyCon + typeRepArgs, -- :: TypeRep -> [TypeRep] + tyConString, -- :: TyCon -> String + typeRepKey, -- :: TypeRep -> IO Int + + -- * The other Typeable classes + -- | /Note:/ The general instances are provided for GHC only. + 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)) + + -- * Default instances + -- | /Note:/ These are not needed by GHC, for which these instances + -- are generated by general instance declarations. + typeOfDefault, -- :: (Typeable1 t, Typeable a) => t a -> TypeRep + typeOf1Default, -- :: (Typeable2 t, Typeable a) => t a b -> TypeRep + typeOf2Default, -- :: (Typeable3 t, Typeable a) => t a b c -> TypeRep + typeOf3Default, -- :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep + typeOf4Default, -- :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep + typeOf5Default, -- :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep + typeOf6Default -- :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep ) where - import qualified Data.HashTable as HT import Data.Maybe -import Data.Either import Data.Int import Data.Word -import Data.List( foldl ) +import Data.List( foldl, intersperse ) +import Unsafe.Coerce #ifdef __GLASGOW_HASKELL__ import GHC.Base -import GHC.Show -import GHC.Err -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 -#endif +import GHC.Show (Show(..), ShowS, + shows, showString, showChar, showParen) +import GHC.Err (undefined) +import GHC.Num (Integer, (+)) +import GHC.Real ( rem, Ratio ) +import GHC.IORef (IORef,newIORef) +import GHC.IO (unsafePerformIO,mask_) + +-- These imports are so we can define Typeable instances +-- It'd be better to give Typeable instances in the modules themselves +-- but they all have to be compiled before Typeable +import GHC.IOArray +import GHC.MVar +import GHC.ST ( ST ) +import GHC.STRef ( STRef ) +import GHC.Ptr ( Ptr, FunPtr ) +import GHC.Stable ( StablePtr, newStablePtr, freeStablePtr, + deRefStablePtr, castStablePtrToPtr, + castPtrToStablePtr ) +import GHC.Arr ( Array, STArray ) -#ifdef __HUGS__ -import Hugs.Prelude -import Hugs.IO -import Hugs.IORef -import Hugs.IOExts #endif -#ifdef __GLASGOW_HASKELL__ -unsafeCoerce :: a -> b -unsafeCoerce = unsafeCoerce# +#ifdef __HUGS__ +import Hugs.Prelude ( Key(..), TypeRep(..), TyCon(..), Ratio, + Handle, Ptr, FunPtr, ForeignPtr, StablePtr ) +import Hugs.IORef ( IORef, newIORef, readIORef, writeIORef ) +import Hugs.IOExts ( unsafePerformIO ) + -- For the Typeable instance +import Hugs.Array ( Array ) +import Hugs.IOArray +import Hugs.ConcBase ( MVar ) #endif #ifdef __NHC__ -import NonStdUnsafeCoerce (unsafeCoerce) -import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO) -#else -#include "Typeable.h" +import NHC.IOExtras (IOArray,IORef,newIORef,readIORef,writeIORef,unsafePerformIO) +import IO (Handle) +import Ratio (Ratio) + -- For the Typeable instance +import NHC.FFI ( Ptr,FunPtr,StablePtr,ForeignPtr ) +import Array ( Array ) #endif +#include "Typeable.h" #ifndef __HUGS__ + ------------------------------------------------------------- -- --- Type representations +-- Type representations -- ------------------------------------------------------------- - -- | A concrete representation of a (monomorphic) type. 'TypeRep' -- supports reasonably efficient equality. data TypeRep = TypeRep !Key TyCon [TypeRep] @@ -115,45 +167,65 @@ data TyCon = TyCon !Key String instance Eq TyCon where (TyCon t1 _) == (TyCon t2 _) = t1 == t2 - #endif - -- - -- let fTy = mkTyCon "Foo" in show (mkAppTy (mkTyCon ",,") - -- [fTy,fTy,fTy]) - -- - -- returns "(Foo,Foo,Foo)" - -- - -- The TypeRep Show instance promises to print tuple types - -- correctly. Tuple type constructors are specified by a - -- sequence of commas, e.g., (mkTyCon ",,,,") returns - -- the 5-tuple tycon. +-- | Returns a unique integer associated with a 'TypeRep'. This can +-- be used for making a mapping with TypeReps +-- as the keys, for example. It is guaranteed that @t1 == t2@ if and only if +-- @typeRepKey t1 == typeRepKey t2@. +-- +-- It is in the 'IO' monad because the actual value of the key may +-- vary from run to run of the program. You should only rely on +-- the equality property, not any actual key value. The relative ordering +-- of keys has no meaning either. +-- +typeRepKey :: TypeRep -> IO Int +typeRepKey (TypeRep (Key i) _ _) = return i + + -- + -- let fTy = mkTyCon "Foo" in show (mkTyConApp (mkTyCon ",,") + -- [fTy,fTy,fTy]) + -- + -- returns "(Foo,Foo,Foo)" + -- + -- The TypeRep Show instance promises to print tuple types + -- correctly. Tuple type constructors are specified by a + -- sequence of commas, e.g., (mkTyCon ",,,,") returns + -- the 5-tuple tycon. ----------------- Construction -------------------- -- | Applies a type constructor to a sequence of types -mkAppTy :: TyCon -> [TypeRep] -> TypeRep -mkAppTy tc@(TyCon tc_k _) args +mkTyConApp :: TyCon -> [TypeRep] -> TypeRep +mkTyConApp tc@(TyCon tc_k _) args = TypeRep (appKeys tc_k arg_ks) tc args where arg_ks = [k | TypeRep k _ _ <- args] -funTc :: TyCon -funTc = mkTyCon "->" - --- | A special case of 'mkAppTy', which applies the function +-- | A special case of 'mkTyConApp', which applies the function -- type constructor to a pair of types. mkFunTy :: TypeRep -> TypeRep -> TypeRep -mkFunTy f a = mkAppTy funTc [f,a] +mkFunTy f a = mkTyConApp funTc [f,a] + +-- | Splits a type constructor application +splitTyConApp :: TypeRep -> (TyCon,[TypeRep]) +splitTyConApp (TypeRep _ tc trs) = (tc,trs) -- | 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, -- returns 'Nothing'. -applyTy :: TypeRep -> TypeRep -> Maybe TypeRep -applyTy (TypeRep _ tc [t1,t2]) t3 - | tc == funTc && t1 == t3 = Just t2 -applyTy _ _ = Nothing +funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep +funResultTy trFun trArg + = case splitTyConApp trFun of + (tc, [t1,t2]) | tc == funTc && t1 == trArg -> Just t2 + _ -> Nothing + +-- | Adds a TypeRep argument to a TypeRep. +mkAppTy :: TypeRep -> TypeRep -> TypeRep +mkAppTy (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, @@ -173,31 +245,25 @@ applyTy _ _ = Nothing -- > mkTyCon "a" == mkTyCon "a" -- -mkTyCon :: String -- ^ the name of the type constructor (should be unique - -- in the program, so it might be wise to use the - -- fully qualified name). - -> TyCon -- ^ A unique 'TyCon' object +mkTyCon :: String -- ^ the name of the type constructor (should be unique + -- in the program, so it might be wise to use the + -- fully qualified name). + -> TyCon -- ^ A unique 'TyCon' object mkTyCon str = TyCon (mkTyConKey str) str - - ----------------- Observation --------------------- - -- | Observe the type constructor of a type representation -typerepTyCon :: TypeRep -> TyCon -typerepTyCon (TypeRep _ tc _) = tc - +typeRepTyCon :: TypeRep -> TyCon +typeRepTyCon (TypeRep _ tc _) = tc -- | Observe the argument types of a type representation -typerepArgs :: TypeRep -> [TypeRep] -typerepArgs (TypeRep _ _ args) = args - +typeRepArgs :: TypeRep -> [TypeRep] +typeRepArgs (TypeRep _ _ args) = args -- | Observe string encoding of a type representation -tyconString :: TyCon -> String -tyconString (TyCon _ str) = str - +tyConString :: TyCon -> String +tyConString (TyCon _ str) = str ----------------- Showing TypeReps -------------------- @@ -207,20 +273,25 @@ 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 - xs | isTupleTyCon tycon -> showTuple tycon xs - | otherwise -> - showParen (p > 9) $ - showsPrec p tycon . - showChar ' ' . - showArgs tys + showsPrec 9 a . + showString " -> " . + showsPrec 8 r + xs | isTupleTyCon tycon -> showTuple xs + | otherwise -> + showParen (p > 9) $ + showsPrec p tycon . + showChar ' ' . + showArgs tys + +showsTypeRep :: TypeRep -> ShowS +showsTypeRep = shows instance Show TyCon where showsPrec _ (TyCon _ s) = showString s isTupleTyCon :: TyCon -> Bool -isTupleTyCon (TyCon _ (',':_)) = True -isTupleTyCon _ = False +isTupleTyCon (TyCon _ ('(':',':_)) = True +isTupleTyCon _ = False -- Some (Show.TypeRep) helpers: @@ -229,21 +300,34 @@ showArgs [] = id showArgs [a] = showsPrec 10 a showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as -showTuple :: TyCon -> [TypeRep] -> ShowS -showTuple (TyCon _ str) args = showChar '(' . go str args - where - go [] [a] = showsPrec 10 a . showChar ')' - go _ [] = showChar ')' -- a failure condition, really. - go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as - go _ _ = showChar ')' - +showTuple :: [TypeRep] -> ShowS +showTuple args = showChar '(' + . (foldr (.) id $ intersperse (showChar ',') + $ map (showsPrec 10) args) + . showChar ')' ------------------------------------------------------------- -- --- The Typeable class +-- The Typeable class and friends -- ------------------------------------------------------------- +{- Note [Memoising typeOf] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +IMPORTANT: we don't want to recalculate the type-rep once per +call to the dummy argument. This is what went wrong in Trac #3245 +So we help GHC by manually keeping the 'rep' *outside* the value +lambda, thus + + typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRep + typeOfDefault = \_ -> rep + where + rep = typeOf1 (undefined :: t a) `mkAppTy` + typeOf (undefined :: a) + +Notice the crucial use of scoped type variables here! +-} + -- | The class 'Typeable' allows a concrete representation of a type to -- be calculated. class Typeable a where @@ -253,10 +337,200 @@ class Typeable a where -- any instance of 'Typeable', so that it is safe to pass 'undefined' as -- the argument. +-- | Variant for unary type constructors +class Typeable1 t where + typeOf1 :: t a -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable' instance from any 'Typeable1' instance. +typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRep +typeOfDefault = \_ -> rep + where + rep = typeOf1 (undefined :: t a) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable' instance from any 'Typeable1' instance. +typeOfDefault :: (Typeable1 t, Typeable a) => t a -> TypeRep +typeOfDefault x = typeOf1 x `mkAppTy` typeOf (argType x) + where + argType :: t a -> a + argType = undefined +#endif + +-- | Variant for binary type constructors +class Typeable2 t where + typeOf2 :: t a b -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable1' instance from any 'Typeable2' instance. +typeOf1Default :: forall t a b. (Typeable2 t, Typeable a) => t a b -> TypeRep +typeOf1Default = \_ -> rep + where + rep = typeOf2 (undefined :: t a b) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable1' instance from any 'Typeable2' instance. +typeOf1Default :: (Typeable2 t, Typeable a) => t a b -> TypeRep +typeOf1Default x = typeOf2 x `mkAppTy` typeOf (argType x) + where + argType :: t a b -> a + argType = undefined +#endif + +-- | Variant for 3-ary type constructors +class Typeable3 t where + typeOf3 :: t a b c -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable2' instance from any 'Typeable3' instance. +typeOf2Default :: forall t a b c. (Typeable3 t, Typeable a) => t a b c -> TypeRep +typeOf2Default = \_ -> rep + where + rep = typeOf3 (undefined :: t a b c) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable2' instance from any 'Typeable3' instance. +typeOf2Default :: (Typeable3 t, Typeable a) => t a b c -> TypeRep +typeOf2Default x = typeOf3 x `mkAppTy` typeOf (argType x) + where + argType :: t a b c -> a + argType = undefined +#endif + +-- | Variant for 4-ary type constructors +class Typeable4 t where + typeOf4 :: t a b c d -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable3' instance from any 'Typeable4' instance. +typeOf3Default :: forall t a b c d. (Typeable4 t, Typeable a) => t a b c d -> TypeRep +typeOf3Default = \_ -> rep + where + rep = typeOf4 (undefined :: t a b c d) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable3' instance from any 'Typeable4' instance. +typeOf3Default :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep +typeOf3Default x = typeOf4 x `mkAppTy` typeOf (argType x) + where + argType :: t a b c d -> a + argType = undefined +#endif + +-- | Variant for 5-ary type constructors +class Typeable5 t where + typeOf5 :: t a b c d e -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable4' instance from any 'Typeable5' instance. +typeOf4Default :: forall t a b c d e. (Typeable5 t, Typeable a) => t a b c d e -> TypeRep +typeOf4Default = \_ -> rep + where + rep = typeOf5 (undefined :: t a b c d e) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable4' instance from any 'Typeable5' instance. +typeOf4Default :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep +typeOf4Default x = typeOf5 x `mkAppTy` typeOf (argType x) + where + argType :: t a b c d e -> a + argType = undefined +#endif + +-- | Variant for 6-ary type constructors +class Typeable6 t where + typeOf6 :: t a b c d e f -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable5' instance from any 'Typeable6' instance. +typeOf5Default :: forall t a b c d e f. (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep +typeOf5Default = \_ -> rep + where + rep = typeOf6 (undefined :: t a b c d e f) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable5' instance from any 'Typeable6' instance. +typeOf5Default :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep +typeOf5Default x = typeOf6 x `mkAppTy` typeOf (argType x) + where + argType :: t a b c d e f -> a + argType = undefined +#endif + +-- | Variant for 7-ary type constructors +class Typeable7 t where + typeOf7 :: t a b c d e f g -> TypeRep + +#ifdef __GLASGOW_HASKELL__ +-- | For defining a 'Typeable6' instance from any 'Typeable7' instance. +typeOf6Default :: forall t a b c d e f g. (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep +typeOf6Default = \_ -> rep + where + rep = typeOf7 (undefined :: t a b c d e f g) `mkAppTy` + typeOf (undefined :: a) + -- Note [Memoising typeOf] +#else +-- | For defining a 'Typeable6' instance from any 'Typeable7' instance. +typeOf6Default :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep +typeOf6Default x = typeOf7 x `mkAppTy` typeOf (argType x) + where + argType :: t a b c d e f g -> a + argType = undefined +#endif + +#ifdef __GLASGOW_HASKELL__ +-- Given a @Typeable@/n/ instance for an /n/-ary type constructor, +-- define the instances for partial applications. +-- Programmers using non-GHC implementations must do this manually +-- for each type constructor. +-- (The INSTANCE_TYPEABLE/n/ macros in Typeable.h include this.) + +-- | One Typeable instance for all Typeable1 instances +instance (Typeable1 s, Typeable a) + => Typeable (s a) where + typeOf = typeOfDefault + +-- | One Typeable1 instance for all Typeable2 instances +instance (Typeable2 s, Typeable a) + => Typeable1 (s a) where + typeOf1 = typeOf1Default + +-- | One Typeable2 instance for all Typeable3 instances +instance (Typeable3 s, Typeable a) + => Typeable2 (s a) where + typeOf2 = typeOf2Default + +-- | One Typeable3 instance for all Typeable4 instances +instance (Typeable4 s, Typeable a) + => Typeable3 (s a) where + typeOf3 = typeOf3Default + +-- | One Typeable4 instance for all Typeable5 instances +instance (Typeable5 s, Typeable a) + => Typeable4 (s a) where + typeOf4 = typeOf4Default + +-- | One Typeable5 instance for all Typeable6 instances +instance (Typeable6 s, Typeable a) + => Typeable5 (s a) where + typeOf5 = typeOf5Default + +-- | One Typeable6 instance for all Typeable7 instances +instance (Typeable7 s, Typeable a) + => Typeable6 (s a) where + typeOf6 = typeOf6Default + +#endif /* __GLASGOW_HASKELL__ */ ------------------------------------------------------------- -- --- Type-safe cast +-- Type-safe cast -- ------------------------------------------------------------- @@ -264,10 +538,9 @@ class Typeable a where cast :: (Typeable a, Typeable b) => a -> Maybe b cast x = r where - r = if typeOf x == typeOf (fromJust r) + r = if typeOf x == typeOf (fromJust r) then Just $ unsafeCoerce x - else Nothing - + else Nothing -- | A flexible variation parameterised in a type constructor gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b) @@ -279,111 +552,90 @@ gcast x = r getArg :: c x -> x getArg = 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 +-- | 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 -- ------------------------------------------------------------- +INSTANCE_TYPEABLE0((),unitTc,"()") +INSTANCE_TYPEABLE1([],listTc,"[]") +#if defined(__GLASGOW_HASKELL__) 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)] - -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)] -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)] - -tup6Tc :: TyCon -tup6Tc = mkTyCon ",,,," - -instance ( Typeable a - , Typeable b - , Typeable c - , Typeable d - , Typeable e - , Typeable f) => Typeable (a,b,c,d,e,f) where - typeOf tu = mkAppTy tup6Tc - [typeOf ( (undefined :: (a,b,c,d,e,f) -> a) tu), - typeOf ((undefined :: (a,b,c,d,e,f) -> b) tu), - typeOf ((undefined :: (a,b,c,d,e,f) -> c) tu), - typeOf ((undefined :: (a,b,c,d,e,f) -> d) tu), - typeOf ((undefined :: (a,b,c,d,e,f) -> e) tu), - typeOf ((undefined :: (a,b,c,d,e,f) -> f) tu)] - -tup7Tc :: TyCon -tup7Tc = mkTyCon ",,,," - -instance ( Typeable a - , Typeable b - , Typeable c - , Typeable d - , Typeable e - , Typeable f - , Typeable g) => Typeable (a,b,c,d,e,f,g) where - typeOf tu = mkAppTy tup7Tc - [typeOf ( (undefined :: (a,b,c,d,e,f,g) -> a) tu), - typeOf ((undefined :: (a,b,c,d,e,f,g) -> b) tu), - typeOf ((undefined :: (a,b,c,d,e,f,g) -> c) tu), - typeOf ((undefined :: (a,b,c,d,e,f,g) -> d) tu), - typeOf ((undefined :: (a,b,c,d,e,f,g) -> e) tu), - typeOf ((undefined :: (a,b,c,d,e,f,g) -> f) tu), - typeOf ((undefined :: (a,b,c,d,e,f,g) -> g) tu)] - -instance (Typeable a, Typeable b) => Typeable (a -> b) where - typeOf f = mkFunTy (typeOf ((undefined :: (a -> b) -> a) f)) - (typeOf ((undefined :: (a -> b) -> b) f)) +listTc = typeRepTyCon (typeOf [()]) +#endif +INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe") +INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio") +#if defined(__GLASGOW_HASKELL__) +{- +TODO: Deriving this instance fails with: +libraries/base/Data/Typeable.hs:589:1: + Can't make a derived instance of `Typeable2 (->)': + The last argument of the instance must be a data or newtype application + In the stand-alone deriving instance for `Typeable2 (->)' +-} +instance Typeable2 (->) where { typeOf2 _ = mkTyConApp funTc [] } +funTc :: TyCon +funTc = mkTyCon "->" +#else +INSTANCE_TYPEABLE2((->),funTc,"->") +#endif +INSTANCE_TYPEABLE1(IO,ioTc,"IO") +#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__) +-- Types defined in GHC.MVar +INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" ) +#endif +INSTANCE_TYPEABLE2(Array,arrayTc,"Array") +INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray") + +#ifdef __GLASGOW_HASKELL__ +-- Hugs has these too, but their Typeable instances are defined +-- elsewhere to keep this module within Haskell 98. +-- This is important because every invocation of runhugs or ffihugs +-- uses this module via Data.Dynamic. +INSTANCE_TYPEABLE2(ST,stTc,"ST") +INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef") +INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray") +#endif + +#ifndef __NHC__ +INSTANCE_TYPEABLE2((,),pairTc,"(,)") +INSTANCE_TYPEABLE3((,,),tup3Tc,"(,,)") +INSTANCE_TYPEABLE4((,,,),tup4Tc,"(,,,)") +INSTANCE_TYPEABLE5((,,,,),tup5Tc,"(,,,,)") +INSTANCE_TYPEABLE6((,,,,,),tup6Tc,"(,,,,,)") +INSTANCE_TYPEABLE7((,,,,,,),tup7Tc,"(,,,,,,)") +#endif /* __NHC__ */ + +INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr") +INSTANCE_TYPEABLE1(FunPtr,funPtrTc,"FunPtr") +#ifndef __GLASGOW_HASKELL__ +INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr") +#endif +INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr") +INSTANCE_TYPEABLE1(IORef,iORefTc,"IORef") ------------------------------------------------------- -- @@ -391,21 +643,19 @@ instance (Typeable a, Typeable b) => Typeable (a -> b) where -- ------------------------------------------------------- -#ifndef __NHC__ INSTANCE_TYPEABLE0(Bool,boolTc,"Bool") INSTANCE_TYPEABLE0(Char,charTc,"Char") INSTANCE_TYPEABLE0(Float,floatTc,"Float") INSTANCE_TYPEABLE0(Double,doubleTc,"Double") INSTANCE_TYPEABLE0(Int,intTc,"Int") +#ifndef __NHC__ +INSTANCE_TYPEABLE0(Word,wordTc,"Word" ) +#endif 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") +#ifndef __GLASGOW_HASKELL__ INSTANCE_TYPEABLE0(Handle,handleTc,"Handle") -INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr") -INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr") +#endif INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8") INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16") @@ -420,18 +670,23 @@ INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64") INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon") INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep") -INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef") -#endif - #ifdef __GLASGOW_HASKELL__ -INSTANCE_TYPEABLE0(Word,wordTc,"Word" ) -#endif - +{- +TODO: This can't be derived currently: +libraries/base/Data/Typeable.hs:674:1: + Can't make a derived instance of `Typeable RealWorld': + The last argument of the instance must be a data or newtype application + In the stand-alone deriving instance for `Typeable RealWorld' +-} +realWorldTc :: TyCon; \ +realWorldTc = mkTyCon "GHC.Base.RealWorld"; \ +instance Typeable RealWorld where { typeOf _ = mkTyConApp realWorldTc [] } +#endif --------------------------------------------- -- --- Internals +-- Internals -- --------------------------------------------- @@ -444,40 +699,49 @@ data KeyPr = KeyPr !Key !Key deriving( Eq ) hashKP :: KeyPr -> Int32 hashKP (KeyPr (Key k1) (Key k2)) = (HT.hashInt k1 + HT.hashInt k2) `rem` HT.prime -data Cache = Cache { next_key :: !(IORef Key), - tc_tbl :: !(HT.HashTable String Key), - ap_tbl :: !(HT.HashTable KeyPr Key) } +data Cache = Cache { next_key :: !(IORef Key), -- Not used by GHC (calls genSym instead) + tc_tbl :: !(HT.HashTable String Key), + ap_tbl :: !(HT.HashTable KeyPr Key) } {-# NOINLINE cache #-} +#ifdef __GLASGOW_HASKELL__ +foreign import ccall unsafe "RtsTypeable.h getOrSetTypeableStore" + getOrSetTypeableStore :: Ptr a -> IO (Ptr a) +#endif + cache :: Cache cache = unsafePerformIO $ do - empty_tc_tbl <- HT.new (==) HT.hashString - empty_ap_tbl <- HT.new (==) hashKP - key_loc <- newIORef (Key 1) - return (Cache { next_key = key_loc, - tc_tbl = empty_tc_tbl, - ap_tbl = empty_ap_tbl }) + empty_tc_tbl <- HT.new (==) HT.hashString + empty_ap_tbl <- HT.new (==) hashKP + key_loc <- newIORef (Key 1) + let ret = Cache { next_key = key_loc, + tc_tbl = empty_tc_tbl, + ap_tbl = empty_ap_tbl } +#ifdef __GLASGOW_HASKELL__ + mask_ $ do + stable_ref <- newStablePtr ret + let ref = castStablePtrToPtr stable_ref + ref2 <- getOrSetTypeableStore ref + if ref==ref2 + then deRefStablePtr stable_ref + else do + freeStablePtr stable_ref + deRefStablePtr + (castPtrToStablePtr ref2) +#else + return ret +#endif newKey :: IORef Key -> IO Key #ifdef __GLASGOW_HASKELL__ -newKey kloc = do i <- genSym; return (Key i) +newKey _ = do i <- genSym; return (Key i) #else newKey kloc = do { k@(Key i) <- readIORef kloc ; - writeIORef kloc (Key (i+1)) ; - return k } + writeIORef kloc (Key (i+1)) ; + return k } #endif #ifdef __GLASGOW_HASKELL__ --- In GHC we use the RTS's genSym function to get a new unique, --- because in GHCi we might have two copies of the Data.Typeable --- library running (one in the compiler and one in the running --- program), and we need to make sure they don't share any keys. --- --- This is really a hack. A better solution would be to centralise the --- whole mutable state used by this module, i.e. both hashtables. But --- the current solution solves the immediate problem, which is that --- dynamics generated in one world with one type were erroneously --- being recognised by the other world as having a different type. foreign import ccall unsafe "genSymZh" genSym :: IO Int #endif @@ -485,101 +749,26 @@ foreign import ccall unsafe "genSymZh" mkTyConKey :: String -> Key mkTyConKey str = unsafePerformIO $ do - let Cache {next_key = kloc, tc_tbl = tbl} = cache - mb_k <- HT.lookup tbl str - case mb_k of - Just k -> return k - Nothing -> do { k <- newKey kloc ; - HT.insert tbl str k ; - return k } + let Cache {next_key = kloc, tc_tbl = tbl} = cache + mb_k <- HT.lookup tbl str + case mb_k of + Just k -> return k + Nothing -> do { k <- newKey kloc ; + HT.insert tbl str k ; + return k } appKey :: Key -> Key -> Key appKey k1 k2 = unsafePerformIO $ do - let Cache {next_key = kloc, ap_tbl = tbl} = cache - mb_k <- HT.lookup tbl kpr - case mb_k of - Just k -> return k - Nothing -> do { k <- newKey kloc ; - HT.insert tbl kpr k ; - return k } + let Cache {next_key = kloc, ap_tbl = tbl} = cache + mb_k <- HT.lookup tbl kpr + case mb_k of + Just k -> return k + Nothing -> do { k <- newKey kloc ; + HT.insert tbl kpr k ; + return k } where kpr = KeyPr k1 k2 appKeys :: Key -> [Key] -> Key appKeys k ks = foldl appKey k ks - - - ------------------------------------------------------------------------------- --- --- Typeable adopted for unary type constructors --- This adoption is at an experimental stage. --- ------------------------------------------------------------------------------- - - --- | Variant for unary type constructors -class Typeable1 t where - typeOf1 :: t a -> TypeRep - - --- | Variant for binary type constructors -class Typeable2 t where - typeOf2 :: t a b -> TypeRep - - -#ifndef __NHC__ - --- | Instance for lists -instance Typeable1 [] where - typeOf1 _ = mkAppTy (typerepTyCon (typeOf (undefined::[()]))) [] - - --- | Instance for maybes -instance Typeable1 Maybe where - typeOf1 _ = mkAppTy (typerepTyCon (typeOf (undefined::Maybe ()))) [] - - --- | Instance for ratios -instance Typeable1 Ratio where - typeOf1 _ = mkAppTy (typerepTyCon (typeOf (undefined::Ratio ()))) [] - - --- | Instance for products -instance Typeable2 (,) where - typeOf2 _ = mkAppTy (typerepTyCon (typeOf (undefined::((),())))) [] - - --- | Instance for sums -instance Typeable2 Either where - typeOf2 _ = mkAppTy (typerepTyCon (typeOf (undefined::Either () ()))) [] - - --- | Instance for functions -instance Typeable2 (->) where - typeOf2 _ = mkAppTy (typerepTyCon (typeOf (undefined::() -> ()))) [] - -#endif - - --- | 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 - - --- | 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