Thank you for your reply, I'd come up with the following:

timed :: Int → IO a → b → IO (Either b a)
timed max act def = do

  r ← new

  t ← forkIO $ do
    a ← act
    r ≔ Right a

  s ← forkIO $ do
    wait max
    e ← em r
    case e of
      True  → do
        kill t
        r ≔ Left def

      False → return ()

  takeMVar r

---------------------

*Network.Port.Scan> timed 500 (wait 50000 >> return 0) 'x'
Left 'x'
*Network.Port.Scan> timed 500000 (wait 50000 >> return 0) 'x'
Right 0

---------------------

before reading your reply:

timed timeout act fallback = do
   res <- newEmptyMVar
   tid <- forkIO $ act >>= writeMVar res
   threadDelay timeout
   stillRunning <- isEmptyMVar res
   if stillRunning then killThread tid >> return fallback else takeMVar res

---------------------

*Network.Port.Scan> timed2 500 (wait 50000 >> return 0) 'x'

<interactive>:1:33:
    No instance for (Num Char)
      arising from the literal `0' at <interactive>:1:33
    Possible fix: add an instance declaration for (Num Char)
    In the first argument of `return', namely `0'
    In the second argument of `(>>)', namely `return 0'
    In the second argument of `timed2', namely
        `(wait 50000 >> return 0)'

Regards,
Cetin Sert

2009/5/30 Sebastian Sylvan <[email protected]>

>
>
> 2009/5/30 Cetin Sert <[email protected]>
>
>> Hi how could one implement a function in concurrent haskell that either
>> returns 'a' successfully or due timeout 'b'?
>>
>> timed :: Int → IO a → b → IO (Either a b)
>> timed max act def = do
>>
>
>
> Something like (warning, untested code - no compiler atm).
>
> timed timeout act fallback = do
>    res <- newEmptyMVar
>    tid <- forkIO $ act >>= writeMVar res
>    threadDelay timeout
>    stillRunning <- isEmptyMVar res
>    if stillRunning then killThread tid >> return fallback else takeMVar res
>
> --
> Sebastian Sylvan
> +44(0)7857-300802
> UIN: 44640862
>
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to