Proposal: Improve the API for TChan, TMVar, and TVar

I've found the following functions helpful for working with STM. Some of them are just filling out the API so that TVars, TMVars, and IORefs match better. And all the non-TVar functions can be optimized considerably by including them in the STM library rather than defining them externally. The implementations are obvious, so I'll just include the types here; see the patch if you're interested. -- | Non-blocking version of 'readTChan'. tryReadTChan :: TChan a -> STM (Maybe a) -- | Get the next value from the 'TChan' without removing it, -- blocking if the channel is empty. peekTChan :: TChan a -> STM a -- | Non-blocking version of 'peekTChan'. tryPeekTChan :: TChan a -> STM (Maybe a) -- | Non-blocking version of 'readTMVar'. tryReadTMVar :: TMVar a -> STM (Maybe a) -- | Like 'modifyIORef' but for 'TVar'. modifyTVar :: TVar a -> (a -> a) -> STM () -- | Strict version of 'modifyTVar'. modifyTVar' :: TVar a -> (a -> a) -> STM () -- | Like 'swapTMVar' but for 'TVar'. swapTVar :: TVar a -> a -> STM a Discussion period: 2 weeks. -- Live well, ~wren

+1 Excerpts from wren ng thornton's message of Sat Mar 26 05:29:29 -0400 2011:
I've found the following functions helpful for working with STM. Some of them are just filling out the API so that TVars, TMVars, and IORefs match better. And all the non-TVar functions can be optimized considerably by including them in the STM library rather than defining them externally. The implementations are obvious, so I'll just include the types here; see the patch if you're interested.
-- | Non-blocking version of 'readTChan'. tryReadTChan :: TChan a -> STM (Maybe a)
-- | Get the next value from the 'TChan' without removing it, -- blocking if the channel is empty. peekTChan :: TChan a -> STM a
-- | Non-blocking version of 'peekTChan'. tryPeekTChan :: TChan a -> STM (Maybe a)
-- | Non-blocking version of 'readTMVar'. tryReadTMVar :: TMVar a -> STM (Maybe a)
-- | Like 'modifyIORef' but for 'TVar'. modifyTVar :: TVar a -> (a -> a) -> STM ()
-- | Strict version of 'modifyTVar'. modifyTVar' :: TVar a -> (a -> a) -> STM ()
-- | Like 'swapTMVar' but for 'TVar'. swapTVar :: TVar a -> a -> STM a
Discussion period: 2 weeks.

On 26 March 2011 10:29, wren ng thornton
tryReadTChan :: TChan a -> STM (Maybe a)
+1 if we also add: tryReadChan :: Chan a -> IO (Maybe a)
peekTChan :: TChan a -> STM a tryPeekTChan :: TChan a -> STM (Maybe a)
+1 if we also add: peekChan :: Chan a -> IO a tryPeekChan :: Chan a -> IO (Maybe a)
tryReadTMVar :: TMVar a -> STM (Maybe a)
+1 if we also add: tryReadMVar :: MVar a -> IO (Maybe a)
modifyTVar :: TVar a -> (a -> a) -> STM () modifyTVar' :: TVar a -> (a -> a) -> STM ()
These are highly useful; I use them myself quite often. There's one issue though that has always bugged me about the current API: The types of modifyIORef and modifyMVar don't "line up": modifyIORef :: IORef a -> (a -> a) -> IO () modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b It would have been nicer if modifyMVar lined up with modifyIORef: modifyMVar :: MVar a -> (a -> a) -> IO () and have a separate: modifyMVarM :: MVar a -> (a -> IO (a,b)) -> IO b I guess it's difficult to change that at this stage. but maybe we can add: purelyModifyMVar :: MVar a -> (a -> a) -> IO () -- Note I don't like this name at all... Note that I'm in favor of adding: modifyTVar :: TVar a -> (a -> a) -> STM () but do we also need to add: modifyTVarM :: TVar a -> (a -> STM (a,b)) -> STM b so that MVars and TVars have more consistent APIs?
swapTVar :: TVar a -> a -> STM a +1
Thanks for the proposal! Bas

On Sat, Mar 26, 2011 at 6:26 AM, Bas van Dijk
On 26 March 2011 10:29, wren ng thornton
wrote: tryReadTChan :: TChan a -> STM (Maybe a)
+1 if we also add: tryReadChan :: Chan a -> IO (Maybe a)
peekTChan :: TChan a -> STM a tryPeekTChan :: TChan a -> STM (Maybe a)
+1 if we also add: peekChan :: Chan a -> IO a tryPeekChan :: Chan a -> IO (Maybe a)
Here's the last time 'tryReadChan' came up, for reference: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/14596 I feel like these sorts of operations are much easier to get right in STM. +1 on adding the above to STM, though. Antoine

On 3/26/11 11:43 AM, Antoine Latter wrote:
On Sat, Mar 26, 2011 at 6:26 AM, Bas van Dijk
wrote: On 26 March 2011 10:29, wren ng thornton
wrote: tryReadTChan :: TChan a -> STM (Maybe a)
+1 if we also add: tryReadChan :: Chan a -> IO (Maybe a)
peekTChan :: TChan a -> STM a tryPeekTChan :: TChan a -> STM (Maybe a)
+1 if we also add: peekChan :: Chan a -> IO a tryPeekChan :: Chan a -> IO (Maybe a)
Here's the last time 'tryReadChan' came up, for reference: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/14596
I feel like these sorts of operations are much easier to get right in STM.
Agreed. I'm all for adding Chan versions to base if we can get the implementation/semantics right, but since I don't have experience with Chans I'm not sure if I'm the best person for that task. -- Live well, ~wren

On 26 March 2011 21:30, wren ng thornton
On 3/26/11 11:43 AM, Antoine Latter wrote:
On Sat, Mar 26, 2011 at 6:26 AM, Bas van Dijk
wrote: On 26 March 2011 10:29, wren ng thornton
wrote: tryReadTChan :: TChan a -> STM (Maybe a)
+1 if we also add: tryReadChan :: Chan a -> IO (Maybe a)
peekTChan :: TChan a -> STM a tryPeekTChan :: TChan a -> STM (Maybe a)
+1 if we also add: peekChan :: Chan a -> IO a tryPeekChan :: Chan a -> IO (Maybe a)
Here's the last time 'tryReadChan' came up, for reference: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/14596
I feel like these sorts of operations are much easier to get right in STM.
Agreed. I'm all for adding Chan versions to base if we can get the implementation/semantics right, but since I don't have experience with Chans I'm not sure if I'm the best person for that task.
The attached patch adds: tryReadMVar :: MVar a -> IO (Maybe a) tryReadChan :: Chan a -> IO (Maybe a) peekChan :: Chan a -> IO a tryPeekChan :: Chan a -> IO (Maybe a) tryReadMVar and tryReadChan were taken from the patch from Mitar. Thanks Antoine for linking that ticket. Someone should definitely take a closer look at peekChan and tryPeekChan and verify if they're correct. Wren, something else: in the documentation of your new STM operations you talk about "blocking". I think it's clearer and more consistent with the rest of STM if you talk about "retrying" instead. Regards, Bas

On 3/26/11 8:04 PM, Bas van Dijk wrote:
Wren, something else: in the documentation of your new STM operations you talk about "blocking". I think it's clearer and more consistent with the rest of STM if you talk about "retrying" instead.
I'll fix that. -- Live well, ~wren

On 3/26/11 7:26 AM, Bas van Dijk wrote:
On 26 March 2011 10:29, wren ng thornton
wrote: modifyTVar :: TVar a -> (a -> a) -> STM () modifyTVar' :: TVar a -> (a -> a) -> STM ()
These are highly useful; I use them myself quite often. There's one issue though that has always bugged me about the current API: The types of modifyIORef and modifyMVar don't "line up":
modifyIORef :: IORef a -> (a -> a) -> IO () modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
It would have been nicer if modifyMVar lined up with modifyIORef: modifyMVar :: MVar a -> (a -> a) -> IO ()
and have a separate: modifyMVarM :: MVar a -> (a -> IO (a,b)) -> IO b
I guess it's difficult to change that at this stage.
Perhaps the solution at this stage would be to: (1) add modifyMVarM :: MVar a -> (a -> IO (a,b)) -> IO b (2) deprecate modifyMVar (3) wait a cycle (4) remove modifyMVar (if needed) (5) wait a cycle (if needed) (6) add modifyMVar :: MVar a -> (a -> a) -> IO () It'll take forever, but I think it's important to get the names right for this kind of thing rather than letting the inconsistency linger. Of course, this would best be done through a separate proposal IMO. The modify* names are already in wide currency with pretty consistent semantics and types, clearly MVars are the outliers: modifyIORef :: IORef a -> (a -> a) -> IO () modifySTRef :: STRef s a -> (a -> a) -> ST s () modifyIOError :: (IOError -> IOError) -> IO a -> IO a transformers:Control.Monad.Trans.RWS.Lazy.modify transformers:Control.Monad.Trans.RWS.Strict.modify :: (Monoid w, Monad m) => (s -> s) -> RWST r w s m () transformers:Control.Monad.Trans.State.Lazy.modify transformers:Control.Monad.Trans.State.Strict.modify :: Monad m => (s -> s) -> StateT s m () mtl:Control.Monad.State.Class.modify :: MonadState s m => (s -> s) -> m () parsec-3:Text.Parsec.Prim.modifyState :: Monad m => (u -> u) -> ParsecT s u m () Perhaps when considering the new name for the current modifyMVar, we should consider the following: atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b The use of the modify* naming convention isn't universal, but the alternative naming conventions, update* and adjust*, seem mostly confined to containers: -- alias for modifyState, for backwards compatibility. parsec-3:Text.Parsec.Prim.updateState :: Monad m => (u -> u) -> ParsecT s u m () containers:Data.Sequence.adjust :: (a -> a) -> Int -> Seq a -> Seq a containers:Data.IntMap.adjust :: (a -> a) -> Key -> IntMap a -> IntMap a containers:Data.Map.adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a And there's some confusion about what the update* functions should mean: containers:Data.Sequence.update :: Int -> a -> Seq a -> Seq a containers:Data.IntMap.update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a containers:Data.Map.update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a containers:Data.Map.updateMin :: (a -> Maybe a) -> Map k a -> Map k a containers:Data.IntMap.updateMin :: (a -> a) -> IntMap a -> IntMap a containers:Data.Map.updateMax :: (a -> Maybe a) -> Map k a -> Map k a containers:Data.IntMap.updateMax :: (a -> a) -> IntMap a -> IntMap a containers:Data.IntMap.updateMaxWithKey :: (Key -> a -> a) -> IntMap a -> IntMap a containers:Data.Map.updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a But fixing containers' API is far beyond the scope of the current proposal or the proposal for deprecate-renaming modifyMVar. -- Live well, ~wren

On 26 March 2011 22:02, wren ng thornton
On 3/26/11 7:26 AM, Bas van Dijk wrote:
On 26 March 2011 10:29, wren ng thornton
wrote: modifyTVar :: TVar a -> (a -> a) -> STM () modifyTVar' :: TVar a -> (a -> a) -> STM ()
These are highly useful; I use them myself quite often. There's one issue though that has always bugged me about the current API: The types of modifyIORef and modifyMVar don't "line up":
modifyIORef :: IORef a -> (a -> a) -> IO () modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
It would have been nicer if modifyMVar lined up with modifyIORef: modifyMVar :: MVar a -> (a -> a) -> IO ()
and have a separate: modifyMVarM :: MVar a -> (a -> IO (a,b)) -> IO b
I guess it's difficult to change that at this stage.
Perhaps the solution at this stage would be to:
(1) add modifyMVarM :: MVar a -> (a -> IO (a,b)) -> IO b (2) deprecate modifyMVar (3) wait a cycle (4) remove modifyMVar (if needed) (5) wait a cycle (if needed) (6) add modifyMVar :: MVar a -> (a -> a) -> IO ()
It'll take forever, but I think it's important to get the names right for this kind of thing rather than letting the inconsistency linger. Of course, this would best be done through a separate proposal IMO.
I agree this should be done in a separate proposal. But while we're talking about it: what's the reason for the extra wait cycle in (5)? Can't we just replace (4),(5) and (6) with a single point where we undeprecate modifyMVar and change its type to the final: MVar a -> (a -> a) -> IO () ? Bas

On 3/26/11 8:11 PM, Bas van Dijk wrote:
On 26 March 2011 22:02, wren ng thornton
wrote: Perhaps the solution at this stage would be to:
(1) add modifyMVarM :: MVar a -> (a -> IO (a,b)) -> IO b (2) deprecate modifyMVar (3) wait a cycle (4) remove modifyMVar (if needed) (5) wait a cycle (if needed) (6) add modifyMVar :: MVar a -> (a -> a) -> IO ()
It'll take forever, but I think it's important to get the names right for this kind of thing rather than letting the inconsistency linger. Of course, this would best be done through a separate proposal IMO.
I agree this should be done in a separate proposal. But while we're talking about it: what's the reason for the extra wait cycle in (5)? Can't we just replace (4),(5) and (6) with a single point where we undeprecate modifyMVar and change its type to the final: MVar a -> (a -> a) -> IO () ?
Because I don't recall the finer points of the deprecation protocol. I added steps (4) and (5) just in case the protocol says they're needed. I'd much rather drop them if that's allowed :) -- Live well, ~wren

On 3/26/11 5:29 AM, wren ng thornton wrote:
I've found the following functions helpful for working with STM. Some of them are just filling out the API so that TVars, TMVars, and IORefs match better. And all the non-TVar functions can be optimized considerably by including them in the STM library rather than defining them externally. The implementations are obvious, so I'll just include the types here; see the patch if you're interested.
[...]
Discussion period: 2 weeks.
The discussion period is up, and it sounds like the patch is in. I've filed a ticket, with the following summary. http://hackage.haskell.org/trac/ghc/ticket/5104 Supported by Edward Z. Yang, Bas van Dijk(*), Antoine Latter. No dissent. Bas van Dijk's support is generally contingent on further improving the overall API by adding similar functions for the non-STM concurrency types. However, doing so requires a deprecation cycle in order to bring modifyMVar in sync with modifyTVar, modifyIORef, and the rest of the Haskell ecosystem. And therefore should be pursued in a separate proposal. He offered a patch, http://www.haskell.org/pipermail/libraries/2011-March/016096.html, which still requires verification of correctness. These changes to the base package are not included in the current proposal. -- Live well, ~wren
participants (4)
-
Antoine Latter
-
Bas van Dijk
-
Edward Z. Yang
-
wren ng thornton