Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch : new-typeable
http://hackage.haskell.org/trac/ghc/changeset/bf664ead63d68f90efb4ac96ee9d1cc8fecab942 >--------------------------------------------------------------- commit bf664ead63d68f90efb4ac96ee9d1cc8fecab942 Author: Jose Pedro Magalhaes <j...@cs.ox.ac.uk> Date: Wed Oct 3 15:31:36 2012 +0100 Remove warnings >--------------------------------------------------------------- compiler/utils/Bag.lhs | 5 +++++ compiler/utils/Serialized.hs | 14 +++++++++++--- 2 files changed, 16 insertions(+), 3 deletions(-) diff --git a/compiler/utils/Bag.lhs b/compiler/utils/Bag.lhs index a833978..7ced9d5 100644 --- a/compiler/utils/Bag.lhs +++ b/compiler/utils/Bag.lhs @@ -6,6 +6,7 @@ Bag: an unordered collection with duplicates \begin{code} +{-# LANGUAGE CPP #-} module Bag ( Bag, -- abstract type @@ -265,7 +266,11 @@ instance (Outputable a) => Outputable (Bag a) where instance Data a => Data (Bag a) where gfoldl k z b = z listToBag `k` bagToList b -- traverse abstract type abstractly +#if __GLASGOW_HASKELL__ > 706 + toConstr _ = abstractConstr $ "Bag("++show (typeRep (Proxy :: Proxy a))++")" +#else toConstr _ = abstractConstr $ "Bag("++show (typeOf (undefined::a))++")" +#endif gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "Bag" dataCast1 x = gcast1 x diff --git a/compiler/utils/Serialized.hs b/compiler/utils/Serialized.hs index 902d2fe..e748d91 100644 --- a/compiler/utils/Serialized.hs +++ b/compiler/utils/Serialized.hs @@ -43,15 +43,23 @@ instance Binary Serialized where return (Serialized the_type bytes) -- | Put a Typeable value that we are able to actually turn into bytes into a 'Serialized' value ready for deserialization later -toSerialized :: Typeable a => (a -> [Word8]) -> a -> Serialized +toSerialized :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized +#if __GLASGOW_HASKELL__ > 706 +toSerialized serialize what = Serialized (typeRep (Proxy :: Proxy a)) (serialize what) +#else toSerialized serialize what = Serialized (typeOf what) (serialize what) +#endif -- | If the 'Serialized' value contains something of the given type, then use the specified deserializer to return @Just@ that. -- Otherwise return @Nothing@. fromSerialized :: forall a. Typeable a => ([Word8] -> a) -> Serialized -> Maybe a fromSerialized deserialize (Serialized the_type bytes) - | the_type == typeOf (undefined :: a) = Just (deserialize bytes) - | otherwise = Nothing +#if __GLASGOW_HASKELL__ > 706 + | the_type == typeRep (Proxy :: Proxy a) = Just (deserialize bytes) +#else + | the_type == typeOf (undefined :: a) = Just (deserialize bytes) +#endif + | otherwise = Nothing -- | Force the contents of the Serialized value so weknow it doesn't contain any bottoms seqSerialized :: Serialized -> () _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc