capability
                                
                                 capability copied to clipboard
                                
                                    capability copied to clipboard
                            
                            
                            
                        `listen` and `pass` breaks on error or with concurrency
The current definitions of listen and pass are:
instance (Monoid w, HasState tag w m)
  => HasWriter tag w (WriterLog m)
  where
    writer_ tag (a, w) = yield_ tag w >> pure a
    {-# INLINE writer_ #-}
    listen_ :: forall a. Proxy# tag -> WriterLog m a -> WriterLog m (a, w)
    listen_ _ m = coerce @(m (a, w)) $ do
      w0 <- get @tag
      put @tag mempty
      a <- coerce m
      w <- get @tag
      put @tag $! w0 <> w
      pure (a, w)
    {-# INLINE listen_ #-}
    pass_ :: forall a. Proxy# tag -> WriterLog m (a, w -> w) -> WriterLog m a
    pass_ _ m = coerce @(m a) $ do
      w0 <- get @tag
      put @tag mempty
      (a, f) <- coerce @_ @(m (a, w -> w)) m
      w <- get @tag
      put @tag $! w0 <> f w
      pure a
    {-# INLINE pass_ #-}
There is no error recovery at all, and by temporarily "repurposing" the mutable state, other threads end up not writing to where they should be writing.
The concurrency problem may not be worth fixing (in some sense), but at least it deserves a warning in the docs; having no error recovery is arguably a larger problem.
I gather that the problem that you are highlighting is solely on the IO implementation? Or does the same happen with, say StateT Maybe?
What behaviour would you expect in case or errors?
Sorry - I was mainly thinking about the situation for ReaderT IO (and my mind didn't work very well yesterday), where I would expect a bracket over the m. This can be provided as a separate strategy on monads with MonadMask.
I'm not entirely sure with the semantics in the case of using a transformer stack, but I can imagine something like this going wrong:
data M a = M { runM :: ExceptT () (State String) a }
  deriving (Functor, Applicative, Monad, Mtl.MonadState String, Mtl.MonadError ())
  deriving (HasSink "log" String, WriterLog "log" String)
    via SinkLog (MonadState M)
  deriving (HasThrow "err" ())
    via MonadError m
f :: (Either () String, String)
f = runState (runExceptT $ runM $ tell "a" *> listen (tell "b" *> throw () *> tell "c")) ""
-- Expected: (Left (), "ab")
-- Actual: (Left (), "b")
disclaimer - I don't have my machine near me, and i haven't tested this. Feel free to ignore before I get home and do some experiment.
The concurrency problem may not be worth fixing (in some sense), but at least it deserves a warning in the docs
HasState, same as MTL's MonadState, is not concurrency safe. In particular modify' is implemented as
 do s <- get
    put $! f s
which is not atomic.
having no error recovery is arguably a larger problem.
This issue about HasMask seems relevant to this question. I imagine that an exception safe version of this would require a bracket of some sort.
We could, presumably, implement modify' using state, though. And implement state with modifyRef, though this is not atomic on IORef by default (which uses modifyIORef, rather than atomicModifyIORef.
That being said, I suppose that get >>= put is safe with MVars, so maybe we simply don't have to care about the concurrency part.
That being said, I suppose that
get >>= putis safe withMVars, so maybe we simply don't have to care about the concurrency part.
Hmm, I might be misreading, but I don't see how. The following kind of interleaving is the issue I'm referring to, where modify' is not atomic.
do s1 <- get     |
                 |  do s2 <- get
   put $! f1 s1  |
                 |     put $! f2 s2
We could, presumably, implement
modify'usingstate, though.
Can we? modify' still needs to be strict in the MTL MonadState case, where state is just the underlying MTL state. And, I presume, in general modify (without ') should still be non-strict.
(Guessing) For MVars, it is possible that we implement modify with takeMVar and putMVar in combination which will be atomic, since any other thread trying to read will be blocked. Apparently that is different from get >>= (put . f) though.
Hmm, I might be misreading, but I don't see how. The following kind of interleaving is the issue I'm referring to, where
modify'is not atomic.
On MVar that interleaving will just have s2 block on get (well, unless get is implemented as readMVar rather than takeMVar… which it probably is. Grumble.)
Can we? modify' still needs to be strict in the MTL MonadState case, where state is just the underlying MTL state. And, I presume, in general modify (without ') should still be non-strict.
It probably depends how state is implemented. If the pair is used lazily (fst, snd), then we can't quite make it strict for State. An alternative is to add a strict state' primitive to the class.
But maybe we should focus on the behaviour with exception first.
On
MVarthat interleaving will just haves2block onget(well, unlessgetis implemented asreadMVarrather thantakeMVar… which it probably is. Grumble.)
get indeed uses readMVar, and it has to, because sequencing get, e.g. get >> get, is allowed by the state API and is not expected to block indefinitely.
My impression is that MonadState and thereby HasState, which is based on the former, is just not designed for a concurrent use-case.
I believe we discussed a potential HasAtomicState that could be designed for that use-case at some point in the past.
But maybe we should focus on the behaviour with exception first.
Agreed. Coming back to HasMask, we could make such a capability a prerequisite of the WriterLog instance. If needed we could provide the simpler UnmaskedWriterLog without such a constraint.
a potential HasAtomicState
What about introducing get_ and put_ as methods of HasState too, allowing different semantics of get >>= put and state? Three operations can all be atomic, and modify can be defined in terms of state (thus also atomic).
a potential HasAtomicState
What about introducing
get_andput_as methods ofHasStatetoo, allowing different semantics ofget >>= putandstate? Three operations can all be atomic, andmodifycan be defined in terms ofstate(thus also atomic).
They are methods of HasState's super-classes HasSource and HasSink already.
An advantage of a dedicated class would be that atomicity could be specified on the class, such that all instances must fulfill it. Meaning, all code using HasAtomicState would be correct in a concurrent use-case. The trouble with making this a property of particular instances is that, in that case, code that is written with the constraint HasState => ... might not be correct for some instances of HasState.