RE: [Haskell-cafe] Implementing computations with timeout

2005-01-10 Thread Simon Marlow
On 07 January 2005 20:00, Sebastian Sylvan wrote:

> On Fri, 7 Jan 2005 20:56:42 +0100, Sebastian Sylvan
> <[EMAIL PROTECTED]> wrote:
>> On Fri, 07 Jan 2005 15:31:10 +0200, Einar Karttunen
>>  wrote:
>>> Hello
>>> 
>>> What is the best way of doing an computation with a timeout?
>> 
>> I like the approach taken in  "Tackling the ackward squad":
>> 
> 
> I should also state that this isn't safe when it comes to asynchronous
> exceptions.
> If one were to raise an exception in a timeout'd computation it would
> simply abort the takeMVar which means the two child processes won't
> get killed.

Yes, making a timeout combinator that (a) can be nested and (b) is
invisible with respect to asynchronous exceptions is quite a challenge.
I'm not sure that we managed to do it.  STM will almost certainly make
it easier, though.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Implementing computations with timeout

2005-01-10 Thread Simon Marlow
On 07 January 2005 22:17, Tomasz Zielonka wrote:

> On Fri, Jan 07, 2005 at 11:00:27PM +0100, Tomasz Zielonka wrote:
>> Hmmm, TMVar's seem to be significantly (ie. 6 times) faster than
>> MVars in some simple tests :) 
>> 
>> Is it expected?
> 
> If it is, we can reimplement MVars using STM, when STM becomes stable
> :) 

No, TMVars are quite a bit slower than MVars if you use the basic
takeMVar/putMVar ops.  However, if you use the safer withMVar/modifyMVar
combinators, then you'll probably find that performance is about the
same. A simple test I did comparing TChan with Chan came up with roughly
the same performance, and STM isn't really tuned yet.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 11:00:27PM +0100, Tomasz Zielonka wrote:
> Hmmm, TMVar's seem to be significantly (ie. 6 times) faster than MVars
> in some simple tests :)
> 
> Is it expected?

If it is, we can reimplement MVars using STM, when STM becomes stable :)

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 04:47:12PM +0100, Tomasz Zielonka wrote:
> On Fri, Jan 07, 2005 at 04:55:05PM +0200, Einar Karttunen wrote:
> > if we use IO as the signature then using the TMVar has few advantages over
> > using an MVar.
> 
> Yes, I think you are right here.

Hmmm, TMVar's seem to be significantly (ie. 6 times) faster than MVars
in some simple tests :)

Is it expected?

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Sebastian Sylvan
On Fri, 7 Jan 2005 20:56:42 +0100, Sebastian Sylvan
<[EMAIL PROTECTED]> wrote:
> On Fri, 07 Jan 2005 15:31:10 +0200, Einar Karttunen
>  wrote:
> > Hello
> >
> > What is the best way of doing an computation with a timeout?
> 
> I like the approach taken in  "Tackling the ackward squad":
> 

I should also state that this isn't safe when it comes to asynchronous
exceptions.
If one were to raise an exception in a timeout'd computation it would
simply abort the takeMVar which means the two child processes won't
get killed.

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Sebastian Sylvan
On Fri, 07 Jan 2005 15:31:10 +0200, Einar Karttunen
 wrote:
> Hello
> 
> What is the best way of doing an computation with a timeout?

I like the approach taken in  "Tackling the ackward squad":

First a funcion which will "race" two IO computations against each
other, returning the "winning" result.
This is accomplished by simply spawning a thread for each computation
which does nothing but evalute the IO computation and putting the
result in an MVar.
Then the MVar is read (this will lock until there is something in the
MVar to read), when finally there is something to read it will
obviously contain the result of the IO computation that completed
first. Then both of the spawned threads are killed (one of them is
already dead at this point) via throwTo.

parIO :: IO a -> IO a -> IO a
parIO a1 a2
 = do m <- newEmptyMVar ;
c1 <- forkIO (child m a1) ;
c2 <- forkIO (child m a2) ;
r <- takeMVar m ;
throwTo c1 Kill ;
throwTo c2 Kill ;
return r
 where child m a = do r <- a
putMVar m r 

Next we simply race the IO computation to be "timed out" against a
thread which delays and then returns Nothing.

timeout :: Int -> IO a -> IO (Maybe a)
timeout n a = parIO a1 a2
where a1 = do r <-a
  return (Just r)
  a2 = do threadDelay n
  return Nothing


/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 04:55:05PM +0200, Einar Karttunen wrote:
> if we use IO as the signature then using the TMVar has few advantages over
> using an MVar.

Yes, I think you are right here.

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 04:55:05PM +0200, Einar Karttunen wrote:
> 
> Isn't this buggy if fun just keeps working without throwing an exception
> or using retry? I meant wholly inside STM

There is not that much that you can do inside STM. This may be a problem
if you want to wait for a genuine IO action.

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 02:57:19PM +0100, Tomasz Zielonka wrote:
> My guess is it would be something like this, however you may want to do it
> differently to get better compositionality (withTimeout returns an IO action,
> not a STM action):

Maybe this will suffice, but I don't know if the delay thread will be
garbage collected.

  import Control.Concurrent
  import Control.Concurrent.STM
  import Monad (when)

  makeDelay :: Int -> IO (STM ())
  makeDelay time = do
  v <- atomically (newTVar False)
  forkIO $ do
  threadDelay time
  atomically (writeTVar v True)
  return $ readTVar v >>= \b -> when (not b) retry

  withTimeout :: Int -> STM a -> IO (Maybe a)
  withTimeout time fun = do
  delay <- makeDelay time
  atomically (fmap Just fun `orElse` (delay >> return Nothing))

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
Tomasz Zielonka <[EMAIL PROTECTED]> writes:
>   import Control.Concurrent (forkIO, threadDelay)
>   import Control.Concurrent.STM
>
>   withTimeout :: Int -> STM a -> IO (Maybe a)
>   withTimeout time fun = do
>   mv <- atomically newEmptyTMVar
>   tid <- forkIO $ do
>   threadDelay time
>   atomically (putTMVar mv ())
>   x <- atomically (fmap Just fun `orElse` (takeTMVar mv >> return 
> Nothing))
>   killThread tid
>   return x

Isn't this buggy if fun just keeps working without throwing an exception
or using retry? I meant wholly inside STM - if we use IO as the
signature then using the TMVar has few advantages over using an MVar.

- Einar Karttunen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 03:31:10PM +0200, Einar Karttunen wrote:
> Hello
> 
> What is the best way of doing an computation with a timeout?
> 
> A naive implementation using two threads is easy to create - but 
> what is the preferred solution?
> 
> withTimeout :: forall a. Int -> IO a -> IO (Maybe a)

> btw How would I do the same with the new STM abstraction?

My guess is it would be something like this, however you may want to do it
differently to get better compositionality (withTimeout returns an IO action,
not a STM action):

  import Control.Concurrent (forkIO, threadDelay)
  import Control.Concurrent.STM

  withTimeout :: Int -> STM a -> IO (Maybe a)
  withTimeout time fun = do
  mv <- atomically newEmptyTMVar
  tid <- forkIO $ do
  threadDelay time
  atomically (putTMVar mv ())
  x <- atomically (fmap Just fun `orElse` (takeTMVar mv >> return Nothing))
  killThread tid
  return x

PS. STM is cool! :)

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe