From 42ab5405e4c988eba25f627d0df133b27e4ce42b Mon Sep 17 00:00:00 2001 From: Peter Selinger <selinger@mathstat.dal.ca> Date: Fri, 4 Jul 2014 10:47:35 -0300 Subject: [PATCH] Fixed syntax of fixity declarations. --- Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 8e918c86..1a73af41 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -455,7 +455,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -465,7 +465,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -882,7 +882,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -947,7 +947,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index f9c6abeb..86742cb9 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -316,13 +316,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +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 +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -511,7 +511,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -586,7 +586,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index edbf1315..2feb7b2b 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -467,7 +467,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -482,7 +482,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1246,7 +1246,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1368,7 +1368,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 6379cd9f..5d2b1b64 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -362,7 +362,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -373,7 +373,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -626,7 +626,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -686,7 +686,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip -- GitLab