[commit: packages/containers] ghc-head: Add test properties for splitRoot. Remove the ordering guarantee for IntSet and IntMap. (Negative numbers screw it up.) (17c5640)

git at git.haskell.org git at git.haskell.org
Thu Jan 16 07:51:10 UTC 2014


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

On branch  : ghc-head
Link       : http://git.haskell.org/packages/containers.git/commitdiff/17c5640a948a2bad01aad5cf329b2c5f71c7b8e2

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

commit 17c5640a948a2bad01aad5cf329b2c5f71c7b8e2
Author: Ryan Newton <rrnewton at gmail.com>
Date:   Tue Dec 3 19:57:16 2013 -0500

    Add test properties for splitRoot.
    Remove the ordering guarantee for IntSet and IntMap.
    (Negative numbers screw it up.)


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

17c5640a948a2bad01aad5cf329b2c5f71c7b8e2
 Data/IntMap/Base.hs        |    7 +++----
 Data/IntSet/Base.hs        |    7 +++----
 tests/intmap-properties.hs |    4 ++++
 tests/intset-properties.hs |    4 ++++
 tests/map-properties.hs    |   11 +++++++++++
 tests/set-properties.hs    |   11 +++++++++++
 6 files changed, 36 insertions(+), 8 deletions(-)

diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 5f238ac..08448dd 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -2081,10 +2081,9 @@ foldlStrict f = go
 -- | /O(1)/.  Decompose a map into pieces based on the structure of the underlying
 -- tree.  This function is useful for consuming a map in parallel.
 --     
--- No guarantee is made as to the sizes of the pieces; an internal, but
--- deterministic process determines this.  However, it is guaranteed that the pieces
--- returned will be in ascending order (all elements in the first submap less than all
--- elements in the second, and so on).
+-- No guarantee is made as to the sizes of the pieces; an internal, but deterministic
+-- process determines this.  Further, there are no guarantees about the ordering
+-- relationships of the output subsets.
 --
 -- Examples:
 --     
diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs
index 0d88363..d58583a 100644
--- a/Data/IntSet/Base.hs
+++ b/Data/IntSet/Base.hs
@@ -1488,10 +1488,9 @@ foldlStrict f = go
 -- | /O(1)/.  Decompose a set into pieces based on the structure of the underlying
 -- tree.  This function is useful for consuming a set in parallel.
 --     
--- No guarantee is made as to the sizes of the pieces; an internal, but
--- deterministic process determines this.  However, it is guaranteed that the pieces
--- returned will be in ascending order (all elements in the first subset less than all
--- elements in the second, and so on).
+-- No guarantee is made as to the sizes of the pieces; an internal, but deterministic
+-- process determines this.  Further, there are no guarantees about the ordering
+-- relationships of the output subsets.
 --
 -- Examples:
 --     
diff --git a/tests/intmap-properties.hs b/tests/intmap-properties.hs
index 6bf7ac5..f598021 100644
--- a/tests/intmap-properties.hs
+++ b/tests/intmap-properties.hs
@@ -160,6 +160,7 @@ main = defaultMain
              , testProperty "fmap"                 prop_fmap
              , testProperty "mapkeys"              prop_mapkeys
              , testProperty "split"                prop_splitModel
+             , testProperty "prop_splitRoot"       prop_splitRoot
              , testProperty "foldr"                prop_foldr
              , testProperty "foldr'"               prop_foldr'
              , testProperty "foldl"                prop_foldl
@@ -994,6 +995,9 @@ prop_splitModel n ys = length ys > 0 ==>
   in  toAscList l == sort [(k, v) | (k,v) <- xs, k < n] &&
       toAscList r == sort [(k, v) | (k,v) <- xs, k > n]
 
+prop_splitRoot :: IMap -> Bool
+prop_splitRoot s = (s == unions (splitRoot s))
+
 prop_foldr :: Int -> [(Int, Int)] -> Property
 prop_foldr n ys = length ys > 0 ==>
   let xs = List.nubBy ((==) `on` fst) ys
diff --git a/tests/intset-properties.hs b/tests/intset-properties.hs
index e424ee9..abfb96d 100644
--- a/tests/intset-properties.hs
+++ b/tests/intset-properties.hs
@@ -63,6 +63,7 @@ main = defaultMain [ testCase "lookupLT" test_lookupLT
                    , testProperty "prop_minView" prop_minView
                    , testProperty "prop_split" prop_split
                    , testProperty "prop_splitMember" prop_splitMember
+                   , testProperty "prop_splitRoot" prop_splitRoot
                    , testProperty "prop_partition" prop_partition
                    , testProperty "prop_filter" prop_filter
 #if MIN_VERSION_base(4,5,0)
@@ -308,6 +309,9 @@ prop_splitMember :: IntSet -> Int -> Bool
 prop_splitMember s i = case splitMember i s of
     (s1,t,s2) -> all (<i) (toList s1) && all (>i) (toList s2) && t == i `member` s && i `delete` s == union s1 s2
 
+prop_splitRoot :: IntSet -> Bool
+prop_splitRoot s = (s == unions (splitRoot s))
+
 prop_partition :: IntSet -> Int -> Bool
 prop_partition s i = case partition odd s of
     (s1,s2) -> all odd (toList s1) && all even (toList s2) && s == s1 `union` s2
diff --git a/tests/map-properties.hs b/tests/map-properties.hs
index 151bcf2..3361e9f 100644
--- a/tests/map-properties.hs
+++ b/tests/map-properties.hs
@@ -136,6 +136,7 @@ main = defaultMain
          , testProperty "deleteMin"            prop_deleteMin
          , testProperty "deleteMax"            prop_deleteMax
          , testProperty "split"                prop_split
+         , testProperty "splitRoot"            prop_splitRoot
 --         , testProperty "split then join"      prop_join
          , testProperty "split then merge"     prop_merge
          , testProperty "union"                prop_union
@@ -859,6 +860,16 @@ prop_split :: Int -> UMap -> Bool
 prop_split k t = let (r,l) = split k t
                  in (valid r, valid l) == (True, True)
 
+prop_splitRoot :: UMap -> Bool
+prop_splitRoot s = loop ls && (s == unions ls)
+ where
+  ls = splitRoot s 
+  loop [] = True
+  loop (s1:rst) = List.null
+                  [ (x,y) | x <- toList s1
+                          , y <- toList (unions rst)
+                          , x > y ]
+
 -- prop_join :: Int -> UMap -> Bool
 -- prop_join k t = let (l,r) = split k t
 --                 in valid (join k () l r)
diff --git a/tests/set-properties.hs b/tests/set-properties.hs
index e32a141..880f9c0 100644
--- a/tests/set-properties.hs
+++ b/tests/set-properties.hs
@@ -64,6 +64,7 @@ main = defaultMain [ testCase "lookupLT" test_lookupLT
                    , testProperty "prop_minView" prop_minView
                    , testProperty "prop_split" prop_split
                    , testProperty "prop_splitMember" prop_splitMember
+                   , testProperty "prop_splitRoot" prop_splitRoot
                    , testProperty "prop_partition" prop_partition
                    , testProperty "prop_filter" prop_filter
                    ]
@@ -359,6 +360,16 @@ prop_splitMember :: Set Int -> Int -> Bool
 prop_splitMember s i = case splitMember i s of
     (s1,t,s2) -> all (<i) (toList s1) && all (>i) (toList s2) && t == i `member` s && i `delete` s == union s1 s2
 
+prop_splitRoot :: Set Int -> Bool
+prop_splitRoot s = loop ls && (s == unions ls)
+ where
+  ls = splitRoot s 
+  loop [] = True
+  loop (s1:rst) = List.null
+                  [ (x,y) | x <- toList s1
+                          , y <- toList (unions rst)
+                          , x > y ]
+
 prop_partition :: Set Int -> Int -> Bool
 prop_partition s i = case partition odd s of
     (s1,s2) -> all odd (toList s1) && all even (toList s2) && s == s1 `union` s2



More information about the ghc-commits mailing list