[commit: packages/containers] ghc-head: -Wall police (1f66cb9)
git at git.haskell.org
git at git.haskell.org
Fri Aug 30 13:34:02 CEST 2013
Repository : ssh://git@git.haskell.org/containers
On branch : ghc-head
Link : http://git.haskell.org/?p=packages/containers.git;a=commit;h=1f66cb9808b9ff1c90f2021bbd9112fc5637d0ac
>---------------------------------------------------------------
commit 1f66cb9808b9ff1c90f2021bbd9112fc5637d0ac
Author: Johan Tibell <johan.tibell at gmail.com>
Date: Thu Sep 20 11:28:41 2012 +0200
-Wall police
>---------------------------------------------------------------
1f66cb9808b9ff1c90f2021bbd9112fc5637d0ac
Data/Map/Base.hs | 4 ++--
Data/Map/Strict.hs | 4 ++--
Data/Set/Base.hs | 4 ++--
3 files changed, 6 insertions(+), 6 deletions(-)
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index edf0241..146c5f3 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -1932,11 +1932,11 @@ fromList [(kx, x)] = Bin 1 kx x Tip Tip
fromList ((kx0, x0) : xs0) | not_ordered kx0 xs0 = fromList' (Bin 1 kx0 x0 Tip Tip) xs0
| otherwise = go (1::Int) (Bin 1 kx0 x0 Tip Tip) xs0
where
- not_ordered kx [] = False
+ not_ordered _ [] = False
not_ordered kx ((ky,_) : _) = kx >= ky
{-# INLINE not_ordered #-}
- fromList' t xs = foldlStrict ins t xs
+ fromList' t0 xs = foldlStrict ins t0 xs
where ins t (k,x) = insert k x t
STRICT_1_OF_3(go)
diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs
index 7bdbc7d..9ecefcc 100644
--- a/Data/Map/Strict.hs
+++ b/Data/Map/Strict.hs
@@ -1026,11 +1026,11 @@ fromList [(kx, x)] = x `seq` Bin 1 kx x Tip Tip
fromList ((kx0, x0) : xs0) | not_ordered kx0 xs0 = x0 `seq` fromList' (Bin 1 kx0 x0 Tip Tip) xs0
| otherwise = x0 `seq` go (1::Int) (Bin 1 kx0 x0 Tip Tip) xs0
where
- not_ordered kx [] = False
+ not_ordered _ [] = False
not_ordered kx ((ky,_) : _) = kx >= ky
{-# INLINE not_ordered #-}
- fromList' t xs = foldlStrict ins t xs
+ fromList' t0 xs = foldlStrict ins t0 xs
where ins t (k,x) = insert k x t
STRICT_1_OF_3(go)
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index a3a49bd..5247261 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -790,11 +790,11 @@ fromList [x] = Bin 1 x Tip Tip
fromList (x0 : xs0) | not_ordered x0 xs0 = fromList' (Bin 1 x0 Tip Tip) xs0
| otherwise = go (1::Int) (Bin 1 x0 Tip Tip) xs0
where
- not_ordered x [] = False
+ not_ordered _ [] = False
not_ordered x (y : _) = x >= y
{-# INLINE not_ordered #-}
- fromList' t xs = foldlStrict ins t xs
+ fromList' t0 xs = foldlStrict ins t0 xs
where ins t x = insert x t
STRICT_1_OF_3(go)
More information about the ghc-commits
mailing list