Hello community,

here is the log from the commit of package ghc-stm for openSUSE:Factory checked 
in at 2015-05-13 07:12:59
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-stm (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-stm.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-stm"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-stm/ghc-stm.changes  2014-11-26 
20:55:13.000000000 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-stm.new/ghc-stm.changes     2015-05-13 
07:13:01.000000000 +0200
@@ -1,0 +2,17 @@
+Fri Apr 10 14:44:06 UTC 2015 - mimi...@gmail.com
+
+- update to 2.4.4
+  * Add support for `base-4.8.0.0`
+  * Tighten Safe Haskell bounds
+  * Add `mkWeakTMVar` to `Control.Concurrent.STM.TMVar`
+  * Add `@since`-annotations
+  * Update behaviour of `newBroadcastTChanIO` to match
+    `newBroadcastTChan` in causing an error on a read from the
+    broadcast channel
+  * Add `mkWeakTVar`
+  * Add `isFullTBQueue`
+  * Fix `TChan` created via `newBroadcastTChanIO` to throw same
+    exception on a `readTChan` as when created via `newBroadcastTChan`
+  * Update to Cabal 1.10 format 
+
+-------------------------------------------------------------------

Old:
----
  stm-2.4.2.tar.gz

New:
----
  stm-2.4.4.tar.gz

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

Other differences:
------------------
++++++ ghc-stm.spec ++++++
--- /var/tmp/diff_new_pack.xj0YEd/_old  2015-05-13 07:13:01.000000000 +0200
+++ /var/tmp/diff_new_pack.xj0YEd/_new  2015-05-13 07:13:01.000000000 +0200
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-stm
 #
-# Copyright (c) 2014 SUSE LINUX Products GmbH, Nuernberg, Germany.
+# Copyright (c) 2015 SUSE LINUX GmbH, Nuernberg, Germany.
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -19,7 +19,7 @@
 %global pkg_name stm
 
 Name:           ghc-stm
-Version:        2.4.2
+Version:        2.4.4
 Release:        0
 Summary:        Software Transactional Memory
 License:        BSD-3-Clause

++++++ stm-2.4.2.tar.gz -> stm-2.4.4.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM/TBQueue.hs 
new/stm-2.4.4/Control/Concurrent/STM/TBQueue.hs
--- old/stm-2.4.2/Control/Concurrent/STM/TBQueue.hs     2012-11-16 
22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Concurrent/STM/TBQueue.hs     2014-12-17 
12:00:31.000000000 +0100
@@ -10,7 +10,7 @@
 -- Module      :  Control.Concurrent.STM.TBQueue
 -- Copyright   :  (c) The University of Glasgow 2012
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -24,20 +24,22 @@
 -- queue representation that uses two lists to obtain amortised /O(1)/
 -- enqueue and dequeue operations.
 --
+-- @since 2.4
 -----------------------------------------------------------------------------
 
 module Control.Concurrent.STM.TBQueue (
         -- * TBQueue
-       TBQueue,
-       newTBQueue,
-       newTBQueueIO,
-       readTBQueue,
-       tryReadTBQueue,
-       peekTBQueue,
-       tryPeekTBQueue,
-       writeTBQueue,
+        TBQueue,
+        newTBQueue,
+        newTBQueueIO,
+        readTBQueue,
+        tryReadTBQueue,
+        peekTBQueue,
+        tryPeekTBQueue,
+        writeTBQueue,
         unGetTBQueue,
         isEmptyTBQueue,
+        isFullTBQueue,
   ) where
 
 import Data.Typeable
@@ -46,6 +48,8 @@
 #define _UPK_(x) {-# UNPACK #-} !(x)
 
 -- | 'TBQueue' is an abstract type representing a bounded FIFO channel.
+--
+-- @since 2.4
 data TBQueue a
    = TBQueue _UPK_(TVar Int)  -- CR: read capacity
              _UPK_(TVar [a])  -- R:  elements waiting to be read
@@ -177,3 +181,17 @@
              case ys of
                [] -> return True
                _  -> return False
+
+-- |Returns 'True' if the supplied 'TBQueue' is full.
+--
+-- @since 2.4.3
+isFullTBQueue :: TBQueue a -> STM Bool
+isFullTBQueue (TBQueue rsize _read wsize _write) = do
+  w <- readTVar wsize
+  if (w > 0)
+     then return False
+     else do
+         r <- readTVar rsize
+         if (r > 0)
+            then return False
+            else return True
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM/TChan.hs 
new/stm-2.4.4/Control/Concurrent/STM/TChan.hs
--- old/stm-2.4.2/Control/Concurrent/STM/TChan.hs       2012-11-16 
22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Concurrent/STM/TChan.hs       2014-12-17 
12:00:31.000000000 +0100
@@ -10,7 +10,7 @@
 -- Module      :  Control.Concurrent.STM.TChan
 -- Copyright   :  (c) The University of Glasgow 2004
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -22,25 +22,25 @@
 
 module Control.Concurrent.STM.TChan (
 #ifdef __GLASGOW_HASKELL__
-       -- * TChans
-       TChan,
+        -- * TChans
+        TChan,
 
         -- ** Construction
         newTChan,
-       newTChanIO,
-       newBroadcastTChan,
-       newBroadcastTChanIO,
+        newTChanIO,
+        newBroadcastTChan,
+        newBroadcastTChanIO,
         dupTChan,
+        cloneTChan,
 
         -- ** Reading and writing
-       readTChan,
-       tryReadTChan,
-       peekTChan,
-       tryPeekTChan,
-       writeTChan,
+        readTChan,
+        tryReadTChan,
+        peekTChan,
+        tryPeekTChan,
+        writeTChan,
         unGetTChan,
-        isEmptyTChan,
-        cloneTChan
+        isEmptyTChan
 #endif
   ) where
 
@@ -95,6 +95,8 @@
 -- it is only written to and never read, items will pile up in memory.  By
 -- using 'newBroadcastTChan' to create the broadcast channel, items can be
 -- garbage collected after clients have seen them.
+--
+-- @since 2.4
 newBroadcastTChan :: STM (TChan a)
 newBroadcastTChan = do
     write_hole <- newTVar TNil
@@ -103,11 +105,12 @@
     return (TChan read write)
 
 -- | @IO@ version of 'newBroadcastTChan'.
+--
+-- @since 2.4
 newBroadcastTChanIO :: IO (TChan a)
 newBroadcastTChanIO = do
-    dummy_hole <- newTVarIO TNil
     write_hole <- newTVarIO TNil
-    read <- newTVarIO dummy_hole
+    read <- newTVarIO (error "reading from a TChan created by 
newBroadcastTChanIO; use dupTChan first")
     write <- newTVarIO write_hole
     return (TChan read write)
 
@@ -127,8 +130,8 @@
   case head of
     TNil -> retry
     TCons a tail -> do
-       writeTVar read tail
-       return a
+        writeTVar read tail
+        return a
 
 -- | A version of 'readTChan' which does not retry. Instead it
 -- returns @Nothing@ if no value is available.
@@ -168,7 +171,7 @@
 -- everyone else.
 dupTChan :: TChan a -> STM (TChan a)
 dupTChan (TChan _read write) = do
-  hole <- readTVar write  
+  hole <- readTVar write
   new_read <- newTVar hole
   return (TChan new_read write)
 
@@ -190,6 +193,8 @@
 
 -- |Clone a 'TChan': similar to dupTChan, but the cloned channel starts with 
the
 -- same content available as the original channel.
+--
+-- @since 2.4
 cloneTChan :: TChan a -> STM (TChan a)
 cloneTChan (TChan read write) = do
   readpos <- readTVar read
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM/TMVar.hs 
new/stm-2.4.4/Control/Concurrent/STM/TMVar.hs
--- old/stm-2.4.2/Control/Concurrent/STM/TMVar.hs       2012-11-16 
22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Concurrent/STM/TMVar.hs       2014-12-17 
12:00:31.000000000 +0100
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, DeriveDataTypeable #-}
+{-# LANGUAGE CPP, DeriveDataTypeable, MagicHash, UnboxedTuples #-}
 
 #if __GLASGOW_HASKELL__ >= 701
 {-# LANGUAGE Trustworthy #-}
@@ -9,7 +9,7 @@
 -- Module      :  Control.Concurrent.STM.TMVar
 -- Copyright   :  (c) The University of Glasgow 2004
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -21,25 +21,28 @@
 
 module Control.Concurrent.STM.TMVar (
 #ifdef __GLASGOW_HASKELL__
-       -- * TMVars
-       TMVar,
-       newTMVar,
-       newEmptyTMVar,
-       newTMVarIO,
-       newEmptyTMVarIO,
-       takeTMVar,
-       putTMVar,
-       readTMVar,      
-       tryReadTMVar,
-       swapTMVar,
-       tryTakeTMVar,
-       tryPutTMVar,
-       isEmptyTMVar
+        -- * TMVars
+        TMVar,
+        newTMVar,
+        newEmptyTMVar,
+        newTMVarIO,
+        newEmptyTMVarIO,
+        takeTMVar,
+        putTMVar,
+        readTMVar,
+        tryReadTMVar,
+        swapTMVar,
+        tryTakeTMVar,
+        tryPutTMVar,
+        isEmptyTMVar,
+        mkWeakTMVar
 #endif
   ) where
 
 #ifdef __GLASGOW_HASKELL__
+import GHC.Base
 import GHC.Conc
+import GHC.Weak
 
 import Data.Typeable (Typeable)
 
@@ -81,7 +84,7 @@
   return (TMVar t)
 
 -- |Return the contents of the 'TMVar'.  If the 'TMVar' is currently
--- empty, the transaction will 'retry'.  After a 'takeTMVar', 
+-- empty, the transaction will 'retry'.  After a 'takeTMVar',
 -- the 'TMVar' is left empty.
 takeTMVar :: TMVar a -> STM a
 takeTMVar (TMVar t) = do
@@ -150,4 +153,12 @@
   case m of
     Nothing -> return True
     Just _  -> return False
+
+-- | Make a 'Weak' pointer to a 'TMVar', using the second argument as
+-- a finalizer to run when the 'TMVar' is garbage-collected.
+--
+-- @since 2.4.4
+mkWeakTMVar :: TMVar a -> IO () -> IO (Weak (TMVar a))
+mkWeakTMVar tmv@(TMVar (TVar t#)) f = IO $ \s ->
+    case mkWeak# t# tmv f s of (# s1, w #) -> (# s1, Weak w #)
 #endif
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM/TQueue.hs 
new/stm-2.4.4/Control/Concurrent/STM/TQueue.hs
--- old/stm-2.4.2/Control/Concurrent/STM/TQueue.hs      2012-11-16 
22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Concurrent/STM/TQueue.hs      2014-12-17 
12:00:31.000000000 +0100
@@ -10,7 +10,7 @@
 -- Module      :  Control.Concurrent.STM.TQueue
 -- Copyright   :  (c) The University of Glasgow 2012
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -28,18 +28,19 @@
 -- queue representation that uses two lists to obtain amortised /O(1)/
 -- enqueue and dequeue operations.
 --
+-- @since 2.4
 -----------------------------------------------------------------------------
 
 module Control.Concurrent.STM.TQueue (
         -- * TQueue
-       TQueue,
-       newTQueue,
-       newTQueueIO,
-       readTQueue,
-       tryReadTQueue,
-       peekTQueue,
-       tryPeekTQueue,
-       writeTQueue,
+        TQueue,
+        newTQueue,
+        newTQueueIO,
+        readTQueue,
+        tryReadTQueue,
+        peekTQueue,
+        tryPeekTQueue,
+        writeTQueue,
         unGetTQueue,
         isEmptyTQueue,
   ) where
@@ -49,6 +50,8 @@
 import Data.Typeable (Typeable)
 
 -- | 'TQueue' is an abstract type representing an unbounded FIFO channel.
+--
+-- @since 2.4
 data TQueue a = TQueue {-# UNPACK #-} !(TVar [a])
                        {-# UNPACK #-} !(TVar [a])
   deriving Typeable
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM/TSem.hs 
new/stm-2.4.4/Control/Concurrent/STM/TSem.hs
--- old/stm-2.4.2/Control/Concurrent/STM/TSem.hs        2012-11-16 
22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Concurrent/STM/TSem.hs        2014-12-17 
12:00:31.000000000 +0100
@@ -10,6 +10,7 @@
 --
 -- 'TSem': transactional semaphores.
 --
+-- @since 2.4.2
 -----------------------------------------------------------------------------
 
 {-# LANGUAGE DeriveDataTypeable #-}
@@ -20,7 +21,6 @@
 import Control.Concurrent.STM
 import Control.Monad
 import Data.Typeable
-import Control.Exception
 
 -- | 'TSem' is a transactional semaphore.  It holds a certain number
 -- of units, and units may be acquired or released by 'waitTSem' and
@@ -35,6 +35,7 @@
 -- resource.  However, like other STM abstractions, 'TSem' is
 -- composable.
 --
+-- @since 2.4.2
 newtype TSem = TSem (TVar Int)
   deriving (Eq, Typeable)
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM/TVar.hs 
new/stm-2.4.4/Control/Concurrent/STM/TVar.hs
--- old/stm-2.4.2/Control/Concurrent/STM/TVar.hs        2012-11-16 
22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Concurrent/STM/TVar.hs        2014-12-17 
12:00:31.000000000 +0100
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE CPP, MagicHash, UnboxedTuples #-}
 
 #if __GLASGOW_HASKELL__ >= 701
 {-# LANGUAGE Trustworthy #-}
@@ -9,7 +9,7 @@
 -- Module      :  Control.Concurrent.STM.TVar
 -- Copyright   :  (c) The University of Glasgow 2004
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -19,32 +19,30 @@
 -----------------------------------------------------------------------------
 
 module Control.Concurrent.STM.TVar (
-       -- * TVars
-       TVar,
-       newTVar,
-       newTVarIO,
-       readTVar,
-       readTVarIO,
-       writeTVar,
-       modifyTVar,
-       modifyTVar',
-       swapTVar,
+        -- * TVars
+        TVar,
+        newTVar,
+        newTVarIO,
+        readTVar,
+        readTVarIO,
+        writeTVar,
+        modifyTVar,
+        modifyTVar',
+        swapTVar,
 #ifdef __GLASGOW_HASKELL__
-       registerDelay
+        registerDelay,
 #endif
+        mkWeakTVar
   ) where
 
 #ifdef __GLASGOW_HASKELL__
+import GHC.Base
 import GHC.Conc
+import GHC.Weak
 #else
 import Control.Sequential.STM
 #endif
 
-#if ! (MIN_VERSION_base(4,2,0))
-readTVarIO = atomically . readTVar
-#endif
-
-
 -- Like 'modifyIORef' but for 'TVar'.
 -- | Mutate the contents of a 'TVar'. /N.B./, this version is
 -- non-strict.
@@ -72,3 +70,11 @@
     return old
 {-# INLINE swapTVar #-}
 
+
+-- | Make a 'Weak' pointer to a 'TVar', using the second argument as
+-- a finalizer to run when 'TVar' is garbage-collected
+--
+-- @since 2.4.3
+mkWeakTVar :: TVar a -> IO () -> IO (Weak (TVar a))
+mkWeakTVar t@(TVar t#) f = IO $ \s ->
+    case mkWeak# t# t f s of (# s1, w #) -> (# s1, Weak w #)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Concurrent/STM.hs 
new/stm-2.4.4/Control/Concurrent/STM.hs
--- old/stm-2.4.2/Control/Concurrent/STM.hs     2012-11-16 22:50:02.000000000 
+0100
+++ new/stm-2.4.4/Control/Concurrent/STM.hs     2014-12-17 12:00:31.000000000 
+0100
@@ -1,6 +1,8 @@
 {-# LANGUAGE CPP #-}
 
-#if __GLASGOW_HASKELL__ >= 701
+#if __GLASGOW_HASKELL__ >= 709
+{-# LANGUAGE Safe #-}
+#elif __GLASGOW_HASKELL__ >= 701
 {-# LANGUAGE Trustworthy #-}
 #endif
 
@@ -9,7 +11,7 @@
 -- Module      :  Control.Concurrent.STM
 -- Copyright   :  (c) The University of Glasgow 2004
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -25,15 +27,15 @@
 -----------------------------------------------------------------------------
 
 module Control.Concurrent.STM (
-       module Control.Monad.STM,
-       module Control.Concurrent.STM.TVar,
+        module Control.Monad.STM,
+        module Control.Concurrent.STM.TVar,
 #ifdef __GLASGOW_HASKELL__
-       module Control.Concurrent.STM.TMVar,
+        module Control.Concurrent.STM.TMVar,
         module Control.Concurrent.STM.TChan,
         module Control.Concurrent.STM.TQueue,
         module Control.Concurrent.STM.TBQueue,
 #endif
-       module Control.Concurrent.STM.TArray
+        module Control.Concurrent.STM.TArray
   ) where
 
 import Control.Monad.STM
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Monad/STM.hs 
new/stm-2.4.4/Control/Monad/STM.hs
--- old/stm-2.4.2/Control/Monad/STM.hs  2012-11-16 22:50:02.000000000 +0100
+++ new/stm-2.4.4/Control/Monad/STM.hs  2014-12-17 12:00:31.000000000 +0100
@@ -10,7 +10,7 @@
 -- Module      :  Control.Monad.STM
 -- Copyright   :  (c) The University of Glasgow 2004
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  librar...@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -23,19 +23,19 @@
 --    and Practice of Parallel Programming/ 2005.
 --    <http://research.microsoft.com/Users/simonpj/papers/stm/index.htm>
 --
--- This module only defines the 'STM' monad; you probably want to 
+-- This module only defines the 'STM' monad; you probably want to
 -- import "Control.Concurrent.STM" (which exports "Control.Monad.STM").
 -----------------------------------------------------------------------------
 
 module Control.Monad.STM (
-       STM,
-       atomically,
+        STM,
+        atomically,
 #ifdef __GLASGOW_HASKELL__
         always,
         alwaysSucceeds,
-       retry,
-       orElse,
-       check,
+        retry,
+        orElse,
+        check,
 #endif
         throwSTM,
         catchSTM
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/Control/Sequential/STM.hs 
new/stm-2.4.4/Control/Sequential/STM.hs
--- old/stm-2.4.2/Control/Sequential/STM.hs     2012-11-16 22:50:02.000000000 
+0100
+++ new/stm-2.4.4/Control/Sequential/STM.hs     2014-12-17 12:00:31.000000000 
+0100
@@ -4,20 +4,24 @@
 
 {-# LANGUAGE CPP #-}
 
-#if __GLASGOW_HASKELL__ >= 701
+#if __GLASGOW_HASKELL__ >= 709
+{-# LANGUAGE Safe #-}
+#elif __GLASGOW_HASKELL__ >= 701
 {-# LANGUAGE Trustworthy #-}
 #endif
 
 -- #hide
 module Control.Sequential.STM (
-       STM, atomically, throwSTM, catchSTM,
-       TVar, newTVar, newTVarIO, readTVar, readTVarIO, writeTVar
+        STM, atomically, throwSTM, catchSTM,
+        TVar, newTVar, newTVarIO, readTVar, readTVarIO, writeTVar
     ) where
 
 #if __GLASGOW_HASKELL__ < 705
 import Prelude hiding (catch)
 #endif
+#if __GLASGOW_HASKELL__ < 709
 import Control.Applicative (Applicative(pure, (<*>)))
+#endif
 import Control.Exception
 import Data.IORef
 
@@ -37,51 +41,33 @@
 instance Monad STM where
     return = pure
     STM m >>= k = STM $ \ r -> do
-       x <- m r
-       unSTM (k x) r
+        x <- m r
+        unSTM (k x) r
 
-#ifdef BASE4
 atomically :: STM a -> IO a
 atomically (STM m) = do
     r <- newIORef (return ())
     m r `onException` do
-       rollback <- readIORef r
-       rollback
-#else
-atomically :: STM a -> IO a
-atomically (STM m) = do
-    r <- newIORef (return ())
-    m r `catch` \ ex -> do
-       rollback <- readIORef r
-       rollback
-       throw ex
-#endif
+        rollback <- readIORef r
+        rollback
 
-#ifdef BASE4
 throwSTM :: Exception e => e -> STM a
-#else
-throwSTM :: Exception -> STM a
-#endif
 throwSTM = STM . const . throwIO
 
-#ifdef BASE4
 catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
-#else
-catchSTM :: STM a -> (Exception -> STM a) -> STM a
-#endif
 catchSTM (STM m) h = STM $ \ r -> do
     old_rollback <- readIORef r
     writeIORef r (return ())
     res <- try (m r)
     rollback_m <- readIORef r
     case res of
-       Left ex -> do
-           rollback_m
-           writeIORef r old_rollback
-           unSTM (h ex) r
-       Right a -> do
-           writeIORef r (rollback_m >> old_rollback)
-           return a
+        Left ex -> do
+            rollback_m
+            writeIORef r old_rollback
+            unSTM (h ex) r
+        Right a -> do
+            writeIORef r (rollback_m >> old_rollback)
+            return a
 
 newtype TVar a = TVar (IORef a)
     deriving (Eq)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/changelog.md new/stm-2.4.4/changelog.md
--- old/stm-2.4.2/changelog.md  1970-01-01 01:00:00.000000000 +0100
+++ new/stm-2.4.4/changelog.md  2014-12-17 12:00:31.000000000 +0100
@@ -0,0 +1,48 @@
+# Changelog for [`stm` package](http://hackage.haskell.org/package/stm)
+
+## 2.4.4  *Dec 2014*
+
+  * Add support for `base-4.8.0.0`
+
+  * Tighten Safe Haskell bounds
+
+  * Add `mkWeakTMVar` to `Control.Concurrent.STM.TMVar`
+
+  * Add `@since`-annotations
+
+## 2.4.3  *Mar 2014*
+
+  * Update behaviour of `newBroadcastTChanIO` to match
+    `newBroadcastTChan` in causing an error on a read from the
+    broadcast channel
+
+  * Add `mkWeakTVar`
+
+  * Add `isFullTBQueue`
+
+  * Fix `TChan` created via `newBroadcastTChanIO` to throw same
+    exception on a `readTChan` as when created via `newBroadcastTChan`
+
+  * Update to Cabal 1.10 format
+
+## 2.4.2  *Nov 2012*
+
+  * Add `Control.Concurrent.STM.TSem` (transactional semaphore)
+
+  * Add Applicative/Alternative instances of STM for GHC <7.0
+
+  * Throw proper exception when `readTChan` called on a broadcast `TChan`
+
+## 2.4  *Jul 2012*
+
+  * Add `Control.Concurrent.STM.TQueue` (a faster `TChan`)
+
+  * Add `Control.Concurrent.STM.TBQueue` (a bounded channel based on `TQueue`)
+
+  * Add `Eq` instance for `TChan`
+
+  * Add `newBroadcastTChan` and `newBroadcastTChanIO`
+
+  * Some performance improvements for `TChan`
+
+  * Add `cloneTChan`
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/stm-2.4.2/stm.cabal new/stm-2.4.4/stm.cabal
--- old/stm-2.4.2/stm.cabal     2012-11-16 22:50:02.000000000 +0100
+++ new/stm-2.4.4/stm.cabal     2014-12-17 12:00:31.000000000 +0100
@@ -1,62 +1,53 @@
-name:          stm
-version:        2.4.2
-license:       BSD3
-license-file:  LICENSE
-maintainer:    librar...@haskell.org
-synopsis:      Software Transactional Memory
+name:           stm
+version:        2.4.4
+-- don't forget to update changelog.md file!
+license:        BSD3
+license-file:   LICENSE
+maintainer:     librar...@haskell.org
+bug-reports:    
http://ghc.haskell.org/trac/ghc/newticket?component=libraries%20%28other%29&keywords=stm
+synopsis:       Software Transactional Memory
 category:       Concurrency
-description:
- A modular composable concurrency abstraction.
- .
- Changes in version 2.4.2
- .
- * Added "Control.Concurrent.STM.TSem" (transactional semaphore)
- .
- Changes in version 2.4.1
- .
- * Added Applicative/Alternative instances of STM for GHC <7.0
- .
- Changes in version 2.4
- .
- * Added "Control.Concurrent.STM.TQueue" (a faster @TChan@)
- .
- * Added "Control.Concurrent.STM.TBQueue" (a bounded channel based on @TQueue@)
- .
- * @TChan@ has an @Eq@ instances
- .
- * Added @newBroadcastTChan@ and @newBroadcastTChanIO@
- .
- * Some performance improvements for @TChan@
- .
- * Added @cloneTChan@
-
+description:    A modular composable concurrency abstraction.
 build-type:     Simple
-cabal-version:  >=1.6
+cabal-version:  >=1.10
+tested-with:    GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, GHC==7.4.2, GHC==7.4.1, 
GHC==7.2.2, GHC==7.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1, 
GHC==6.12.3
+
+extra-source-files:
+    changelog.md
 
 source-repository head
     type:     git
-    location: http://darcs.haskell.org/packages/stm.git/
-
-flag base4
+    location: http://git.haskell.org/packages/stm.git
 
 library
-  exposed-modules:
-    Control.Concurrent.STM
-    Control.Concurrent.STM.TArray
-    Control.Concurrent.STM.TVar
-    Control.Concurrent.STM.TChan
-    Control.Concurrent.STM.TMVar
-    Control.Concurrent.STM.TQueue
-    Control.Concurrent.STM.TBQueue
-    Control.Concurrent.STM.TSem
-    Control.Monad.STM
-  other-modules:
-    Control.Sequential.STM
-  build-depends: base < 5, array
-  if flag(base4)
-    build-depends: base >=4
-    cpp-options:   -DBASE4
-  else
-    build-depends: base <4
-  if impl(ghc >= 6.10)
-    build-depends: base >=4
+    default-language: Haskell98
+    other-extensions:
+        CPP
+        DeriveDataTypeable
+        FlexibleInstances
+        MagicHash
+        MultiParamTypeClasses
+        UnboxedTuples
+    if impl(ghc >= 7.2)
+        other-extensions: Trustworthy
+    if impl(ghc >= 7.9)
+        other-extensions: Safe
+
+    build-depends:
+        base  >= 4.2 && < 4.9,
+        array >= 0.3 && < 0.6
+
+    exposed-modules:
+        Control.Concurrent.STM
+        Control.Concurrent.STM.TArray
+        Control.Concurrent.STM.TVar
+        Control.Concurrent.STM.TChan
+        Control.Concurrent.STM.TMVar
+        Control.Concurrent.STM.TQueue
+        Control.Concurrent.STM.TBQueue
+        Control.Concurrent.STM.TSem
+        Control.Monad.STM
+    other-modules:
+        Control.Sequential.STM
+
+    ghc-options: -Wall


Reply via email to