Concurrent Haskell Actions with Timeout

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 Best Regards, Cetin Sert

2009/5/30 Cetin Sert
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

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
2009/5/30 Cetin Sert
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

On Sat, May 30, 2009 at 10:32 PM, Cetin Sert
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)'
Right, I forgot about the "Either" bit so you'd have to make sure the action's result and the default has the same type (or modify it to return an Either). -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

The proper way is just to wrap System.Timeout, which does some rather clever things with regards to exception semantics. The code for it is a joy to read, by the way. --S. On May 30, 2009, at 5:36 PM, Sebastian Sylvan wrote:
On Sat, May 30, 2009 at 10:32 PM, Cetin Sert
wrote: 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)'
Right, I forgot about the "Either" bit so you'd have to make sure the action's result and the default has the same type (or modify it to return an Either).
-- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

-__-" hehe why did I not let Hayoo or Hoogle help me there *sigh*
Thanks!!
2009/5/31 Sterling Clover
The proper way is just to wrap System.Timeout, which does some rather clever things with regards to exception semantics. The code for it is a joy to read, by the way.
--S.
On May 30, 2009, at 5:36 PM, Sebastian Sylvan wrote:
On Sat, May 30, 2009 at 10:32 PM, Cetin Sert
wrote: 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)'
Right, I forgot about the "Either" bit so you'd have to make sure the action's result and the default has the same type (or modify it to return an Either).
-- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Cetin Sert
-
Sebastian Sylvan
-
Sterling Clover