Repository : ssh://darcs.haskell.org//srv/darcs/packages/containers

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/53ae69346098a3ebc2015b3ee73f2b830d2a2e81

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

commit 53ae69346098a3ebc2015b3ee73f2b830d2a2e81
Author: Johan Tibell <[email protected]>
Date:   Sun Nov 20 22:32:30 2011 -0800

    Remove tests for deprecated functions

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

 containers.cabal        |    5 ++++
 tests/map-properties.hs |   58 ++++------------------------------------------
 2 files changed, 10 insertions(+), 53 deletions(-)

diff --git a/containers.cabal b/containers.cabal
index 8df6f4d..3bf07ae 100644
--- a/containers.cabal
+++ b/containers.cabal
@@ -22,6 +22,9 @@ source-repository head
 flag testing
     description: Expose internals for testing (required for cabal test)
 
+flag testing-strict
+    description: Test the strict API (instead of the lazy API)
+
 Library
     build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.3
     ghc-options: -O2
@@ -66,3 +69,5 @@ Test-suite map-properties
         test-framework,
         test-framework-hunit,
         test-framework-quickcheck2
+    if flag(testing-strict)
+        cpp-options: -DSTRICT
\ No newline at end of file
diff --git a/tests/map-properties.hs b/tests/map-properties.hs
index 3348a63..680f2a9 100644
--- a/tests/map-properties.hs
+++ b/tests/map-properties.hs
@@ -6,7 +6,11 @@
 
 --
 
-import Data.Map
+#ifdef STRICT
+import Data.Map.Strict as Data.Map
+#else
+import Data.Map.Lazy as Data.Map
+#endif
 import Data.Monoid
 import Data.Maybe hiding (mapMaybe)
 import Data.Ord
@@ -72,8 +76,6 @@ main = do
     q $ label   "prop_foldr"            prop_foldr
     q $ label   "prop_foldl"            prop_foldl
 --     q $ label   "prop_foldl'"           prop_foldl'
-    q $ label   "prop_fold"           prop_fold
-    q $ label   "prop_folWithKeyd"           prop_foldWithKey
 
     defaultMain tests
 
@@ -373,18 +375,6 @@ prop_foldl (n :: Int) (ys :: [(Int, Int)]) =
 --         Data.Map.foldlWithKey' (\a _ b -> a + b) n m == List.foldl' (+) n 
(List.map snd xs)
 
 
-prop_fold (n :: Int) (ys :: [(Int, Int)]) =
-    let m = fromList ys
-        xs = List.nubBy ((==) `on` fst) (reverse ys) -- note.
-    in 
-        Data.Map.fold (+) n m == List.foldr (+) n (List.map snd xs)
-
-prop_foldWithKey (n :: Int) (ys :: [(Int, Int)]) =
-    let m = fromList ys
-        xs = List.nubBy ((==) `on` fst) (reverse ys) -- note.
-    in 
-        Data.Map.foldWithKey (const (+)) n m == List.foldr (+) n (List.map snd 
xs)
-
 ------------------------------------------------------------------------
 
 type UMap = Map Int ()
@@ -408,11 +398,8 @@ tests = [ testGroup "Test Case" [
              , testCase "singleton" test_singleton
              , testCase "insert" test_insert
              , testCase "insertWith" test_insertWith
-             , testCase "insertWith'" test_insertWith'
              , testCase "insertWithKey" test_insertWithKey
-             , testCase "insertWithKey'" test_insertWithKey'
              , testCase "insertLookupWithKey" test_insertLookupWithKey
-             , testCase "insertLookupWithKey'" test_insertLookupWithKey'
              , testCase "delete" test_delete
              , testCase "adjust" test_adjust
              , testCase "adjustWithKey" test_adjustWithKey
@@ -441,8 +428,6 @@ tests = [ testGroup "Test Case" [
              , testCase "mapKeys" test_mapKeys
              , testCase "mapKeysWith" test_mapKeysWith
              , testCase "mapKeysMonotonic" test_mapKeysMonotonic
-             , testCase "fold" test_fold
-             , testCase "foldWithKey" test_foldWithKey
              , testCase "elems" test_elems
              , testCase "keys" test_keys
              , testCase "keysSet" test_keysSet
@@ -611,12 +596,6 @@ test_insertWith = do
     insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) @?= fromList [(3, 
"b"), (5, "a"), (7, "xxx")]
     insertWith (++) 5 "xxx" empty                         @?= singleton 5 "xxx"
 
-test_insertWith' :: Assertion
-test_insertWith' = do
-    insertWith' (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) @?= fromList [(3, 
"b"), (5, "xxxa")]
-    insertWith' (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) @?= fromList [(3, 
"b"), (5, "a"), (7, "xxx")]
-    insertWith' (++) 5 "xxx" empty                         @?= singleton 5 
"xxx"
-
 test_insertWithKey :: Assertion
 test_insertWithKey = do
     insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) @?= fromList [(3, 
"b"), (5, "5:xxx|a")]
@@ -625,14 +604,6 @@ test_insertWithKey = do
   where
     f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ 
old_value
 
-test_insertWithKey' :: Assertion
-test_insertWithKey' = do
-    insertWithKey' f 5 "xxx" (fromList [(5,"a"), (3,"b")]) @?= fromList [(3, 
"b"), (5, "5:xxx|a")]
-    insertWithKey' f 7 "xxx" (fromList [(5,"a"), (3,"b")]) @?= fromList [(3, 
"b"), (5, "a"), (7, "xxx")]
-    insertWithKey' f 5 "xxx" empty                         @?= singleton 5 
"xxx"
-  where
-    f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ 
old_value
-
 test_insertLookupWithKey :: Assertion
 test_insertLookupWithKey = do
     insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) @?= (Just "a", 
fromList [(3, "b"), (5, "5:xxx|a")])
@@ -642,15 +613,6 @@ test_insertLookupWithKey = do
   where
     f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ 
old_value
 
-test_insertLookupWithKey' :: Assertion
-test_insertLookupWithKey' = do
-    insertLookupWithKey' f 5 "xxx" (fromList [(5,"a"), (3,"b")]) @?= (Just 
"a", fromList [(3, "b"), (5, "5:xxx|a")])
-    insertLookupWithKey' f 2 "xxx" (fromList [(5,"a"), (3,"b")]) @?= 
(Nothing,fromList [(2,"xxx"),(3,"b"),(5,"a")])
-    insertLookupWithKey' f 7 "xxx" (fromList [(5,"a"), (3,"b")]) @?= (Nothing, 
 fromList [(3, "b"), (5, "a"), (7, "xxx")])
-    insertLookupWithKey' f 5 "xxx" empty                         @?= (Nothing, 
 singleton 5 "xxx")
-  where
-    f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ 
old_value
-
 ----------------------------------------------------------------
 -- Delete/Update
 
@@ -813,16 +775,6 @@ test_mapKeysMonotonic = do
     valid (mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")])) @?= 
True
     valid (mapKeysMonotonic (\ _ -> 1)     (fromList [(5,"a"), (3,"b")])) @?= 
False
 
-test_fold :: Assertion
-test_fold = fold f 0 (fromList [(5,"a"), (3,"bbb")]) @?= 4
-  where
-    f a len = len + (length a)
-
-test_foldWithKey :: Assertion
-test_foldWithKey = foldWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) @?= 
"Map: (5:a)(3:b)"
-  where
-    f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
-
 ----------------------------------------------------------------
 -- Conversion
 



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to