On 01/05/10 16:17, Bas van Dijk wrote:
I created a ticket about the "asynchronous exception wormholes" so
that we won't forget about them:
http://hackage.haskell.org/trac/ghc/ticket/4035
Thanks - don't worry, I haven't forgotten, just been busy with other things.
Cheers,
Simon
__
I created a ticket about the "asynchronous exception wormholes" so
that we won't forget about them:
http://hackage.haskell.org/trac/ghc/ticket/4035
regards,
Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listi
On Thu, Apr 22, 2010 at 10:30 AM, Simon Marlow wrote:
> Funnily enough, before posting the above message I followed exactly the line
> of reasoning you detail below to discover that there isn't a way to fix this
> using parametricity. It's useful to have it documented, though - thanks.
In their
On 21/04/2010 19:38, Bas van Dijk wrote:
On Tue, Apr 20, 2010 at 12:56 PM, Simon Marlow wrote:
On 09/04/2010 12:14, Bertram Felgenhauer wrote:
It could be baked into a variant of the forkIO primitive, say
forkIOwithUnblock :: ((IO a ->IO a) ->IO b) ->IO ThreadId
I agree wit
On Tue, Apr 20, 2010 at 12:56 PM, Simon Marlow wrote:
> On 09/04/2010 12:14, Bertram Felgenhauer wrote:
>>
>> Simon Marlow wrote:
>>>
>>> On 09/04/2010 09:40, Bertram Felgenhauer wrote:
timeout t io = mask $ \restore -> do
result<- newEmptyMVar
tid<- for
On 04/20/10 06:56, Simon Marlow wrote:
On 09/04/2010 12:14, Bertram Felgenhauer wrote:
Simon Marlow wrote:
On 09/04/2010 09:40, Bertram Felgenhauer wrote:
timeout t io = mask $ \restore -> do
result<- newEmptyMVar
tid<- forkIO $ restore (io>>= putMVar result)
threadDelay t `onException` killTh
On 09/04/2010 12:14, Bertram Felgenhauer wrote:
Simon Marlow wrote:
On 09/04/2010 09:40, Bertram Felgenhauer wrote:
timeout t io = mask $ \restore -> do
result<- newEmptyMVar
tid<- forkIO $ restore (io>>= putMVar result)
threadDelay t `onException` killThrea
On Mon, Apr 19, 2010 at 5:54 PM, Simon Marlow wrote:
> So I think I like this variant, even though it adds a little API overhead.
> Anyone else have any thoughts on this?
I do think the RankNTypes version:
mask :: ((forall b. IO b -> IO b) -> IO a) -> IO a
is easier to use and explain because it
On 10/04/2010 19:42, Iavor Diatchki wrote:
Hello,
It seems that rank-2 types are sufficient to make the more polymorphic types:
{-# LANGUAGE Rank2Types #-}
import Control.Exception
data Mask = Mask (forall a. IO a -> IO a)
mask :: (Mask ->
On 10/04/2010 20:07, Iavor Diatchki wrote:
Hello,
I wonder if it might be possible to use just one primitive which
atomically changes the interrupt mask for a thread? Here is an example
of what I'm thinking:
data MaskingState = Unmasked
| MaskedInterruptible
Hello,
I wonder if it might be possible to use just one primitive which atomically
changes the interrupt mask for a thread? Here is an example of what I'm
thinking:
data MaskingState = Unmasked
| MaskedInterruptible
| MaskedNonInterruptible
-- Atomically c
Hello,
It seems that rank-2 types are sufficient to make the more polymorphic types:
{-# LANGUAGE Rank2Types #-}
import Control.Exception
data Mask = Mask (forall a. IO a -> IO a)
mask :: (Mask -> IO a) -> IO a
mask io = do
b <- blocked
if b
On 09/04/2010 10:33, Bas van Dijk wrote:
On Fri, Apr 9, 2010 at 3:22 AM, Isaac Dupree
wrote:
OK, thanks for the link! In fact, [tell me if my reasoning is wrong...], in
that fork-definition, the 'putMVar' will never block, because there is only
putMVar one for each created MVar.
Yes that's
On 08/04/2010 06:27, Dean Herington wrote:
Is there any reason not to use the more standard "uninterruptible"
instead of "noninterruptible"?
Good point, I'll change that.
Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
ht
Simon Marlow wrote:
> On 09/04/2010 09:40, Bertram Felgenhauer wrote:
> >Simon Marlow wrote:
> >>mask :: ((IO a -> IO a) -> IO b) -> IO b
> >
> >How does forkIO fit into the picture? That's one point where reasonable
> >code may want to unblock all exceptions unconditionally - for example to
> >
On Wed, Apr 7, 2010 at 5:12 PM, Simon Marlow wrote:
> Comments? I have a working implementation, just cleaning it up to make a
> patch.
Can you also take a look at these bugs I reported earlier:
http://hackage.haskell.org/trac/ghc/ticket/3944
http://hackage.haskell.org/trac/ghc/ticket/3945
The
On Fri, Apr 9, 2010 at 10:40 AM, Bertram Felgenhauer
wrote:
> How does forkIO fit into the picture? That's one point where reasonable
> code may want to unblock all exceptions unconditionally - for example to
> allow the thread to be killed later.
>
> timeout t io = block $ do
> result <
On 08/04/2010 21:20, Tyson Whitehead wrote:
On March 26, 2010 15:51:42 Isaac Dupree wrote:
On 03/25/10 12:36, Simon Marlow wrote:
I'd also be amenable to having block/unblock count nesting levels
instead, I don't think it would be too hard to implement and it wouldn't
require any changes at the
On 09/04/2010 09:40, Bertram Felgenhauer wrote:
Simon Marlow wrote:
but they are needlessly complicated, in my opinion. This offers the
same functionality:
mask :: ((IO a -> IO a) -> IO b) -> IO b
mask io = do
b<- blocked
if b
then io id
else block $ io unblock
How does
On Fri, Apr 9, 2010 at 3:22 AM, Isaac Dupree
wrote:
> OK, thanks for the link! In fact, [tell me if my reasoning is wrong...], in
> that fork-definition, the 'putMVar' will never block, because there is only
> putMVar one for each created MVar.
Yes that's correct.
> I seem to remember that any
Simon Marlow wrote:
> but they are needlessly complicated, in my opinion. This offers the
> same functionality:
>
> mask :: ((IO a -> IO a) -> IO b) -> IO b
> mask io = do
> b <- blocked
> if b
> then io id
> else block $ io unblock
How does forkIO fit into the picture? That's one
On 04/08/10 19:56, Bas van Dijk wrote:
Control.Concurrent.Thread.fork is a similar and simpler example of why
nonInterruptibleMask is needed:
http://hackage.haskell.org/packages/archive/threads/0.1/doc/html/src/Control-Concurrent-Thread.html#fork
If an asynchronous exception is thrown during th
On Thu, Apr 8, 2010 at 11:45 PM, Bas van Dijk wrote:
> On Thu, Apr 8, 2010 at 9:15 PM, Isaac Dupree
> wrote:
>> I still would like to see examples of where it's needed, because I slightly
>> suspect that wrapping possibly-blocking operations in an exception handler
>> that does something appropri
On Thu, Apr 8, 2010 at 9:15 PM, Isaac Dupree
wrote:
> I still would like to see examples of where it's needed, because I slightly
> suspect that wrapping possibly-blocking operations in an exception handler
> that does something appropriate, along with ordinary 'mask', might be
> sufficient... But
On 04/07/10 17:50, Simon Marlow wrote:
On 07/04/10 21:23, Bas van Dijk wrote:
On Wed, Apr 7, 2010 at 5:12 PM, Simon Marlow wrote:
Comments?
I really like this design.
One question, are you planning to write the MVar utility functions
using 'mask' or using 'nonInterruptibleMask'? As in:
wit
On 04/08/10 04:23, Simon Marlow wrote:
On 07/04/2010 18:54, Isaac Dupree wrote:
On 04/07/10 11:12, Simon Marlow wrote:
It's possible to mis-use the API, e.g.
getUnmask = mask return
...incidentally,
unmask a = mask (\restore -> return restore) >>= (\restore -> restore a)
That doesn't work,
On 07/04/2010 18:54, Isaac Dupree wrote:
On 04/07/10 11:12, Simon Marlow wrote:
It's possible to mis-use the API, e.g.
getUnmask = mask return
...incidentally,
unmask a = mask (\restore -> return restore) >>= (\restore -> restore a)
That doesn't work, as in it can't be used to unmask except
Is there any reason not to use the more standard "uninterruptible"
instead of "noninterruptible"?
Dean
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 07/04/10 21:23, Bas van Dijk wrote:
On Wed, Apr 7, 2010 at 5:12 PM, Simon Marlow wrote:
Comments?
I really like this design.
One question, are you planning to write the MVar utility functions
using 'mask' or using 'nonInterruptibleMask'? As in:
withMVar :: MVar a -> (a -> IO b) -> IO
On Wed, Apr 7, 2010 at 5:12 PM, Simon Marlow wrote:
> Comments?
I really like this design.
One question, are you planning to write the MVar utility functions
using 'mask' or using 'nonInterruptibleMask'? As in:
> withMVar :: MVar a -> (a -> IO b) -> IO b
> withMVar m f = whichMask? $ \restore -
On 04/07/10 11:12, Simon Marlow wrote:
It's possible to mis-use the API, e.g.
getUnmask = mask return
...incidentally,
unmask a = mask (\restore -> return restore) >>= (\restore -> restore a)
mask :: ((IO a -> IO a) -> IO b) -> IO b
It needs to be :: ((forall a. IO a -> IO a) -> IO b) -> I
On 07/04/2010 16:20, Sittampalam, Ganesh wrote:
Simon Marlow wrote:
I came to the conclusion that counting nesting layers doesn't solve
the problem: the wormhole still exists in the form of nested unmasks.
That is, a library function could always escape out of a masked
context by writing
u
Simon Marlow wrote:
> I came to the conclusion that counting nesting layers doesn't solve
> the problem: the wormhole still exists in the form of nested unmasks.
> That is, a library function could always escape out of a masked
> context by writing
>
>unmask $ unmask $ unmask $ ...
>
> enoug
On 25/03/2010 23:16, Bas van Dijk wrote:
On Thu, Mar 25, 2010 at 11:23 PM, Simon Marlow wrote:
So I'm all for deprecating 'block' in favor of 'mask'. However what do
we call 'unblock'? 'unmask' maybe? However when we have:
mask $ mask $ unmask x
and these operations have the counting nesting
Simon Marlow writes:
> On 26/03/2010 19:51, Isaac Dupree wrote:
>> On 03/25/10 12:36, Simon Marlow wrote:
>>> I'd also be amenable to having block/unblock count nesting levels
>>> instead, I don't think it would be too hard to implement and it wouldn't
>>> require any changes at the library level
On 26/03/2010 19:51, Isaac Dupree wrote:
On 03/25/10 12:36, Simon Marlow wrote:
I'd also be amenable to having block/unblock count nesting levels
instead, I don't think it would be too hard to implement and it wouldn't
require any changes at the library level.
Wasn't there a reason that it did
On 03/25/10 12:36, Simon Marlow wrote:
I'd also be amenable to having block/unblock count nesting levels
instead, I don't think it would be too hard to implement and it wouldn't
require any changes at the library level.
Wasn't there a reason that it didn't nest?
I think it was that operations
On Mar 25, 2010, at 19:16 , Bas van Dijk wrote:
But with regard to naming, I think the name 'unmask' is a bit
misleading because it doesn't unmask asynchronous exceptions. What it
does is remove a layer of masking so to speak. I think the names of
the functions should reflect the nesting or stack
On Thu, Mar 25, 2010 at 11:23 PM, Simon Marlow wrote:
>> So I'm all for deprecating 'block' in favor of 'mask'. However what do
>> we call 'unblock'? 'unmask' maybe? However when we have:
>>
>> mask $ mask $ unmask x
>>
>> and these operations have the counting nesting levels semantics,
>> asynchr
On 25/03/10 17:16, Bas van Dijk wrote:
On Thu, Mar 25, 2010 at 5:36 PM, Simon Marlow wrote:
Nice, I hadn't noticed that you can now code this up in the library since we
added 'blocked'. Unfortunately this isn't cheap: 'blocked' is currently an
out-of-line call to the RTS, so if we want to star
On Thu, 25 Mar 2010 18:16:07 +0100, you wrote:
>Yes counting the nesting level like Twan proposed will definitely
>solve the modularity problem.
>
>I do think we need to optimize the block and unblock operations in
>such a way that they don't need to use IORefs to save the counting
>level. The ver
On Thu, Mar 25, 2010 at 5:36 PM, Simon Marlow wrote:
> Nice, I hadn't noticed that you can now code this up in the library since we
> added 'blocked'. Unfortunately this isn't cheap: 'blocked' is currently an
> out-of-line call to the RTS, so if we want to start using it for important
> things li
On 25/03/2010 11:57, Bas van Dijk wrote:
Dear all, (sorry for this long mail)
When programming in the IO monad you have to be careful about
asynchronous exceptions. These nasty little worms can be thrown to you
at any point in your IO computation. You have to be extra careful when
doing, what mu
43 matches
Mail list logo