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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/6665d7ae5b3f101fd4f016b8edf733ed004d8fb4

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

commit 6665d7ae5b3f101fd4f016b8edf733ed004d8fb4
Author: Milan Straka <[email protected]>
Date:   Thu Nov 24 16:03:07 2011 +0100

    Extensions are now maintained per-file.
    
    We drop the cabal support for extensions and instead list
    all needed extensions in the file needing them.
    
    It is a bit ugly, but feels better. We can now compile individual
    files without cabal support (i.e., we can do ghci file).

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

 Data/Graph.hs         |    4 ++++
 Data/IntMap/Base.hs   |   13 +++++--------
 Data/IntMap/Strict.hs |   10 ++--------
 Data/IntSet.hs        |    4 ++++
 Data/Map/Base.hs      |    5 ++++-
 Data/Sequence.hs      |    4 ++++
 Data/Set.hs           |    3 +++
 Data/Tree.hs          |    4 ++++
 containers.cabal      |    7 -------
 9 files changed, 30 insertions(+), 24 deletions(-)

diff --git a/Data/Graph.hs b/Data/Graph.hs
index a2029ff..8c481ba 100644
--- a/Data/Graph.hs
+++ b/Data/Graph.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE Rank2Types #-}
+#endif
 #if __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Trustworthy #-}
 #endif
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index eeaa72e..b881e3c 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE NoBangPatterns, ScopedTypeVariables #-}
+{-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE MagicHash, DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Trustworthy #-}
 #endif
@@ -1633,20 +1636,14 @@ fromAscListWithKey f (x0 : xs0) = fromDistinctAscList 
(combineEq x0 xs0)
 --
 -- > fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
 
-#ifdef __GLASGOW_HASKELL__
-fromDistinctAscList :: forall a. [(Key,a)] -> IntMap a
-#else
-fromDistinctAscList ::           [(Key,a)] -> IntMap a
-#endif
+fromDistinctAscList :: [(Key,a)] -> IntMap a
 fromDistinctAscList []         = Nil
 fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada
   where
     work (kx,vx) []            stk = finish kx (Tip kx vx) stk
     work (kx,vx) (z@(kz,_):zs) stk = reduce z zs (branchMask kx kz) kx (Tip kx 
vx) stk
 
-#ifdef __GLASGOW_HASKELL__
     reduce :: (Key,a) -> [(Key,a)] -> Mask -> Prefix -> IntMap a -> Stack a -> 
IntMap a
-#endif
     reduce z zs _ px tx Nada = work z zs (Push px tx Nada)
     reduce z zs m px tx stk@(Push py ty stk') =
         let mxy = branchMask px py
diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs
index a576c08..26185c2 100644
--- a/Data/IntMap/Strict.hs
+++ b/Data/IntMap/Strict.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE NoBangPatterns, ScopedTypeVariables #-}
+{-# LANGUAGE CPP #-}
 #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Trustworthy #-}
 #endif
@@ -842,20 +842,14 @@ fromAscListWithKey f (x0 : xs0) = fromDistinctAscList 
(combineEq x0 xs0)
 --
 -- > fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
 
-#ifdef __GLASGOW_HASKELL__
-fromDistinctAscList :: forall a. [(Key,a)] -> IntMap a
-#else
-fromDistinctAscList ::           [(Key,a)] -> IntMap a
-#endif
+fromDistinctAscList :: [(Key,a)] -> IntMap a
 fromDistinctAscList []         = Nil
 fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada
   where
     work (kx,vx) []            stk = vx `seq` finish kx (Tip kx vx) stk
     work (kx,vx) (z@(kz,_):zs) stk = vx `seq` reduce z zs (branchMask kx kz) 
kx (Tip kx vx) stk
 
-#ifdef __GLASGOW_HASKELL__
     reduce :: (Key,a) -> [(Key,a)] -> Mask -> Prefix -> IntMap a -> Stack a -> 
IntMap a
-#endif
     reduce z zs _ px tx Nada = work z zs (Push px tx Nada)
     reduce z zs m px tx stk@(Push py ty stk') =
         let mxy = branchMask px py
diff --git a/Data/IntSet.hs b/Data/IntSet.hs
index 390c335..58b12d4 100644
--- a/Data/IntSet.hs
+++ b/Data/IntSet.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE MagicHash, DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Trustworthy #-}
 #endif
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 377ec15..d32eb3d 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE CPP, NoBangPatterns #-}
+{-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Safe #-}
 #endif
diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index add2e6e..5150aba 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 #if __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Trustworthy #-}
 #endif
diff --git a/Data/Set.hs b/Data/Set.hs
index 81cb4cd..daab0c6 100644
--- a/Data/Set.hs
+++ b/Data/Set.hs
@@ -1,4 +1,7 @@
 {-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Safe #-}
 #endif
diff --git a/Data/Tree.hs b/Data/Tree.hs
index 21a29d6..56af20f 100644
--- a/Data/Tree.hs
+++ b/Data/Tree.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+#if __GLASGOW_HASKELL__
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 #if __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Safe #-}
 #endif
diff --git a/containers.cabal b/containers.cabal
index 7631716..84ee7d0 100644
--- a/containers.cabal
+++ b/containers.cabal
@@ -51,13 +51,6 @@ Library
 
     include-dirs: include
 
-    extensions: CPP
-    if impl(ghc)
-        extensions:
-            DeriveDataTypeable
-            StandaloneDeriving
-            MagicHash
-            Rank2Types
     if flag(testing)
         cpp-options: -DTESTING
 



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

Reply via email to