[Haskell-cafe] threadDelay delays less time than expected (Windows)
amindfv at gmail.com
amindfv at gmail.com
Wed Dec 28 16:51:48 UTC 2016
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Tom
> El 28 dic 2016, a las 08:20, Lian Hung Hon <hon.lianhung at gmail.com> escribió:
>
> Dear Haskellers,
>
> I am baffled by a strange bug (?) with threadDelay on Windows. It delays for less time than expected (500 seconds vs expected 24 hours), and is consistently reproducible on my system. Can someone have a look (need some patience, ~8 minutes waiting), just to be sure? I glanced around trac but didn't find any related issues.
>
> How to reproduce:
>
> module Main where
>
> import Data.Time
> import Control.Concurrent
> import Control.Monad
>
> main :: IO ()
> main = do
> _ <- forkIO thread
> getLine >>= print -- Just to keep the main thread running
>
> thread :: IO ()
> thread = forever $ do
> now <- getCurrentTime
> print now
> threadDelay 86400000000
> print "done waiting"
>
>
> Expected result:
> 2016-12-28 13:07:49.5113098 UTC
> ...
> (next timing should be the next day 2016-12-29)
>
>
> Actual result:
> 2016-12-28 13:07:49.5113098 UTC
> "done waiting"
> 2016-12-28 13:16:10.2159485 UTC
> "done waiting"
> 2016-12-28 13:24:30.8735845 UTC
> "done waiting"
> 2016-12-28 13:32:51.5292203 UTC
> ...
>
>
> System: Windows 7 Enterprise Service Pack 1, ghc 7.10.3
>
>
> This seems specific to Windows, it doesn't appear on Debian 8. Help is appreciated!
>
>
> Regards,
> Hon
>
> Rant: It has cost me significant debugging time! Please tell me I made a rookie mistake or misread the docs somewhere!
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20161228/48a69a38/attachment.html>
More information about the Haskell-Cafe
mailing list