[commit: packages/primitive] ghc-head: Add atomicModifyMutVar (ee250c3)
git at git.haskell.org
git at git.haskell.org
Thu Sep 26 11:44:24 CEST 2013
Repository : ssh://git@git.haskell.org/primitive
On branch : ghc-head
Link : http://git.haskell.org/packages/primitive.git/commitdiff/ee250c34cd84e910e079679cc430ac8252e5d262
>---------------------------------------------------------------
commit ee250c34cd84e910e079679cc430ac8252e5d262
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Date: Tue Sep 25 14:56:02 2012 -0700
Add atomicModifyMutVar
>---------------------------------------------------------------
ee250c34cd84e910e079679cc430ac8252e5d262
Data/Primitive/MutVar.hs | 9 ++++++++-
1 file changed, 8 insertions(+), 1 deletion(-)
diff --git a/Data/Primitive/MutVar.hs b/Data/Primitive/MutVar.hs
index ebccd6a..e77406d 100644
--- a/Data/Primitive/MutVar.hs
+++ b/Data/Primitive/MutVar.hs
@@ -18,11 +18,13 @@ module Data.Primitive.MutVar (
readMutVar,
writeMutVar,
+ atomicModifyMutVar,
modifyMutVar
) where
import Control.Monad.Primitive ( PrimMonad(..), primitive_ )
-import GHC.Prim ( MutVar#, sameMutVar#, newMutVar#, readMutVar#, writeMutVar# )
+import GHC.Prim ( MutVar#, sameMutVar#, newMutVar#,
+ readMutVar#, writeMutVar#, atomicModifyMutVar# )
import Data.Typeable ( Typeable )
-- | A 'MutVar' behaves like a single-element mutable array associated
@@ -50,6 +52,11 @@ writeMutVar :: PrimMonad m => MutVar (PrimState m) a -> a -> m ()
{-# INLINE writeMutVar #-}
writeMutVar (MutVar mv#) newValue = primitive_ (writeMutVar# mv# newValue)
+-- | Atomically mutate the contents of a 'MutVar'
+atomicModifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> (a,b)) -> m b
+{-# INLINE atomicModifyMutVar #-}
+atomicModifyMutVar (MutVar mv#) f = primitive $ atomicModifyMutVar# mv# f
+
-- | Mutate the contents of a 'MutVar'
modifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> a) -> m ()
{-# INLINE modifyMutVar #-}
More information about the ghc-commits
mailing list