Bug fixes in progress

Certain people (*cough*quicksilver*cough*) thought it'd be nice of me to inform you of what I've been up to the last few days re: reactive bug-fixing, so here's an update. - I've rewritten unamb, fixing all the issues I've managed to find (relating to nested unamb invocations, mostly) and having it throw a BothBottom exception if both values are a finite bottom. - Written an IsEvaluated library (now on hackage) that might speed up unamb a bit. The code to use it is in place, but disabled; I don't trust it to be bug-free yet. - Rewritten makeEvent (from reactive legacy-adapters) to take advantage of finalizers. It will now produce finite events instead of deadlocking. I'm now trying to fix the joinE/>>=/mappend problems, but that might take a while. Meanwhile, more eyes on the rewritten code is better, so I've attached it; there hasn't been an official release yet. -- Svein Ove Aas

Svein Ove Aas wrote:
Certain people (*cough*quicksilver*cough*) thought it'd be nice of me to inform you of what I've been up to the last few days re: reactive bug-fixing, so here's an update.
- I've rewritten unamb, fixing all the issues I've managed to find (relating to nested unamb invocations, mostly) and having it throw a BothBottom exception if both values are a finite bottom.
Why not choose one of the two existing bottoms and throw that? It'd be like the semantics of Haskell's imprecise exceptions anyway...
I'm now trying to fix the joinE/>>=/mappend problems, but that might take a while. Meanwhile, more eyes on the rewritten code is better, so I've attached it; there hasn't been an official release yet.
okay I read it! I just have some questions / suggestions to comment things better in the code, currently
unamb = ... where retry act = act `catch`
the definition of retry here makes almost no sense to me... but as I understand it, it's completely an RTS hack. First I'd put a comment saying so, and then explain exactly what problem it avoids and how it does that, with more comments. in "race": How does your current version kill descendent threads any better than "Simple version"? Oh I see it puts the `finally` kill-the-threads in, around the read-the-mvar ("descentent" just means the two threads that "race" spawns, not the threads spawned by those two threads?). But I'm not sure what the *extra* complication is for, that's beyond "Simple version"'s complexity? Is it just in order to be able to throw BothBottom at the right time (a worthy goal)? I also don't understand why putCatch wants to prevent certain kinds of exceptions from escaping the thread? (Would they emit into the calling-thread that `race` runs in? or what is the difference? How did you choose the three or four things to catch; and what is wrong with NonTermination?) thanks! -Isaac

On Fri, May 29, 2009 at 6:17 PM, Isaac Dupree
Svein Ove Aas wrote:
Certain people (*cough*quicksilver*cough*) thought it'd be nice of me to inform you of what I've been up to the last few days re: reactive bug-fixing, so here's an update.
- I've rewritten unamb, fixing all the issues I've managed to find (relating to nested unamb invocations, mostly) and having it throw a BothBottom exception if both values are a finite bottom.
Why not choose one of the two existing bottoms and throw that? It'd be like the semantics of Haskell's imprecise exceptions anyway...
Basically, so it's easier to tell when an exception originates in Unamb, for debugging Reactive. Your suggestion has merit, but I think it'd be better to wrap *both* the exceptions inside BothBottom instead.
I'm now trying to fix the joinE/>>=/mappend problems, but that might take a while. Meanwhile, more eyes on the rewritten code is better, so I've attached it; there hasn't been an official release yet.
okay I read it! I just have some questions / suggestions to comment things better in the code, currently
unamb = ... where retry act = act `catch`
the definition of retry here makes almost no sense to me... but as I understand it, it's completely an RTS hack. First I'd put a comment saying so, and then explain exactly what problem it avoids and how it does that, with more comments.
Yes indeed. I'll have a go right away: - When an unsafePerformIO action is aborted (due, presumably, to an exception either thrown by or thrownTo the thread running it), the RTS puts the entire execution context of the IO code on ice, so if the closure is later re-entered no work will have been lost, and actions aren't executed twice unless the entire thing is executed twice. The implementation is somewhat involved, but this is the Right Thing; it makes the semantics of unsafePerformIO nearly identical to ordinary pure code with regards to exceptions. - If an unsafePerformIO action uses throw/throwIO itself, once the unpause happens it'll just throw the exception again. Nice and predictable. - However, if we catch an exception in race, we clean up by killing the threads. This messes up the entire pause/unpause mechanic - it might be disabling it. I haven't examined it very deeply, as it in any case doesn't do what we want. Therefore, after killing the subordinate threads in race, the exception propagates further to the handler in unamb, which catches all possible exceptions. This exception handler proceeds to re-throw the exception; inside an unblock, as exception handlers otherwise block asynchronous exceptions until they're done. Importantly, it does this by first getting the ID of the current thread, and then throwTo'ing the thread instead of just throwIO'ing the exception. This means that, once the throwTo is re-executed after the closure is later unpaused, it'll try rethrowing the exception to *another* (now dead, hopefully) thread, and then retry the amb call. Now, the ordinary case for an exception in unamb is that some other unamb invocation is killing the thread due to already having found a non-bottom value.. ...I just figured out a potential bug here, actually. If this isn't the case - if this is a top-level unamb invocation, not something forkIO'd by race - then the exception might get caught and the /same thread/ might decide to retry the same unamb closure later, which would throw the exception to that thread again... great. Okay. It's fixable, by having unamb always execute in a separate thread entirely.. might lend itself to cleaner code, too. I'll look into it.
in "race": How does your current version kill descendent threads any better than "Simple version"? Oh I see it puts the `finally` kill-the-threads in, around the read-the-mvar ("descentent" just means the two threads that "race" spawns, not the threads spawned by those two threads?). But I'm not sure what the *extra* complication is for, that's beyond "Simple version"'s complexity? Is it just in order to be able to throw BothBottom at the right time (a worthy goal)? I also don't understand why putCatch wants to prevent certain kinds of exceptions from escaping the thread? (Would they emit into the calling-thread that `race` runs in? or what is the difference? How did you choose the three or four things to catch; and what is wrong with NonTermination?)
I didn't pick what exceptions to catch, or decide that NonTermination is bad; that's all conal's doing. reactive seems to work better with that code in. I'm not touching it. *cargo-cults* About my implementation of race - the major worry is handling asynchronous exceptions correctly, where the thread is killed between starting the descendant threads and setting up an exception handler to kill them. That's what the block/unblock construct is for. Also, my version has the descendants inform their creator of finite bottoms, meaning it can throw BothBottom when they're both dead. -- Svein Ove Aas

Okay. I've tested, and there is no bug.
This breaks my mental model of how unsafePerformIO actually works
somewhat. I'm going to have to chat with #ghc before I can write any
comments.
On Fri, May 29, 2009 at 8:24 PM, Svein Ove Aas
On Fri, May 29, 2009 at 6:17 PM, Isaac Dupree
wrote: Svein Ove Aas wrote:
Certain people (*cough*quicksilver*cough*) thought it'd be nice of me to inform you of what I've been up to the last few days re: reactive bug-fixing, so here's an update.
- I've rewritten unamb, fixing all the issues I've managed to find (relating to nested unamb invocations, mostly) and having it throw a BothBottom exception if both values are a finite bottom.
Why not choose one of the two existing bottoms and throw that? It'd be like the semantics of Haskell's imprecise exceptions anyway...
Basically, so it's easier to tell when an exception originates in Unamb, for debugging Reactive.
Your suggestion has merit, but I think it'd be better to wrap *both* the exceptions inside BothBottom instead.
I'm now trying to fix the joinE/>>=/mappend problems, but that might take a while. Meanwhile, more eyes on the rewritten code is better, so I've attached it; there hasn't been an official release yet.
okay I read it! I just have some questions / suggestions to comment things better in the code, currently
unamb = ... where retry act = act `catch`
the definition of retry here makes almost no sense to me... but as I understand it, it's completely an RTS hack. First I'd put a comment saying so, and then explain exactly what problem it avoids and how it does that, with more comments.
Yes indeed. I'll have a go right away: - When an unsafePerformIO action is aborted (due, presumably, to an exception either thrown by or thrownTo the thread running it), the RTS puts the entire execution context of the IO code on ice, so if the closure is later re-entered no work will have been lost, and actions aren't executed twice unless the entire thing is executed twice. The implementation is somewhat involved, but this is the Right Thing; it makes the semantics of unsafePerformIO nearly identical to ordinary pure code with regards to exceptions. - If an unsafePerformIO action uses throw/throwIO itself, once the unpause happens it'll just throw the exception again. Nice and predictable. - However, if we catch an exception in race, we clean up by killing the threads. This messes up the entire pause/unpause mechanic - it might be disabling it. I haven't examined it very deeply, as it in any case doesn't do what we want.
Therefore, after killing the subordinate threads in race, the exception propagates further to the handler in unamb, which catches all possible exceptions. This exception handler proceeds to re-throw the exception; inside an unblock, as exception handlers otherwise block asynchronous exceptions until they're done.
Importantly, it does this by first getting the ID of the current thread, and then throwTo'ing the thread instead of just throwIO'ing the exception. This means that, once the throwTo is re-executed after the closure is later unpaused, it'll try rethrowing the exception to *another* (now dead, hopefully) thread, and then retry the amb call.
Now, the ordinary case for an exception in unamb is that some other unamb invocation is killing the thread due to already having found a non-bottom value..
...I just figured out a potential bug here, actually. If this isn't the case - if this is a top-level unamb invocation, not something forkIO'd by race - then the exception might get caught and the /same thread/ might decide to retry the same unamb closure later, which would throw the exception to that thread again... great.
Okay. It's fixable, by having unamb always execute in a separate thread entirely.. might lend itself to cleaner code, too. I'll look into it.
in "race": How does your current version kill descendent threads any better than "Simple version"? Oh I see it puts the `finally` kill-the-threads in, around the read-the-mvar ("descentent" just means the two threads that "race" spawns, not the threads spawned by those two threads?). But I'm not sure what the *extra* complication is for, that's beyond "Simple version"'s complexity? Is it just in order to be able to throw BothBottom at the right time (a worthy goal)? I also don't understand why putCatch wants to prevent certain kinds of exceptions from escaping the thread? (Would they emit into the calling-thread that `race` runs in? or what is the difference? How did you choose the three or four things to catch; and what is wrong with NonTermination?)
I didn't pick what exceptions to catch, or decide that NonTermination is bad; that's all conal's doing. reactive seems to work better with that code in. I'm not touching it. *cargo-cults*
About my implementation of race - the major worry is handling asynchronous exceptions correctly, where the thread is killed between starting the descendant threads and setting up an exception handler to kill them. That's what the block/unblock construct is for.
Also, my version has the descendants inform their creator of finite bottoms, meaning it can throw BothBottom when they're both dead.
-- Svein Ove Aas
-- Svein Ove Aas

Svein Ove Aas wrote:
Okay. I've tested, and there is no bug.
This breaks my mental model of how unsafePerformIO actually works somewhat. I'm going to have to chat with #ghc before I can write any comments.
thanks for the written reflections! (and someday when we're sufficiently confident that they're correct, it can turn into comments in the code :-) So, how it works, as I understand it: when GHC resumes the thread, it does not re-execute the throwTo (since it was already executed last time), just like it would not re-execute a putChar. The only reason we don't use throw/throwIO is that a closure interrupted by a *synchronous* exception won't be re-tried at all by the RTS (it will memorize that it evaluates to that exception, instead -- after all, that's more efficient in normal, pure, non-unsafePerformIO cases where a thunk leads to an error-call). now, I might have misunderstood, or it might have changed (there was a discussion a few months(?) ago, about what to do in general about throw/throwTo/unsafePerformIO; -- and this is all fiddly business) -Isaac

On Fri, May 29, 2009 at 9:34 PM, Isaac Dupree
So, how it works, as I understand it: when GHC resumes the thread, it does not re-execute the throwTo (since it was already executed last time), just like it would not re-execute a putChar. The only reason we don't use throw/throwIO is that a closure interrupted by a *synchronous* exception won't be re-tried at all by the RTS (it will memorize that it evaluates to that exception, instead -- after all, that's more efficient in normal, pure, non-unsafePerformIO cases where a thunk leads to an error-call).
now, I might have misunderstood, or it might have changed (there was a discussion a few months(?) ago, about what to do in general about throw/throwTo/unsafePerformIO; -- and this is all fiddly business)
This sounds reasonable, and would explain the behaviour of my code, but I'd still like to make sure. :-) -- Svein Ove Aas

Yes indeed. I'll have a go right away: - When an unsafePerformIO action is aborted (due, presumably, to an exception either thrown by or thrownTo the thread running it), the RTS puts the entire execution context of the IO code on ice, so if the closure is later re-entered no work will have been lost, and actions aren't executed twice unless the entire thing is executed twice. The implementation is somewhat involved, but this is the Right Thing; it makes the semantics of unsafePerformIO nearly identical to ordinary pure code with regards to exceptions.
This is perhaps a silly idea, but perhaps useful -- there should be a version of unsafePerformIO that always does the "right" thing with regards to exceptions. From that, the other unamb primitives can perhaps be built more obviously? Additionally, this implementation would be potentially useful to libraries beyond unamb. Cheers, S.

Sterling Clover wrote:
This is perhaps a silly idea, but perhaps useful -- there should be a version of unsafePerformIO that always does the "right" thing with regards to exceptions. From that, the other unamb primitives can perhaps be built more obviously? Additionally, this implementation would be potentially useful to libraries beyond unamb.
You mean something like this? -- | A version of 'unsafePerformIO' that assures that the resulting -- (pure) computation can be restarted if it is killed by an -- asynchronous exception. Note that as a result, the IO action -- may be performed more than once. exceptionSafeUnsafePerformIO act = unsafePerformIO $ retry act where retry act = unblock act `catch` \SomeException e -> do myid <- myThreadId throwTo myid e retry act That could be useful indeed. Btw, in an ideal world we'd distinguish between asynchronous and synchronous exceptions here, and rethrow them appropriately. Sadly, there's currently no way to distinguish them. See http://hackage.haskell.org/trac/ghc/ticket/2558 regards, Bertram

On Sat, May 30, 2009 at 5:48 PM, Bertram Felgenhauer
Sterling Clover wrote:
This is perhaps a silly idea, but perhaps useful -- there should be a version of unsafePerformIO that always does the "right" thing with regards to exceptions. From that, the other unamb primitives can perhaps be built more obviously? Additionally, this implementation would be potentially useful to libraries beyond unamb.
You mean something like this?
-- | A version of 'unsafePerformIO' that assures that the resulting -- (pure) computation can be restarted if it is killed by an -- asynchronous exception. Note that as a result, the IO action -- may be performed more than once. exceptionSafeUnsafePerformIO act = unsafePerformIO $ retry act where retry act = unblock act `catch` \SomeException e -> do myid <- myThreadId throwTo myid e retry act
That could be useful indeed.
Let's call it restartingUnsafePerformIO, though. It's not in any way "safer" than the normal one - in a number of circumstances it's less safe. Besides that, I've turned in a patch documenting this discussion in Unamb.hs. You can see the resulting commentary in http://brage.info/~svein/unamb.patch for the time being; feel free to tell me it's mistaken in some respect. -- Svein Ove Aas

I've pushed Svein's patch, plus some small tweaks of my own, to the darcs
repo at http://code.haskell.org/unamb . Comments, please. I have a pretty
tenuous grip on this block/unblock/retry stuff.
- Conal
On Sun, May 31, 2009 at 2:04 PM, Svein Ove Aas
On Sat, May 30, 2009 at 5:48 PM, Bertram Felgenhauer
wrote: Sterling Clover wrote:
This is perhaps a silly idea, but perhaps useful -- there should be a version of unsafePerformIO that always does the "right" thing with regards to exceptions. From that, the other unamb primitives can perhaps be built more obviously? Additionally, this implementation would be potentially useful to libraries beyond unamb.
You mean something like this?
-- | A version of 'unsafePerformIO' that assures that the resulting -- (pure) computation can be restarted if it is killed by an -- asynchronous exception. Note that as a result, the IO action -- may be performed more than once. exceptionSafeUnsafePerformIO act = unsafePerformIO $ retry act where retry act = unblock act `catch` \SomeException e -> do myid <- myThreadId throwTo myid e retry act
That could be useful indeed.
Let's call it restartingUnsafePerformIO, though. It's not in any way "safer" than the normal one - in a number of circumstances it's less safe.
Besides that, I've turned in a patch documenting this discussion in Unamb.hs. You can see the resulting commentary in http://brage.info/~svein/unamb.patchhttp://brage.info/%7Esvein/unamb.patchfor the time being; feel free to tell me it's mistaken in some respect.
-- Svein Ove Aas _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Svein Ove Aas wrote:
- I've rewritten unamb, fixing all the issues I've managed to find (relating to nested unamb invocations, mostly) and having it throw a BothBottom exception if both values are a finite bottom.
Can you name those issues? The old code only handled ThreadKilled properly (because this is the most important exception to get right; I didn't really give the others much thought.) What other problems were there? I like moving the retry logic to unamb, because IO actions should never have to worry about being restarted. Only pure functions that use unsafePerformIO will have to worry. (further down the thread)
This breaks my mental model of how unsafePerformIO actually works somewhat. I'm going to have to chat with #ghc before I can write any comments.
Isaac's answer is correct. I'll elaborate. unsafePerformIO "just" creates a RealWorld# token out of thin air. From the RTS' perspective it's indistinguishable from a pure computation. The real issue is how exceptions are handled. On receiving an exception, the RTS stack is unwound to the first exception handling frame. The most important part is what happens to update frames. (Each update frame corresponds to a thunk that the current thread has entered.) For synchronous exceptions (throw/throwIO), those pending updates are performed to reflect the error: the corresponding thunks are replaced by a thunk that rethrows the exception. This has the advantage that reevaluating those thunks is fast, and that it cures a potential space leak. For asynchronous exceptions (throwTo), the RTS has to cope with the fact that the update frames may correspond to a pure computation, so it has to arrange for the computation to be resumed. So what it does is turn the update frames into thunks that, when entered, reconstruct the stack frames and continue the term's evaluation. The exception is not rethrown when the computation is resumed. Most of the gory details are in raiseAsync() in rts/RaiseException.c in the ghc sources. [...]
module Data.Unamb [...] unamb :: a -> a -> a unamb a b = unsafePerformIO $ do -- First, check whether one of the values already is evaluated -- #ifdef this for GHC a' <- return False --isEvaluated a b' <- return False --isEvaluated b case (a',b') of (True,_) -> return a (_,True) -> return b otherwise -> do retry (amb a b) where retry act = act `catch` (\(SomeException e) -> do -- The throwTo is apparently needed, to ensure the -- exception is thrown to *this* thread. -- unsafePerformIO would otherwise restart the -- throwIO call when re-invoked. -- print "abort" myid <- myThreadId unblock $ throwTo myid e >> retry act)
Would it make sense to do the isEvaluated checks again when retrying? Obscure fact: throwTo myid e works even if exceptions are blocked in the current thread. (Rationale: throwTo is a blocking operation; if it blocks, exceptions can be delivered regardless of 'block' or 'unblock') So you could write retry act = unblock act `catch` \(SomeException e) -> do myid <- myThreadId -- Kill this thread. We need to rethrow the exception -- as an /asynchronous/ exception to ensure that this -- computation can be restarted. throwTo myid e retry act
-- | Race two actions against each other in separate threads, and pick -- whichever finishes first. See also 'amb'. race :: IO a -> IO a -> IO a
-- Here is an improved version, based on suggestions from Sterling Clover -- and Bertram Felgenhauer. It takes care to kill children when killed. -- Importantly, it also sets itself up to be retried if the unamb value is -- accessed again after its computation is aborted.
-- race a b = block $ do -- v <- newEmptyMVar -- let f x = forkIO (unblock (putCatch x v)) -- ta <- f a -- tb <- f b -- let cleanup = killThread ta >> killThread tb -- (do r <- takeMVar v; cleanup; return r) `catch` -- \e -> do cleanup -- case fromException e of -- Just ThreadKilled -> -- -- kill self asynchronously and then retry if -- -- evaluated again. -- do throwIO e
This throwIO e was not in the original code, and indeed it would produce non-restartable behaviour. Please remove that line.
-- myThreadId >>= killThread -- unblock (race a b) -- _ -> throwIO e
-- Finally, an improved version written by Svein Ove Aas
-- This version kills descendant threads when killed, but does not restart -- any work if it's called by unamb. That code is left in unamb.
race a b = block $ do v <- newEmptyMVar let f x = forkIO $ putCatch x v ta <- f a tb <- f b let cleanup = killThread ta >> killThread tb loop 0 = throwIO BothBottom loop t = do x <- takeMVar v case x of Nothing -> loop (t-1) Just x' -> return x' unblock (loop (2 :: Int) `finally` cleanup)
Okay, by signaling finite bottoms with Nothing you avoid having to wait for a garbage collection to detect the case of two finite bottoms, which would deliver a BlockedOnDeadMVar exception to the 'race' thread with the old code.
-- A thread can bottom-out efficiently by throwing that exception. -- Before a thread bails out for any reason, it informs race of its bailing out.
-- Execute a given action and store the result in an MVar. Catch -- all errors, bypassing the MVar write and registering a dead thread in that -- mvar before passing them on. -- We suppress error-printing for.. what, exactly? When should we *not* do it?
Good question, are there any exceptions here that we want to see? I guess there are a few. Hiding stack overflows would be a bad thing, for example.
-- Using old code for now. putCatch :: IO a -> MVar (Maybe a) -> IO () putCatch act v = onException (act >>= putMVar v . Just) (putMVar v Nothing) `catches` [ Handler $ \ ErrorCall {} -> return () , Handler $ \ BothBottom {} -> return () , Handler $ \ PatternMatchFail {} -> return () -- This next handler hides bogus black holes, which show up as -- "<<loop>>" messages. I'd rather eliminate the problem than hide it. , Handler $ \ NonTermination -> print "Unamb.hs: Bogus black hole?" >> throwIO NonTermination ]
Regards, Bertram

On Sat, May 30, 2009 at 5:37 PM, Bertram Felgenhauer
Svein Ove Aas wrote:
- I've rewritten unamb, fixing all the issues I've managed to find (relating to nested unamb invocations, mostly) and having it throw a BothBottom exception if both values are a finite bottom.
Can you name those issues? The old code only handled ThreadKilled properly (because this is the most important exception to get right; I didn't really give the others much thought.) What other problems were there?
Ah.. no. I did a bunch of tests, and basically permuted my code into working - although, in retrospect, I can now reasonably claim it *ought* to work too, so it's not pure magic. Problem is, I forgot to write down most of those tests. I did add the most critical one, namely recursive unamb invocations. The others were potential race conditions with threads, that in retrospect I'm not sure ever existed at all. I'm going to have to take a long, hard look at how this function really works now.
I like moving the retry logic to unamb, because IO actions should never have to worry about being restarted. Only pure functions that use unsafePerformIO will have to worry.
I also get the impression that this restart logic should get factored out into a separate library. Or perhaps we could rename Unamb to WeirdRTSTricks.
Isaac's answer is correct. I'll elaborate.
That's repeating my current mental model word for word, but it's nice having it confirmed. :-)
[...]
module Data.Unamb [...] unamb :: a -> a -> a unamb a b = unsafePerformIO $ do -- First, check whether one of the values already is evaluated -- #ifdef this for GHC a' <- return False --isEvaluated a b' <- return False --isEvaluated b case (a',b') of (True,_) -> return a (_,True) -> return b otherwise -> do retry (amb a b) where retry act = act `catch` (\(SomeException e) -> do -- The throwTo is apparently needed, to ensure the -- exception is thrown to *this* thread. -- unsafePerformIO would otherwise restart the -- throwIO call when re-invoked. -- print "abort" myid <- myThreadId unblock $ throwTo myid e >> retry act)
Would it make sense to do the isEvaluated checks again when retrying?
Yes, that's a good idea, once we call it at all. Really, I suppose the entire unamb call should be inside retry.
Obscure fact: throwTo myid e works even if exceptions are blocked in the current thread. (Rationale: throwTo is a blocking operation; if it blocks, exceptions can be delivered regardless of 'block' or 'unblock') So you could write
retry act = unblock act `catch` \(SomeException e) -> do myid <- myThreadId -- Kill this thread. We need to rethrow the exception -- as an /asynchronous/ exception to ensure that this -- computation can be restarted. throwTo myid e retry act
Hm. So the old code doesn't fail to work due to that particular (nonexistent) deadlock, then.. I wonder what it was.
race a b = block $ do v <- newEmptyMVar let f x = forkIO $ putCatch x v ta <- f a tb <- f b let cleanup = killThread ta >> killThread tb loop 0 = throwIO BothBottom loop t = do x <- takeMVar v case x of Nothing -> loop (t-1) Just x' -> return x' unblock (loop (2 :: Int) `finally` cleanup)
Okay, by signaling finite bottoms with Nothing you avoid having to wait for a garbage collection to detect the case of two finite bottoms, which would deliver a BlockedOnDeadMVar exception to the 'race' thread with the old code.
Yep. I'm contemplating embedding the two bottoms inside the exception, too. -- Svein Ove Aas
participants (5)
-
Bertram Felgenhauer
-
Conal Elliott
-
Isaac Dupree
-
Sterling Clover
-
Svein Ove Aas