[commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Added fixity declarations for member, notMember, union, and intersection. (3999b51)
git at git.haskell.org
git at git.haskell.org
Fri Jan 23 22:38:45 UTC 2015
- Previous message: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #44 from thoughtpolice/amp (e84c5d2)
- Next message: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Added fixity declarations for member, notMember, union, and intersection. (3999b51)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
Repository : ssh://git@git.haskell.org/containers
On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel
Link : http://git.haskell.org/packages/containers.git/commitdiff/3999b512f5aa28a7b119a18b286a8485d1285319
>---------------------------------------------------------------
commit 3999b512f5aa28a7b119a18b286a8485d1285319
Author: Peter Selinger <selinger at mathstat.dal.ca>
Date: Fri Jul 4 10:31:20 2014 -0300
Added fixity declarations for member, notMember, union, and intersection.
>---------------------------------------------------------------
3999b512f5aa28a7b119a18b286a8485d1285319
Data/IntMap/Base.hs | 8 ++++++++
Data/IntSet/Base.hs | 7 +++++++
Data/Map/Base.hs | 8 ++++++++
Data/Set/Base.hs | 8 ++++++++
4 files changed, 31 insertions(+)
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 75b3ae9..9f7be70 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -395,6 +395,8 @@ 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
@@ -403,6 +405,8 @@ member k = k `seq` go
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]
@@ -818,6 +822,8 @@ 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")]
@@ -881,6 +887,8 @@ 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 0063c3f..9719de1 100644
--- a/Data/IntSet/Base.hs
+++ b/Data/IntSet/Base.hs
@@ -332,10 +332,14 @@ 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
@@ -523,6 +527,7 @@ union t@(Bin _ _ _ _) Nil = t
union (Tip kx bm) t = insertBM kx bm t
union Nil t = t
+infixl 5 union
{--------------------------------------------------------------------
Difference
@@ -597,6 +602,8 @@ 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 db9549f..9d066fa 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -456,6 +456,8 @@ 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
@@ -469,6 +471,8 @@ 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
@@ -1230,6 +1234,8 @@ 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
@@ -1350,6 +1356,8 @@ 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 ffcdfd0..5727de6 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -318,6 +318,8 @@ 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
@@ -327,6 +329,8 @@ 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
@@ -578,6 +582,8 @@ 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)
@@ -636,6 +642,8 @@ 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
- Previous message: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #44 from thoughtpolice/amp (e84c5d2)
- Next message: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Added fixity declarations for member, notMember, union, and intersection. (3999b51)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
More information about the ghc-commits
mailing list