Repository : ssh://darcs.haskell.org//srv/darcs/packages/deepseq

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/0b1dbecfd13feba1720a1e76735815c6bb40590a

>---------------------------------------------------------------

commit 0b1dbecfd13feba1720a1e76735815c6bb40590a
Author: Ian Lynagh <[email protected]>
Date:   Thu Sep 8 12:19:43 2011 +0100

    Don't include containers instances; part of #5468
    
    containers now defines its own instances.
    
    Also, we now have a {-# LANGUAGE Safe #-} pragma, needed to make the
    GHC build go through.

>---------------------------------------------------------------

 Control/DeepSeq.hs |   23 +++--------------------
 deepseq.cabal      |    2 +-
 2 files changed, 4 insertions(+), 21 deletions(-)

diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs
index d59aebb..021fb74 100644
--- a/Control/DeepSeq.hs
+++ b/Control/DeepSeq.hs
@@ -1,3 +1,6 @@
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Safe #-}
+#endif
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.DeepSeq
@@ -50,11 +53,6 @@ import Data.Int
 import Data.Word
 import Data.Ratio
 import Data.Complex
-import Data.Map
-import Data.Set
-import Data.IntMap
-import Data.IntSet
-import Data.Tree
 import Data.Array
 
 infixr 0 $!!
@@ -150,21 +148,6 @@ instance (NFData a, NFData b) => NFData (Either a b) where
     rnf (Left x)  = rnf x
     rnf (Right y) = rnf y
 
-instance (NFData k, NFData a) => NFData (Data.Map.Map k a) where
-    rnf = rnf . Data.Map.toList
-
-instance NFData a => NFData (Data.Set.Set a) where
-    rnf = rnf . Data.Set.toList
-
-instance NFData a => NFData (Data.Tree.Tree a) where
-    rnf (Data.Tree.Node r f) = rnf r `seq` rnf f
-
-instance NFData a => NFData (Data.IntMap.IntMap a) where
-    rnf = rnf . Data.IntMap.toList
-
-instance NFData Data.IntSet.IntSet where
-    rnf = rnf . Data.IntSet.toList
-
 instance NFData a => NFData [a] where
     rnf [] = ()
     rnf (x:xs) = rnf x `seq` rnf xs
diff --git a/deepseq.cabal b/deepseq.cabal
index 5db632e..f8be57a 100644
--- a/deepseq.cabal
+++ b/deepseq.cabal
@@ -29,7 +29,7 @@ source-repository head
 library {
   exposed-modules: Control.DeepSeq
   build-depends: base       >= 3   && < 5, 
-                 containers >= 0.1 && < 0.5,
                  array      >= 0.1 && < 0.4
   ghc-options: -Wall
+  extensions: CPP
 }



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to