Why does sleep not work?

Hi Haskell Cafe, I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5. I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does: main = do putStrLn "Waiting for 5 seconds." threadDelay 5000000 -- works putStrLn "Done." main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done." Anybody know what's happening? Thanks -John

Hello John, Tuesday, February 10, 2009, 12:35:25 AM, you wrote:
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
Anybody know what's happening?
1) this depends on your sleep definition 2) read threadDelay docs -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi John,
Which sleep are you using? From which module? Can you show the full source
with import statements?
Cheers,
Peter
2009/2/9 John Ky
Hi Haskell Cafe,
I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5.
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
main = do putStrLn "Waiting for 5 seconds." threadDelay 5000000 -- works putStrLn "Done."
main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
Anybody know what's happening?
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Peter,
Source code:
import System.IO
import System.Posix
main = do
putStrLn "Waiting for 5 seconds."
sleep 5 -- doesn't sleep at all
putStrLn "Done."
OS:
Mac OS X 10.5
Compile command:
ghc --threaded testsleep.hs
If I remove --threaded, then it does sleep.
Thanks,
-John
On Tue, Feb 10, 2009 at 8:59 AM, Peter Verswyvelen
Hi John, Which sleep are you using? From which module? Can you show the full source with import statements?
Cheers, Peter
2009/2/9 John Ky
Hi Haskell Cafe,
I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5.
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
main = do putStrLn "Waiting for 5 seconds." threadDelay 5000000 -- works putStrLn "Done."
main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
Anybody know what's happening?
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I can confirm this behaviour, on: Linux 2.6.27-11-generic #1 SMP i686 GNU/Linux Difference in the RTS between non-working and working: ("RTS way", "rts_thr") ("RTS way", "rts") - George

The POSIX sleep function is defined as:
sleep() makes the current process sleep until seconds seconds have
elapsed or a signal arrives which is not ignored.
Sounds like a signal is arriving that is interrupting the sleep.
-Corey O'Connor
2009/2/9 John Ky
Hi Peter,
Source code: import System.IO import System.Posix
main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
OS: Mac OS X 10.5
Compile command: ghc --threaded testsleep.hs
If I remove --threaded, then it does sleep.
Thanks,
-John
On Tue, Feb 10, 2009 at 8:59 AM, Peter Verswyvelen
wrote: Hi John, Which sleep are you using? From which module? Can you show the full source with import statements? Cheers, Peter 2009/2/9 John Ky
Hi Haskell Cafe,
I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5.
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
main = do putStrLn "Waiting for 5 seconds." threadDelay 5000000 -- works putStrLn "Done."
main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
Anybody know what's happening?
Thanks
-John
_______________________________________________ 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

Not to say the issue shouldn't be tracked down, but shouldn't a more
portable function be used anyway?
untested example:
maxBoundMicroSecInSec =(maxBound `div` 10^6)
threadDelaySec :: Int -> IO ()
threadDelaySec s
| s > maxBoundMicroSecInSec = threadDelay (maxBoundMicroSecInSec *
10^6) >> threadDelaySec (s - maxBoundMicroSecInSec)
| otherwise = threadDelay (s * 10^6)
On Tue, Feb 10, 2009 at 5:57 PM, Corey O'Connor
The POSIX sleep function is defined as: sleep() makes the current process sleep until seconds seconds have elapsed or a signal arrives which is not ignored.
Sounds like a signal is arriving that is interrupting the sleep.
-Corey O'Connor
2009/2/9 John Ky
: Hi Peter,
Source code: import System.IO import System.Posix
main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
OS: Mac OS X 10.5
Compile command: ghc --threaded testsleep.hs
If I remove --threaded, then it does sleep.
Thanks,
-John
On Tue, Feb 10, 2009 at 8:59 AM, Peter Verswyvelen
wrote: Hi John, Which sleep are you using? From which module? Can you show the full source with import statements? Cheers, Peter 2009/2/9 John Ky
Hi Haskell Cafe,
I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5.
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
main = do putStrLn "Waiting for 5 seconds." threadDelay 5000000 -- works putStrLn "Done."
main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
Anybody know what's happening?
Thanks
-John
_______________________________________________ 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, 2009-02-10 at 09:57 -0800, Corey O'Connor wrote:
The POSIX sleep function is defined as: sleep() makes the current process sleep until seconds seconds have elapsed or a signal arrives which is not ignored.
Sounds like a signal is arriving that is interrupting the sleep.
-Corey O'Connor
I tested this when testing the original code; sleep reports that the signal received is 5 (SIGTRAP). However, the following code does not work:
import System.Posix
main = do putStrLn "Waiting for 5 seconds." print sigTRAP blockSignals $ addSignal sigTRAP emptySignalSet signal <- sleep 5 print signal putStrLn "Done."
This, on the other (strange) hand, does:
import System.Posix
main = do putStrLn "Waiting for 5 seconds." blockSignals fullSignalSet signal <- sleep 5 print signal putStrLn "Done."
- George

John Ky ha scritto:
Hi Haskell Cafe,
I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5.
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
[...] main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
Anybody know what's happening?
Here is a syscal trace, on Linux: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=1332#a1332 The interesting part: write(1, "Waiting for 5 seconds.\n"..., 23) = 23 rt_sigprocmask(SIG_BLOCK, [CHLD], [], 8) = 0 rt_sigaction(SIGCHLD, NULL, {SIG_DFL}, 8) = 0 rt_sigprocmask(SIG_SETMASK, [], NULL, 8) = 0 nanosleep({5, 0}, 0xbf85f5cc) = ? ERESTART_RESTARTBLOCK (To be restarted) --- SIGVTALRM (Virtual timer expired) @ 0 (0) --- sigreturn() = ? (mask now []) write(1, "5\n"..., 2) = 2 So, it seems nanosleep get interruped by a signal. Manlio Perillo

On Wed, 2009-02-11 at 00:05 +0100, Manlio Perillo wrote:
John Ky ha scritto:
Hi Haskell Cafe,
I wrote very short program to sleep for 5 seconds compiled with the -threaded option in ghc on the Mac OS X 1.5.
I am finding that using the sleep function doesn't sleep at all, whereas using threadDelay does:
[...] main = do putStrLn "Waiting for 5 seconds." sleep 5 -- doesn't sleep at all putStrLn "Done."
Anybody know what's happening?
Here is a syscal trace, on Linux: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=1332#a1332
The interesting part: write(1, "Waiting for 5 seconds.\n"..., 23) = 23 rt_sigprocmask(SIG_BLOCK, [CHLD], [], 8) = 0 rt_sigaction(SIGCHLD, NULL, {SIG_DFL}, 8) = 0 rt_sigprocmask(SIG_SETMASK, [], NULL, 8) = 0 nanosleep({5, 0}, 0xbf85f5cc) = ? ERESTART_RESTARTBLOCK (To be restarted) --- SIGVTALRM (Virtual timer expired) @ 0 (0) --- sigreturn() = ? (mask now []) write(1, "5\n"..., 2) = 2
So, it seems nanosleep get interruped by a signal.
This works:
import System.Posix
main = do putStrLn "Waiting for 5 seconds." blockSignals $ addSignal sigVTALRM emptySignalSet sleep 5 putStrLn "Done."
So (see my earlier email) `sleep` is lying about what interrupts it :) - George

Corey O'Connor ha scritto:
2009/2/10 George Pollard
: import System.Posix
main = do putStrLn "Waiting for 5 seconds." blockSignals $ addSignal sigVTALRM emptySignalSet sleep 5 putStrLn "Done."
Huh! Does the GHC runtime uses this signal? Perhaps for scheduling?
Right. It is used for scheduling, as far as I understand. So blocking it is a bad idea (unless you block it in a thread other than the main thread, IMO).
Cheers, -Corey O'Connor
Regards Manlio

George Pollard ha scritto:
[...]
So, it seems nanosleep get interruped by a signal.
This works:
import System.Posix
main = do putStrLn "Waiting for 5 seconds." blockSignals $ addSignal sigVTALRM emptySignalSet sleep 5 putStrLn "Done."
So (see my earlier email) `sleep` is lying about what interrupts it :)
- George
A possibly better solution is: sleep' :: Int -> IO Int sleep' n = do n' <- sleep n if n' == 0 then return 0 else sleep' n' From the trace, I see that nanosleep is being called 17 times here. Another solution is to set RTS flag: ./bug_sleep +RTS -V0 -RTS What strange is that the timer is created in non threaded RTS, too, but sleep is interrupted only with the threaded RTS. This may be caused by an "incorrect" execution of a foreign function marked safe. Regards Manlio

On Wed, 2009-02-11 at 01:50 +0100, Manlio Perillo wrote:
George Pollard ha scritto:
[...]
So, it seems nanosleep get interruped by a signal.
This works:
import System.Posix
main = do putStrLn "Waiting for 5 seconds." blockSignals $ addSignal sigVTALRM emptySignalSet sleep 5 putStrLn "Done."
So (see my earlier email) `sleep` is lying about what interrupts it :)
- George
A possibly better solution is:
sleep' :: Int -> IO Int sleep' n = do n' <- sleep n if n' == 0 then return 0 else sleep' n'
From the trace, I see that nanosleep is being called 17 times here.
Another solution is to set RTS flag: ./bug_sleep +RTS -V0 -RTS
What strange is that the timer is created in non threaded RTS, too, but sleep is interrupted only with the threaded RTS.
This may be caused by an "incorrect" execution of a foreign function marked safe.
I just realized that for some reason I thought that `sleep` reported the signal that interrupted it... contrary to the documentation... as such, several of my replies to this thread may read as non-sequiturs :P
participants (7)
-
Bulat Ziganshin
-
Corey O'Connor
-
George Pollard
-
John Ky
-
Manlio Perillo
-
Peter Verswyvelen
-
Thomas DuBuisson