[commit: packages/containers] changelog-foldtree, cleaned_bugfix394, develop, develop-0.6, develop-0.6-questionable, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-184-generic, revert-408-bugfix_394, zip-devel: Revert "Added fixity declarations for member, notMember, union, and intersection." (3b1eee5)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:33:48 UTC 2017


Repository : ssh://git@git.haskell.org/containers

On branches: changelog-foldtree,cleaned_bugfix394,develop,develop-0.6,develop-0.6-questionable,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-184-generic,revert-408-bugfix_394,zip-devel
Link       : http://git.haskell.org/packages/containers.git/commitdiff/3b1eee514581edcc51c3c4304087e2dff30e05cd

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

commit 3b1eee514581edcc51c3c4304087e2dff30e05cd
Author: Johan Tibell <johan.tibell at gmail.com>
Date:   Tue Jul 22 17:09:50 2014 +0200

    Revert "Added fixity declarations for member, notMember, union, and intersection."
    
    This reverts commit 3999b512f5aa28a7b119a18b286a8485d1285319.


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

3b1eee514581edcc51c3c4304087e2dff30e05cd
 Data/IntMap/Base.hs | 8 --------
 Data/IntSet/Base.hs | 7 -------
 Data/Map/Base.hs    | 8 --------
 Data/Set/Base.hs    | 8 --------
 4 files changed, 31 deletions(-)

diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 9f7be70..75b3ae9 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -395,8 +395,6 @@ member k = k `seq` go
     go (Tip kx _) = k == kx
     go Nil = False
 
-infix 4 member
-
 -- | /O(min(n,W))/. Is the key not a member of the map?
 --
 -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False
@@ -405,8 +403,6 @@ infix 4 member
 notMember :: Key -> IntMap a -> Bool
 notMember k m = not $ member k m
 
-infix 4 notMember
-
 -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'.
 
 -- See Note: Local 'go' functions and capturing]
@@ -822,8 +818,6 @@ union :: IntMap a -> IntMap a -> IntMap a
 union m1 m2
   = mergeWithKey' Bin const id id m1 m2
 
-infixl 5 union
-
 -- | /O(n+m)/. The union with a combining function.
 --
 -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
@@ -887,8 +881,6 @@ intersection :: IntMap a -> IntMap b -> IntMap a
 intersection m1 m2
   = mergeWithKey' bin const (const Nil) (const Nil) m1 m2
 
-infixl 5 intersection
-
 -- | /O(n+m)/. The intersection with a combining function.
 --
 -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs
index 9719de1..0063c3f 100644
--- a/Data/IntSet/Base.hs
+++ b/Data/IntSet/Base.hs
@@ -332,14 +332,10 @@ member x = x `seq` go
     go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0
     go Nil = False
 
-infix 4 member
-
 -- | /O(min(n,W))/. Is the element not in the set?
 notMember :: Key -> IntSet -> Bool
 notMember k = not . member k
 
-infix 4 notMember
-
 -- | /O(log n)/. Find largest element smaller than the given one.
 --
 -- > lookupLT 3 (fromList [3, 5]) == Nothing
@@ -527,7 +523,6 @@ union t@(Bin _ _ _ _) Nil = t
 union (Tip kx bm) t = insertBM kx bm t
 union Nil t = t
 
-infixl 5 union
 
 {--------------------------------------------------------------------
   Difference
@@ -602,8 +597,6 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2
 
 intersection Nil _ = Nil
 
-infixl 5 intersection
-
 {--------------------------------------------------------------------
   Subset
 --------------------------------------------------------------------}
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 9d066fa..db9549f 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -456,8 +456,6 @@ member = go
 {-# INLINE member #-}
 #endif
 
-infix 4 member
-
 -- | /O(log n)/. Is the key not a member of the map? See also 'member'.
 --
 -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False
@@ -471,8 +469,6 @@ notMember k m = not $ member k m
 {-# INLINE notMember #-}
 #endif
 
-infix 4 notMember
-
 -- | /O(log n)/. Find the value at a key.
 -- Calls 'error' when the element can not be found.
 find :: Ord k => k -> Map k a -> a
@@ -1234,8 +1230,6 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2
 {-# INLINABLE union #-}
 #endif
 
-infixl 5 union
-
 -- left-biased hedge union
 hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b
 hedgeUnion _   _   t1  Tip = t1
@@ -1356,8 +1350,6 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2
 {-# INLINABLE intersection #-}
 #endif
 
-infixl 5 intersection
-
 hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a
 hedgeInt _ _ _   Tip = Tip
 hedgeInt _ _ Tip _   = Tip
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index 5727de6..ffcdfd0 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -318,8 +318,6 @@ member = go
 {-# INLINE member #-}
 #endif
 
-infix 4 member
-
 -- | /O(log n)/. Is the element not in the set?
 notMember :: Ord a => a -> Set a -> Bool
 notMember a t = not $ member a t
@@ -329,8 +327,6 @@ notMember a t = not $ member a t
 {-# INLINE notMember #-}
 #endif
 
-infix 4 notMember
-
 -- | /O(log n)/. Find largest element smaller than the given one.
 --
 -- > lookupLT 3 (fromList [3, 5]) == Nothing
@@ -582,8 +578,6 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2
 {-# INLINABLE union #-}
 #endif
 
-infixl 5 union
-
 hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a
 hedgeUnion _   _   t1  Tip = t1
 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r)
@@ -642,8 +636,6 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2
 {-# INLINABLE intersection #-}
 #endif
 
-infixl 5 intersection
-
 hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a
 hedgeInt _ _ _   Tip = Tip
 hedgeInt _ _ Tip _   = Tip



More information about the ghc-commits mailing list