[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Kill a bunch of silly warnings. (51bc08c)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:44:49 UTC 2017


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

On branches: cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/51bc08cbcb17faacb5ed687241ab93116ff3b8ad

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

commit 51bc08cbcb17faacb5ed687241ab93116ff3b8ad
Author: David Feuer <David.Feuer at gmail.com>
Date:   Wed Aug 10 16:39:04 2016 -0400

    Kill a bunch of silly warnings.
    
    Just name shadowing and unused binding nonsense.


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

51bc08cbcb17faacb5ed687241ab93116ff3b8ad
 Data/Map/Base.hs          | 18 +++++++++---------
 Data/Map/Strict.hs        | 12 ++++++------
 Data/Utils/PtrEquality.hs |  1 -
 3 files changed, 15 insertions(+), 16 deletions(-)

diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 07b7127..ff52b10 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -704,7 +704,7 @@ insertR = go
   where
     go :: Ord k => k -> a -> Map k a -> Map k a
     go !kx x Tip = singleton kx x
-    go kx x t@(Bin sz ky y l r) =
+    go kx x t@(Bin _ ky y l r) =
         case compare kx ky of
             LT | l' `ptrEq` l -> t
                | otherwise -> balanceL ky y l' r
@@ -1781,9 +1781,9 @@ restrictKeys m@(Bin _ k x l1 r1) s
 intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
 -- We have no hope of pointer equality tricks here because every single
 -- element in the result will be a thunk.
-intersectionWith f Tip _ = Tip
-intersectionWith f _ Tip = Tip
-intersectionWith f t1@(Bin _ k x1 l1 r1) t2 = case mb of
+intersectionWith _f Tip _ = Tip
+intersectionWith _f _ Tip = Tip
+intersectionWith f (Bin _ k x1 l1 r1) t2 = case mb of
     Just x2 -> link k (f x1 x2) l1l2 r1r2
     Nothing -> merge l1l2 r1r2
   where
@@ -1800,9 +1800,9 @@ intersectionWith f t1@(Bin _ k x1 l1 r1) t2 = case mb of
 -- > intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
 
 intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
-intersectionWithKey f Tip _ = Tip
-intersectionWithKey f _ Tip = Tip
-intersectionWithKey f t1@(Bin _ k x1 l1 r1) t2 = case mb of
+intersectionWithKey _f Tip _ = Tip
+intersectionWithKey _f _ Tip = Tip
+intersectionWithKey f (Bin _ k x1 l1 r1) t2 = case mb of
     Just x2 -> link k (f k x1 x2) l1l2 r1r2
     Nothing -> merge l1l2 r1r2
   where
@@ -2797,7 +2797,7 @@ split !k0 t0 = toPair $ go k0 t0
 -- > splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
 -- > splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
 splitLookup :: Ord k => k -> Map k a -> (Map k a,Maybe a,Map k a)
-splitLookup k m = case go k m of
+splitLookup k0 m = case go k0 m of
      StrictTriple l mv r -> (l, mv, r)
   where
     go :: Ord k => k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
@@ -2821,7 +2821,7 @@ splitLookup k m = case go k m of
 -- implement 'intersection' to avoid allocating unnecessary 'Just'
 -- constructors.
 splitMember :: Ord k => k -> Map k a -> (Map k a,Bool,Map k a)
-splitMember k m = case go k m of
+splitMember k0 m = case go k0 m of
      StrictTriple l mv r -> (l, mv, r)
   where
     go :: Ord k => k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs
index ba059ec..6e1f6e0 100644
--- a/Data/Map/Strict.hs
+++ b/Data/Map/Strict.hs
@@ -928,9 +928,9 @@ differenceWithKey f t1 t2 = mergeWithKey f id (const Tip) t1 t2
 -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
 
 intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
-intersectionWith f Tip _ = Tip
-intersectionWith f _ Tip = Tip
-intersectionWith f t1@(Bin _ k x1 l1 r1) t2 = case mb of
+intersectionWith _f Tip _ = Tip
+intersectionWith _f _ Tip = Tip
+intersectionWith f (Bin _ k x1 l1 r1) t2 = case mb of
     Just x2 -> let !x1' = f x1 x2 in link k x1' l1l2 r1r2
     Nothing -> merge l1l2 r1r2
   where
@@ -947,9 +947,9 @@ intersectionWith f t1@(Bin _ k x1 l1 r1) t2 = case mb of
 -- > intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
 
 intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
-intersectionWithKey f Tip _ = Tip
-intersectionWithKey f _ Tip = Tip
-intersectionWithKey f t1@(Bin _ k x1 l1 r1) t2 = case mb of
+intersectionWithKey _f Tip _ = Tip
+intersectionWithKey _f _ Tip = Tip
+intersectionWithKey f (Bin _ k x1 l1 r1) t2 = case mb of
     Just x2 -> let !x1' = f k x1 x2 in link k x1' l1l2 r1r2
     Nothing -> merge l1l2 r1r2
   where
diff --git a/Data/Utils/PtrEquality.hs b/Data/Utils/PtrEquality.hs
index ca89af5..bdbb87d 100644
--- a/Data/Utils/PtrEquality.hs
+++ b/Data/Utils/PtrEquality.hs
@@ -7,7 +7,6 @@ module Data.Utils.PtrEquality (ptrEq) where
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Exts ( reallyUnsafePtrEquality# )
-import Unsafe.Coerce (unsafeCoerce)
 #if __GLASGOW_HASKELL__ < 707
 import GHC.Exts ( (==#) )
 #else



More information about the ghc-commits mailing list