Hello community,

here is the log from the commit of package ghc-stm-containers for 
openSUSE:Factory checked in at 2016-05-17 17:16:00
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-stm-containers (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-stm-containers.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-stm-containers"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-stm-containers/ghc-stm-containers.changes    
2016-02-17 12:12:00.000000000 +0100
+++ 
/work/SRC/openSUSE:Factory/.ghc-stm-containers.new/ghc-stm-containers.changes   
    2016-05-17 17:16:01.000000000 +0200
@@ -1,0 +2,5 @@
+Sat May 14 20:26:17 UTC 2016 - mimi...@gmail.com
+
+- update to 0.2.11 
+
+-------------------------------------------------------------------

Old:
----
  stm-containers-0.2.10.tar.gz

New:
----
  stm-containers-0.2.11.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-stm-containers.spec ++++++
--- /var/tmp/diff_new_pack.zw9q7N/_old  2016-05-17 17:16:02.000000000 +0200
+++ /var/tmp/diff_new_pack.zw9q7N/_new  2016-05-17 17:16:02.000000000 +0200
@@ -20,7 +20,7 @@
 %bcond_with tests
 
 Name:           ghc-stm-containers
-Version:        0.2.10
+Version:        0.2.11
 Release:        0
 Summary:        Containers for STM
 Group:          System/Libraries
@@ -37,8 +37,6 @@
 BuildRequires:  ghc-focus-devel
 BuildRequires:  ghc-hashable-devel
 BuildRequires:  ghc-list-t-devel
-BuildRequires:  ghc-loch-th-devel
-BuildRequires:  ghc-placeholders-devel
 BuildRequires:  ghc-primitive-devel
 BuildRequires:  ghc-transformers-devel
 %if %{with tests}

++++++ stm-containers-0.2.10.tar.gz -> stm-containers-0.2.11.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/stm-containers-0.2.10/executables/APITests/MapTests.hs 
new/stm-containers-0.2.11/executables/APITests/MapTests.hs
--- old/stm-containers-0.2.10/executables/APITests/MapTests.hs  2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/executables/APITests/MapTests.hs  2016-05-14 
09:21:20.000000000 +0200
@@ -72,6 +72,20 @@
 -- * Tests
 -------------------------
 
+prop_sizeAndList =
+  forAll gen prop
+  where
+    gen = do
+      keys <- nub <$> listOf (arbitrary :: Gen Char)
+      mapM (liftA2 (flip (,)) (arbitrary :: Gen Int) . pure) keys
+    prop list =
+      length list == stmMapLength
+      where
+        stmMapLength =
+          unsafePerformIO $ atomically $ do
+            x <- stmMapFromList list
+            STMMap.size x
+
 prop_fromListToListIsomorphism =
   forAll gen prop
   where
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/stm-containers-0.2.10/executables/ConcurrentInsertionBench.hs 
new/stm-containers-0.2.11/executables/ConcurrentInsertionBench.hs
--- old/stm-containers-0.2.10/executables/ConcurrentInsertionBench.hs   
2016-02-12 13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/executables/ConcurrentInsertionBench.hs   
2016-05-14 09:21:20.000000000 +0200
@@ -119,12 +119,12 @@
           [
             bgroup "STM Containers"
               [
-                bench "Focus-based" $ 
+                bench "Focus-based" $ nfIO $
                   scSessionRunner focusSCInterpreter threadTransactions,
-                bench "Specialized" $ 
+                bench "Specialized" $ nfIO $
                   scSessionRunner specializedSCInterpreter threadTransactions
               ],
-            bench "Unordered Containers" $
+            bench "Unordered Containers" $ nfIO $
               ucSessionRunner threadTransactions
           ]
   where
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/stm-containers-0.2.10/executables/ConcurrentTransactionsBench.hs 
new/stm-containers-0.2.11/executables/ConcurrentTransactionsBench.hs
--- old/stm-containers-0.2.10/executables/ConcurrentTransactionsBench.hs        
2016-02-12 13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/executables/ConcurrentTransactionsBench.hs        
2016-05-14 09:21:20.000000000 +0200
@@ -202,7 +202,7 @@
         map concat $! 
         slices (length transactionsGroups `div` threadsNum) transactionsGroups
       in
-        bench (shows threadsNum . showString "/" . shows (transactionsNum 
`div` threadsNum) $ "") $
+        bench (shows threadsNum . showString "/" . shows (transactionsNum 
`div` threadsNum) $ "") $ nfIO $
           scSessionRunner specializedSCInterpreter session
   where
     threadsNums = [1, 2, 4, 6, 8, 12, 16, 32, 40, 52, 64, 80, 128]
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-containers-0.2.10/executables/InsertionBench.hs 
new/stm-containers-0.2.11/executables/InsertionBench.hs
--- old/stm-containers-0.2.10/executables/InsertionBench.hs     2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/executables/InsertionBench.hs     2016-05-14 
09:21:20.000000000 +0200
@@ -16,12 +16,12 @@
     [
       bgroup "STM Containers"
       [
-        bench "focus-based" $ 
+        bench "focus-based" $ nfIO $
           do
             t <- atomically $ STMContainers.new :: IO (STMContainers.Map 
Text.Text ())
             forM_ keys $ \k -> atomically $ STMContainers.focus (Focus.insertM 
()) k t
         ,
-        bench "specialized" $
+        bench "specialized" $ nfIO $
           do
             t <- atomically $ STMContainers.new :: IO (STMContainers.Map 
Text.Text ())
             forM_ keys $ \k -> atomically $ STMContainers.insert () k t
@@ -33,7 +33,7 @@
       bench "Containers" $
         nf (foldr (\k -> Containers.insert k ()) Containers.empty) keys
       ,
-      bench "Hashtables" $ 
+      bench "Hashtables" $ nfIO $
         do
           t <- Hashtables.new :: IO (Hashtables.BasicHashTable Text.Text ())
           forM_ keys $ \k -> Hashtables.insert t k ()
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-containers-0.2.10/library/STMContainers/Bimap.hs 
new/stm-containers-0.2.11/library/STMContainers/Bimap.hs
--- old/stm-containers-0.2.10/library/STMContainers/Bimap.hs    2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/library/STMContainers/Bimap.hs    2016-05-14 
09:21:20.000000000 +0200
@@ -14,6 +14,7 @@
   focus1,
   focus2,
   null,
+  size,
   stream,
 )
 where
@@ -63,6 +64,12 @@
 null = Map.null . m1
 
 -- |
+-- Get the number of elements.
+{-# INLINE size #-}
+size :: Bimap a b -> STM Int
+size = Map.size . m1
+
+-- |
 -- Look up a right value by a left value.
 {-# INLINABLE lookup1 #-}
 lookup1 :: (Association a b) => a -> Bimap a b -> STM (Maybe b)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/stm-containers-0.2.10/library/STMContainers/HAMT/Nodes.hs 
new/stm-containers-0.2.11/library/STMContainers/HAMT/Nodes.hs
--- old/stm-containers-0.2.10/library/STMContainers/HAMT/Nodes.hs       
2016-02-12 13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/library/STMContainers/HAMT/Nodes.hs       
2016-05-14 09:21:20.000000000 +0200
@@ -159,3 +159,17 @@
     Nodes n -> stream (Level.succ l) n
     Leaf _ e -> return e
     Leaves _ a -> ListT.fromFoldable a
+
+size :: Nodes e -> STM Int
+size nodes =
+  readTVar nodes >>= foldlM step 0
+  where
+    step a =
+      fmap (a+) . nodeSize
+      where
+        nodeSize :: Node e -> STM Int
+        nodeSize =
+          \case
+            Nodes nodes -> size nodes
+            Leaf _ _ -> pure 1
+            Leaves _ x -> pure (SizedArray.size x)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-containers-0.2.10/library/STMContainers/Map.hs 
new/stm-containers-0.2.11/library/STMContainers/Map.hs
--- old/stm-containers-0.2.10/library/STMContainers/Map.hs      2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/library/STMContainers/Map.hs      2016-05-14 
09:21:20.000000000 +0200
@@ -9,6 +9,7 @@
   lookup,
   focus,
   null,
+  size,
   stream,
 )
 where
@@ -89,6 +90,12 @@
 null (Map h) = HAMT.null h
 
 -- |
+-- Get the number of elements.
+{-# INLINE size #-}
+size :: Map k v -> STM Int
+size (Map h) = HAMTNodes.size h
+
+-- |
 -- Stream associations.
 -- 
 -- Amongst other features this function provides an interface to folding 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/stm-containers-0.2.10/library/STMContainers/Multimap.hs 
new/stm-containers-0.2.11/library/STMContainers/Multimap.hs
--- old/stm-containers-0.2.10/library/STMContainers/Multimap.hs 2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/library/STMContainers/Multimap.hs 2016-05-14 
09:21:20.000000000 +0200
@@ -10,6 +10,7 @@
   delete,
   deleteByKey,
   lookup,
+  lookupByKey,
   focus,
   null,
   stream,
@@ -26,7 +27,7 @@
 
 -- |
 -- A multimap, based on an STM-specialized hash array mapped trie.
--- 
+--
 -- Basically it's just a wrapper API around @'Map.Map' k ('Set.Set' v)@.
 newtype Multimap k v = Multimap (Map.Map k (Set.Set v))
   deriving (Typeable)
@@ -47,19 +48,25 @@
 -- Look up an item by a value and a key.
 {-# INLINE lookup #-}
 lookup :: (Association k v) => v -> k -> Multimap k v -> STM Bool
-lookup v k (Multimap m) = 
+lookup v k (Multimap m) =
   maybe (return False) (Set.lookup v) =<< Map.lookup k m
 
 -- |
+-- Look up all values by key.
+{-# INLINE lookupByKey #-}
+lookupByKey :: Key k => k -> Multimap k v -> STM (Maybe (Set.Set v))
+lookupByKey k (Multimap m) = Map.lookup k m
+
+-- |
 -- Insert an item.
 {-# INLINABLE insert #-}
 insert :: (Association k v) => v -> k -> Multimap k v -> STM ()
 insert v k (Multimap m) =
   Map.focus ms k m
   where
-    ms = 
-      \case 
-        Just s -> 
+    ms =
+      \case
+        Just s ->
           do
             Set.insert v s
             return ((), Focus.Keep)
@@ -76,9 +83,9 @@
 delete v k (Multimap m) =
   Map.focus ms k m
   where
-    ms = 
-      \case 
-        Just s -> 
+    ms =
+      \case
+        Just s ->
           do
             Set.delete v s
             Set.null s >>= returnDecision . bool Focus.Keep Focus.Remove
@@ -91,23 +98,23 @@
 -- Delete all values associated with a key.
 {-# INLINEABLE deleteByKey #-}
 deleteByKey :: Key k => k -> Multimap k v -> STM ()
-deleteByKey k (Multimap m) = 
+deleteByKey k (Multimap m) =
   Map.delete k m
 
 -- |
 -- Focus on an item with a strategy by a value and a key.
--- 
+--
 -- This function allows to perform simultaneous lookup and modification.
--- 
+--
 -- The strategy is over a unit since we already know,
 -- which value we're focusing on and it doesn't make sense to replace it,
 -- however we still can decide wether to keep or remove it.
 {-# INLINE focus #-}
 focus :: (Association k v) => Focus.StrategyM STM () r -> v -> k -> Multimap k 
v -> STM r
-focus = 
+focus =
   \s v k (Multimap m) -> Map.focus (liftSetItemStrategy v s) k m
   where
-    liftSetItemStrategy :: 
+    liftSetItemStrategy ::
       (Set.Element e) => e -> Focus.StrategyM STM () r -> Focus.StrategyM STM 
(Set.Set e) r
     liftSetItemStrategy e s =
       \case
@@ -123,7 +130,7 @@
                     return (Focus.Replace s)
                 _ ->
                   return Focus.Keep
-        Just set -> 
+        Just set ->
           do
             r <- Set.focus s e set
             (r,) . bool Focus.Keep Focus.Remove <$> Set.null set
@@ -136,8 +143,8 @@
 
 -- |
 -- Construct a new multimap in IO.
--- 
--- This is useful for creating it on a top-level using 'unsafePerformIO', 
+--
+-- This is useful for creating it on a top-level using 'unsafePerformIO',
 -- because using 'atomically' inside 'unsafePerformIO' isn't possible.
 {-# INLINE newIO #-}
 newIO :: IO (Multimap k v)
@@ -151,11 +158,11 @@
 
 -- |
 -- Stream associations.
--- 
--- Amongst other features this function provides an interface to folding 
+--
+-- Amongst other features this function provides an interface to folding
 -- via the 'ListT.fold' function.
 stream :: Multimap k v -> ListT STM (k, v)
-stream (Multimap m) = 
+stream (Multimap m) =
   Map.stream m >>= \(k, s) -> (k,) <$> Set.stream s
 
 -- |
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/stm-containers-0.2.10/library/STMContainers/Prelude.hs 
new/stm-containers-0.2.11/library/STMContainers/Prelude.hs
--- old/stm-containers-0.2.10/library/STMContainers/Prelude.hs  2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/library/STMContainers/Prelude.hs  2016-05-14 
09:21:20.000000000 +0200
@@ -1,8 +1,6 @@
 module STMContainers.Prelude
 ( 
   module Exports,
-  bug,
-  bottom,
   traversePair,
 )
 where
@@ -11,10 +9,6 @@
 -------------------------
 import BasePrelude as Exports
 
--- placeholders
--------------------------
-import Development.Placeholders as Exports
-
 -- hashable
 -------------------------
 import Data.Hashable as Exports (Hashable(..))
@@ -27,16 +21,6 @@
 -------------------------
 import ListT as Exports (ListT)
 
--- custom
--------------------------
-import qualified Debug.Trace.LocationTH
-
-bug = [e| $(Debug.Trace.LocationTH.failure) . (msg <>) |]
-  where
-    msg = "A \"stm-containers\" package bug: " :: String
-
-bottom = [e| $bug "Bottom evaluated" |]
-
 -- | A replacement for the missing 'Traverse' instance of pair in base < 4.7.
 traversePair :: Functor f => (a -> f b) -> (c, a) -> f (c, b)
 traversePair f (x, y) = (,) x <$> f y
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-containers-0.2.10/library/STMContainers/Set.hs 
new/stm-containers-0.2.11/library/STMContainers/Set.hs
--- old/stm-containers-0.2.10/library/STMContainers/Set.hs      2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/library/STMContainers/Set.hs      2016-05-14 
09:21:20.000000000 +0200
@@ -9,6 +9,7 @@
   lookup,
   focus,
   null,
+  size,
   stream,
 )
 where
@@ -93,6 +94,12 @@
 null = HAMT.null . hamt
 
 -- |
+-- Get the number of elements.
+{-# INLINE size #-}
+size :: Set e -> STM Int
+size (Set h) = HAMTNodes.size h
+
+-- |
 -- Stream elements.
 -- 
 -- Amongst other features this function provides an interface to folding 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-containers-0.2.10/stm-containers.cabal 
new/stm-containers-0.2.11/stm-containers.cabal
--- old/stm-containers-0.2.10/stm-containers.cabal      2016-02-12 
13:36:47.000000000 +0100
+++ new/stm-containers-0.2.11/stm-containers.cabal      2016-05-14 
09:21:20.000000000 +0200
@@ -1,7 +1,7 @@
 name:
   stm-containers
 version:
-  0.2.10
+  0.2.11
 synopsis:
   Containers for STM
 description:
@@ -66,9 +66,6 @@
     list-t >= 0.2 && < 0.5,
     focus >= 0.1.2 && < 0.2,
     transformers >= 0.2 && < 0.6,
-    -- debugging:
-    loch-th == 0.2.*,
-    placeholders == 0.1.*,
     -- general:
     primitive >= 0.5 && < 0.7,
     base-prelude < 2


Reply via email to