X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Data%2FTypeable.hs;h=804e853b8de6aec58f024901f498eda4b0b4c127;hb=41e8fba828acbae1751628af50849f5352b27873;hp=c400710b4418e3f3785db2bce03ae48a6622cf87;hpb=d2063b5b0be014545b21819172c87756efcb0b0c;p=ghc-base.git diff --git a/Data/Typeable.hs b/Data/Typeable.hs index c400710..804e853 100644 --- a/Data/Typeable.hs +++ b/Data/Typeable.hs @@ -1,4 +1,11 @@ -{-# OPTIONS_GHC -XNoImplicitPrelude -XOverlappingInstances -funbox-strict-fields #-} +{-# LANGUAGE CPP + , NoImplicitPrelude + , OverlappingInstances + , ScopedTypeVariables + , ForeignFunctionInterface + , FlexibleInstances + #-} +{-# OPTIONS_GHC -funbox-strict-fields #-} -- The -XOverlappingInstances flag allows the user to over-ride -- the instances for Typeable given here. In particular, we provide an instance @@ -93,10 +100,10 @@ import GHC.Base import GHC.Show (Show(..), ShowS, shows, showString, showChar, showParen) import GHC.Err (undefined) -import GHC.Num (Integer, fromInteger, (+)) +import GHC.Num (Integer, (+)) import GHC.Real ( rem, Ratio ) import GHC.IORef (IORef,newIORef) -import GHC.IO (IO, unsafePerformIO,block) +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 @@ -302,6 +309,22 @@ showTuple args = showChar '(' -- ------------------------------------------------------------- +{- 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 @@ -315,78 +338,148 @@ class Typeable a where 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 + 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 + 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 + 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 - + 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 + 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 + 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 + argType = undefined +#endif #ifdef __GLASGOW_HASKELL__ -- Given a @Typeable@/n/ instance for an /n/-ary type constructor, @@ -595,7 +688,7 @@ cache = unsafePerformIO $ do tc_tbl = empty_tc_tbl, ap_tbl = empty_ap_tbl } #ifdef __GLASGOW_HASKELL__ - block $ do + mask_ $ do stable_ref <- newStablePtr ret let ref = castStablePtrToPtr stable_ref ref2 <- getOrSetTypeableStore ref