[Haskell-cafe] Misleading MVar documentation

Edward Z. Yang ezyang at MIT.EDU
Sat Dec 25 02:47:32 CET 2010


Here is one suggested doc patch.  Comments and revisions welcome:

ezyang at javelin:~/Dev/ghc-clean/libraries/base/Control/Concurrent$ darcs whatsnew -u
hunk ./Control/Concurrent/MVar.hs 59
 
 {-|
   This is a combination of 'takeMVar' and 'putMVar'; ie. it takes the value
-  from the 'MVar', puts it back, and also returns it.
+  from the 'MVar', puts it back, and also returns it.  This function
+  is race safe only if there are no other producers (i.e. threads calling
+  'putMVar') for this 'MVar'.
 -}
 readMVar :: MVar a -> IO a
 readMVar m =
hunk ./Control/Concurrent/MVar.hs 72
 
 {-|
   Take a value from an 'MVar', put a new value into the 'MVar' and
-  return the value taken. Note that there is a race condition whereby
-  another process can put something in the 'MVar' after the take
-  happens but before the put does.
+  return the value taken. This function is race safe only if there are
+  no other prodcuers for this 'MVar'.
 -}
 swapMVar :: MVar a -> a -> IO a
 swapMVar mvar new =
hunk ./Control/Concurrent/MVar.hs 83
     return old
 
 {-|
-  'withMVar' is a safe wrapper for operating on the contents of an
-  'MVar'.  This operation is exception-safe: it will replace the
+  'withMVar' is an exception-safe wrapper for operating on the contents
+  of an 'MVar'.  This operation is exception-safe: it will replace the
   original contents of the 'MVar' if an exception is raised (see
hunk ./Control/Concurrent/MVar.hs 86
-  "Control.Exception").
+  "Control.Exception").  However, it is only race safe if there are no
+  other producers for this 'MVar'.
 -}
 {-# INLINE withMVar #-}
 -- inlining has been reported to have dramatic effects; see
hunk ./Control/Concurrent/MVar.hs 101
     return b
 
 {-|
-  A safe wrapper for modifying the contents of an 'MVar'.  Like 'withMVar', $
-  'modifyMVar' will replace the original contents of the 'MVar' if an
-  exception is raised during the operation.
+  An exception-safe wrapper for modifying the contents of an 'MVar'.
+  Like 'withMVar', 'modifyMVar' will replace the original contents of
+  the 'MVar' if an exception is raised during the operation.  This
+  function is only race safe if there are no other producers for this
+  'MVar'.
 -}
 {-# INLINE modifyMVar_ #-}
 modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()

Cheers,
Edward



More information about the Haskell-Cafe mailing list