Proposal: System.Timeout module for base

On Fri, Jan 26, 2007 at 11:48:58PM +0100, Peter Simons wrote:
+-- |Wrap an 'IO' computation to time out and return @Nothing@ if it hasn't +-- succeeded after @n@ microseconds. If the computation finishes before the +-- timeout expires, @Just a@ is returned. Timeouts are specified in microseconds +-- (@1\/10^6@ seconds). Negative values mean \"wait indefinitely\". When +-- specifying long timeouts, be careful not to exceed @maxBound :: Int@. + +timeout :: Int -> IO a -> IO (Maybe a)
I'd prefer a function of the type timeout :: Int -> IO a -> IO a which just throws the exception when there's an error. I like exception handling. Then you could optionally also include a catchTimeout :: IO a -> IO a -> IO a to avoid exposing your exception type. Another question is whether we could have a nicer type for the time argument. It'd certainly be nicer if we could use some sort of time type that has units, but I've not been following the time module at all, so I don't know if there's an appropriate type. I'd hate to have to uglify code with error-prone unit conversions when I might be able to have something for which the compiler can verify the unit conversions for me. Otherwise I'd be tempted to want System.Timeout to export hour :: Int second :: Int day :: Int which would get silly. -- David Roundy http://www.darcs.net

Hi David,
I'd prefer a function of the type "timeout :: Int -> IO a -> IO a" which just throws the exception when there's an error. I like exception handling.
A timeout event can be signaled using both exceptions and a return code ('Nothing'), and there are valid arguments that favor either approach. In my humble opinion, an exception is an _exceptional_ event. It is something you didn't expect to happen. When I read from a socket, but that socket doesn't work anymore because the peer suddenly closed the connection, then that is something I want to have reported as an exception. When I read from a socket, but can't because the input stream has reached EOF, then that is _not_ an exception, that is EOF, a state every stream reaches eventually. In terms of timeout, I prefer the "Maybe a" return type because when I say "timeout n f", a timeout event is an expected result, not an unexpected one. Besides, the computation timeout n f >>= maybe (fail "timeout") return is no major effort to write and has the neat advantage that it doesn't dictate the type of the exception thrown in case of a timeout. I like the fact that the dynamic exception used internally isn't visible on the outside.
Another question is whether we could have a nicer type for the time argument.
Originally, the module exported "type MicroSeconds = int" to make things a little more readable, but in the end it felt odd to have System.Timeout export a MicroSeconds type. The signature we have now isn't perfect, but at least it's consistent with hWaitForInput and threadDelay. If there is a concrete type the code could use, I'm all for using it, but I'm against delaying the inclusion of timeout for another couple of years because we don't have a type for microseconds right now. Best regards, Peter

On Sun, Jan 28, 2007 at 05:46:06PM +0100, Peter Simons wrote:
Hi David,
Hi Peter,
I'd prefer a function of the type "timeout :: Int -> IO a -> IO a" which just throws the exception when there's an error. I like exception handling.
A timeout event can be signaled using both exceptions and a return code ('Nothing'), and there are valid arguments that favor either approach. In my humble opinion, an exception is an _exceptional_ event. It is something you didn't expect to happen. When I read from a socket, but that socket doesn't work anymore because the peer suddenly closed the connection, then that is something I want to have reported as an exception. When I read from a socket, but can't because the input stream has reached EOF, then that is _not_ an exception, that is EOF, a state every stream reaches eventually.
The difference is that there already exists a whole framework for dealing with exceptions in a pretty way, and I'd like to make use of that. Actually, reading beyond EOF does raise an exception, doesn't it? In my opinion, whenever external forces prevent my code from doing what it's trying to do, that's an exception, and my preference is to use exceptions to describe that, as they're readily handled in a modular way, without manual threading of error information. We could have readChar :: IO (Maybe Char) but we don't, because then every bit of code that uses readChar would have to deal with the exception, instead of having it propogated up to the handler written by the coder.
In terms of timeout, I prefer the "Maybe a" return type because when I say "timeout n f", a timeout event is an expected result, not an unexpected one. Besides, the computation
timeout n f >>= maybe (fail "timeout") return
is no major effort to write and has the neat advantage that it doesn't dictate the type of the exception thrown in case of a timeout. I like the fact that the dynamic exception used internally isn't visible on the outside.
Alternatively, it's also no hard work to write (Just `fmap` timeout n t) `catch` (\_ -> return Nothing) or (Just `fmap` timeout n t) `catchTimeout` (return Nothing) In the standard libraries, I prefer simplicity of exception handling. As you've written it, every library that uses timeout (e.g. an http client library, etc) would need to implement their own exception handling for timeout errors. That doesn't seem like a plus, to me. -- David Roundy http://www.darcs.net

Hi David, let's agree to disagree. Apparently our personal preferences differ when it comes to error handling. Regarding the submission of 'timeout', I feel that those two lines say it all: timeout n f >>= maybe (fail "timeout") return (Just `fmap` timeout n t) `catch` (\_ -> return Nothing) An exception-throwing timeout combinator is obviously equivalent to one that returns "Maybe a" because both versions can be trivially wrapped to behave like the other one. I am in favor of using the version we have. Best regards, Peter

On 26.01 23:48, Peter Simons wrote:
timeout :: Int -> IO a -> IO (Maybe a) timeout n f | n < 0 = fmap Just f | n == 0 = return Nothing | otherwise = do pid <- myThreadId ex <- fmap Timeout newUnique handleJust (\e -> dynExceptions e >>= fromDynamic >>= guard . (ex ==)) (\_ -> return Nothing) (bracket (forkIO (threadDelay n >> throwDynTo pid ex)) (killThread) (\_ -> fmap Just f))
This seems broken on GHC with FFI. The thread gets blocked on a FFI call that blocks forever and thus the timeout exception is not delivered - if I remember things correctly. - Einar Karttunen

Hi Einar,
This seems broken on GHC with FFI. The thread gets blocked on a FFI call that blocks forever and thus the timeout exception is not delivered - if I remember things correctly.
I am sorry, but I'm uncertain whether I understand your explanation correctly. The problem you describe seems to be that the to-be-timed-out thread blocks because of an FFI call and thus cannot be interrupted when the timeout occurs. Is this what you were saying? If it is, I'm wondering whether that behavior is something that should be credited to the timeout function. In other words, I don't feel that timeout is broken because a blocked FFI call can't receive exceptions. It is, however, a limitation that should be documented. Best regards, Peter

On 28.01 17:21, Peter Simons wrote:
I am sorry, but I'm uncertain whether I understand your explanation correctly. The problem you describe seems to be that the to-be-timed-out thread blocks because of an FFI call and thus cannot be interrupted when the timeout occurs. Is this what you were saying? If it is, I'm wondering whether that behavior is something that should be credited to the timeout function. In other words, I don't feel that timeout is broken because a blocked FFI call can't receive exceptions. It is, however, a limitation that should be documented.
Yes, this is the case. Of course one can also write timeout combinators that work even if the blocking call is a FFI one. Maybe have two variants since the safer one is slightly slower. - Einar Karttunen

Einar Karttunen wrote:
On 28.01 17:21, Peter Simons wrote:
I am sorry, but I'm uncertain whether I understand your explanation correctly. The problem you describe seems to be that the to-be-timed-out thread blocks because of an FFI call and thus cannot be interrupted when the timeout occurs. Is this what you were saying? If it is, I'm wondering whether that behavior is something that should be credited to the timeout function. In other words, I don't feel that timeout is broken because a blocked FFI call can't receive exceptions. It is, however, a limitation that should be documented.
Yes, this is the case. Of course one can also write timeout combinators that work even if the blocking call is a FFI one.
Maybe have two variants since the safer one is slightly slower.
How would you interrupt the FFI call when the timeout expired? pthread_cancel(), maybe? Or perhaps you just want to run the IO action in a separate thread, so that timeout can return even though the IO action is still blocked. I'd say this was wrong though, because the FFI call will still be running, and that may well be visible. Cheers, Simon

On 30.01 12:20, Simon Marlow wrote:
How would you interrupt the FFI call when the timeout expired? pthread_cancel(), maybe?
That is one solution. Just letting it running and returning is "good enough" for most things. One common thing would be network related functions if implemented in a blocking way (over various C libraries). They usually do need timeouts and are blocking FFI calls. - musasabi

Einar Karttunen wrote:
On 30.01 12:20, Simon Marlow wrote:
How would you interrupt the FFI call when the timeout expired? pthread_cancel(), maybe?
That is one solution. Just letting it running and returning is "good enough" for most things. One common thing would be network related functions if implemented in a blocking way (over various C libraries). They usually do need timeouts and are blocking FFI calls.
I think it would be wrong to leave the FFI call running and still deliver the exception to the thread. Wrong because it leads to surprising behaviour: if the blocked call has a side effect, e.g. a write(), then the side-effect may still heppen, despite the fact that the Haskell thread has been interrupted by the timeout. And wrong because it's not possible to implement it in GHC, at least for bound threads: the OS thread making the foreign call is the only one that can execute the Haskell thread. So that leaves pthread_cancel(). Unfortunately pthread_cancel() isn't really an exception - it can be caught, but the handler is for cleaning up only, it can't continue. So this doesn't let us interrupt FFI calls either. Any other suggestions? My take on this is that if you want to make an interruptible FFI call, you make it in a separate thread, and ensure that if it continues to execute after the parent has received an exception, then this is benign. This is essentially what the IO manager thread in the GHC IO library does: any thread blocked on I/O can be interrupted by a signal, because it is the IO manager thread performing the FFI call. Cheers, Simon

Hello Simon, Thursday, February 1, 2007, 12:46:29 PM, you wrote:
Any other suggestions?
may be, we can raise exception in foreign language? at least for 'safe' calls. i.e., we establish in RTS signal handler. this handler checks whether we are performing safe call and if so - raise language-specific exception... hmm, if that's possible btw, how about using for *Haskell* code *default* signal handler that raise Haskell exception? i think that using signal handlers to process OS-generated events is just legacy from the C days. i.e. 'main' should be called by RTS inside code like this: mainThread <- myThreadId let onBreak event = do throwTo mainThread BreakException bracket (installHandler$ Catch onBreak) (installHandler) $ \oldHandler -> do main (of course, this handles only ^Break and only on Windows) among other things, this should make signal handling portable between Win/Unix -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Simon,
Thursday, February 1, 2007, 12:46:29 PM, you wrote:
Any other suggestions?
may be, we can raise exception in foreign language? at least for 'safe' calls. i.e., we establish in RTS signal handler. this handler checks whether we are performing safe call and if so - raise language-specific exception... hmm, if that's possible
There's no way to raise an exception in C, in general.
btw, how about using for *Haskell* code *default* signal handler that raise Haskell exception? i think that using signal handlers to process OS-generated events is just legacy from the C days. i.e. 'main' should be called by RTS inside code like this:
mainThread <- myThreadId let onBreak event = do throwTo mainThread BreakException bracket (installHandler$ Catch onBreak) (installHandler) $ \oldHandler -> do main
(of course, this handles only ^Break and only on Windows)
among other things, this should make signal handling portable between Win/Unix
Yes, we've discussed this in the past (e.g. there was a thread about this on the haskell-prime list). I'm definitely in favour of doing something along these lines. Cheers, Simon

btw, how about using for *Haskell* code *default* signal handler that raise Haskell exception? i think that using signal handlers to process OS-generated events is just legacy from the C days. i.e. 'main' should be called by RTS inside code like this:
mainThread <- myThreadId let onBreak event = do throwTo mainThread BreakException bracket (installHandler$ Catch onBreak) (installHandler) $ \oldHandler -> do main
(of course, this handles only ^Break and only on Windows)
among other things, this should make signal handling portable between Win/Unix
Yes, we've discussed this in the past (e.g. there was a thread about this on the haskell-prime list). I'm definitely in favour of doing something along these lines.
how about adding such facility to ghc HEAD? i can write initial windows implementation and put it to discussion here or in ghc maillist -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
btw, how about using for *Haskell* code *default* signal handler that raise Haskell exception? i think that using signal handlers to process OS-generated events is just legacy from the C days. i.e. 'main' should be called by RTS inside code like this:
mainThread <- myThreadId let onBreak event = do throwTo mainThread BreakException bracket (installHandler$ Catch onBreak) (installHandler) $ \oldHandler -> do main
(of course, this handles only ^Break and only on Windows)
among other things, this should make signal handling portable between Win/Unix
Yes, we've discussed this in the past (e.g. there was a thread about this on the haskell-prime list). I'm definitely in favour of doing something along these lines.
how about adding such facility to ghc HEAD? i can write initial windows implementation and put it to discussion here or in ghc maillist
I don't have a clear idea for the design, I'd have to go back and look at the haskell prime discussion. Do you want to propose something? Cheers, Simon

Simon Marlow writes:
Any other suggestions?
The fact that blocking FFI threads cannot be timed out with the current implementation is unpleasant, and I would be happy to lift that limitation. I wonder, though, whether depending on unportable low-level OS mechanisms like pthread_cancel() or pthread signals to deliver a timeout might prove to be far more unpleasant than the limitation we try to lift. As far as I'm concerned, the limitation that blocking FFI threads cannot be timed out from Haskell is not that hard. A blocking FFI call, well, blocks. In all honesty, I wouldn't expect that to be any different. I would be far more surprised if it turned out that my currently running C code suddenly receives signals and is supposed to deal with that. My preferred approach would be to agree on the _signature_ of the combinator. We should find consensus that timeout is supposed to look like this: timeout :: Int -> IO a -> IO (Maybe a) If that is the case, then we can add the function into the distribution now and worry about wild improvements of the implementation later. I feel that making even an unperfect solution available to Haskell programmers would be a significant step forward. Maybe this endeavor would be easier to accomplish if we rename the function to unsafeTimeout? ;-) Peter

Peter Simons wrote:
Simon Marlow writes:
Any other suggestions?
The fact that blocking FFI threads cannot be timed out with the current implementation is unpleasant, and I would be happy to lift that limitation.
I wonder, though, whether depending on unportable low-level OS mechanisms like pthread_cancel() or pthread signals to deliver a timeout might prove to be far more unpleasant than the limitation we try to lift. As far as I'm concerned, the limitation that blocking FFI threads cannot be timed out from Haskell is not that hard. A blocking FFI call, well, blocks. In all honesty, I wouldn't expect that to be any different. I would be far more surprised if it turned out that my currently running C code suddenly receives signals and is supposed to deal with that.
Yes, agreed.
My preferred approach would be to agree on the _signature_ of the combinator. We should find consensus that timeout is supposed to look like this:
timeout :: Int -> IO a -> IO (Maybe a)
If that is the case, then we can add the function into the distribution now and worry about wild improvements of the implementation later. I feel that making even an unperfect solution available to Haskell programmers would be a significant step forward.
I'd go with the proposed signature above. One further suggestion: the docs should mention *how* the timeout is implemented (namely as an asynchronous dynamic exception), which makes it clear that you can take the usual protective measures against mutable data getting into an inconsistent state when the timeout happens: exception handlers, bracket, withMVar, block/unblock etc. Cheers, Simon
participants (5)
-
Bulat Ziganshin
-
David Roundy
-
Einar Karttunen
-
Peter Simons
-
Simon Marlow