Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch : new-typeable
http://hackage.haskell.org/trac/ghc/changeset/bf0bfb7e2e2b11f6f9868a75b1730278caae3f24 >--------------------------------------------------------------- commit bf0bfb7e2e2b11f6f9868a75b1730278caae3f24 Author: Jose Pedro Magalhaes <j...@cs.ox.ac.uk> Date: Mon Nov 19 10:57:34 2012 +0000 Remove unnecessary CPP >--------------------------------------------------------------- compiler/utils/Bag.lhs | 5 ----- compiler/utils/Serialized.hs | 14 +++----------- 2 files changed, 3 insertions(+), 16 deletions(-) diff --git a/compiler/utils/Bag.lhs b/compiler/utils/Bag.lhs index 7ced9d5..a833978 100644 --- a/compiler/utils/Bag.lhs +++ b/compiler/utils/Bag.lhs @@ -6,7 +6,6 @@ Bag: an unordered collection with duplicates \begin{code} -{-# LANGUAGE CPP #-} module Bag ( Bag, -- abstract type @@ -266,11 +265,7 @@ 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 e748d91..902d2fe 100644 --- a/compiler/utils/Serialized.hs +++ b/compiler/utils/Serialized.hs @@ -43,23 +43,15 @@ 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 :: forall a. Typeable a => (a -> [Word8]) -> a -> Serialized -#if __GLASGOW_HASKELL__ > 706 -toSerialized serialize what = Serialized (typeRep (Proxy :: Proxy a)) (serialize what) -#else +toSerialized :: Typeable a => (a -> [Word8]) -> a -> Serialized 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) -#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 + | the_type == typeOf (undefined :: a) = Just (deserialize bytes) + | 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