threadDelay delays less time than expected (Windows)

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!

(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
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.

Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this. Yitz

Dear Tom/Yitz,
Just tested, returns False. I'm on 64 bit by the way. What should I do from
here?
Regards,
Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz

Not to be infuriating, but I think you should check and re-check your
tooling is not using 32 bit values at any particular point.
Notice:
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is
your observation. Any time you depend on `Int` to represent numbers
near or greater than 2^28, or perhaps 2^31 in practice, you should
think hard about bounds and implications regarding portability anyway.
-Thomas
On Wed, Dec 28, 2016 at 4:05 PM, Lian Hung Hon
Dear Tom/Yitz,
Just tested, returns False. I'm on 64 bit by the way. What should I do from here?
Regards, Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
wrote: Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz
_______________________________________________ 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.

If their supplied code sample is failing, couldn't that indicate a bug in the Windows threadDelay implementation for very large values? Hon: if you're looking for a short-term solution you can always: replicateM 48 $ threadDelay $ (half an hour) This way you only have to wait half an hour to be sure there's no overflow or incorrect timing. Tom
El 28 dic 2016, a las 18:47, Thomas DuBuisson
escribió: Not to be infuriating, but I think you should check and re-check your tooling is not using 32 bit values at any particular point.
Notice:
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is your observation. Any time you depend on `Int` to represent numbers near or greater than 2^28, or perhaps 2^31 in practice, you should think hard about bounds and implications regarding portability anyway.
-Thomas
On Wed, Dec 28, 2016 at 4:05 PM, Lian Hung Hon
wrote: Dear Tom/Yitz, Just tested, returns False. I'm on 64 bit by the way. What should I do from here?
Regards, Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
wrote: Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz
_______________________________________________ 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.
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.

Dear Tom,
That is a good workaround, now I'm using divMod with the max value of Int,
and things are working again :) So it really is because of int overflow
somewhere..
Since a workaround is available I guess I won't file a bug report yet.
Thomas' comment also got me second guessing myself..
Thank you everyone for your help and guidance!
Regards,
Hon
On 29 Dec 2016 09:47,
If their supplied code sample is failing, couldn't that indicate a bug in the Windows threadDelay implementation for very large values?
Hon: if you're looking for a short-term solution you can always:
replicateM 48 $ threadDelay $ (half an hour)
This way you only have to wait half an hour to be sure there's no overflow or incorrect timing.
Tom
El 28 dic 2016, a las 18:47, Thomas DuBuisson < thomas.dubuisson@gmail.com> escribió:
Not to be infuriating, but I think you should check and re-check your tooling is not using 32 bit values at any particular point.
Notice:
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is your observation. Any time you depend on `Int` to represent numbers near or greater than 2^28, or perhaps 2^31 in practice, you should think hard about bounds and implications regarding portability anyway.
-Thomas
On Wed, Dec 28, 2016 at 4:05 PM, Lian Hung Hon
wrote: Dear Tom/Yitz, Just tested, returns False. I'm on 64 bit by the way. What should I do from here?
Regards, Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
wrote: Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz
_______________________________________________ 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.
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.

The existence of a workaround doesn't make it not a bug! Definitely report
it anyway. Worst case, the bug is actually in Windows but is now known and
centrally documented. For that matter, GCH could build the replicateM trick
into the implementation on a platform-specific basis.
On Dec 29, 2016 5:21 AM, "Lian Hung Hon"
Dear Tom,
That is a good workaround, now I'm using divMod with the max value of Int, and things are working again :) So it really is because of int overflow somewhere..
Since a workaround is available I guess I won't file a bug report yet. Thomas' comment also got me second guessing myself..
Thank you everyone for your help and guidance!
Regards, Hon
On 29 Dec 2016 09:47,
wrote: If their supplied code sample is failing, couldn't that indicate a bug in the Windows threadDelay implementation for very large values?
Hon: if you're looking for a short-term solution you can always:
replicateM 48 $ threadDelay $ (half an hour)
This way you only have to wait half an hour to be sure there's no overflow or incorrect timing.
Tom
El 28 dic 2016, a las 18:47, Thomas DuBuisson < thomas.dubuisson@gmail.com> escribió:
Not to be infuriating, but I think you should check and re-check your tooling is not using 32 bit values at any particular point.
Notice:
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is your observation. Any time you depend on `Int` to represent numbers near or greater than 2^28, or perhaps 2^31 in practice, you should think hard about bounds and implications regarding portability anyway.
-Thomas
On Wed, Dec 28, 2016 at 4:05 PM, Lian Hung Hon
wrote: Dear Tom/Yitz, Just tested, returns False. I'm on 64 bit by the way. What should I do from here?
Regards, Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
wrote: Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz
_______________________________________________ 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.
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.
_______________________________________________ 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.

The unbounded-delays package should probably do what you want:
https://hackage.haskell.org/package/unbounded-delays
On 29 Dec 2016 13:29, "Theodore Lief Gannon"
The existence of a workaround doesn't make it not a bug! Definitely report it anyway. Worst case, the bug is actually in Windows but is now known and centrally documented. For that matter, GCH could build the replicateM trick into the implementation on a platform-specific basis.
On Dec 29, 2016 5:21 AM, "Lian Hung Hon"
wrote: Dear Tom,
That is a good workaround, now I'm using divMod with the max value of Int, and things are working again :) So it really is because of int overflow somewhere..
Since a workaround is available I guess I won't file a bug report yet. Thomas' comment also got me second guessing myself..
Thank you everyone for your help and guidance!
Regards, Hon
On 29 Dec 2016 09:47,
wrote: If their supplied code sample is failing, couldn't that indicate a bug in the Windows threadDelay implementation for very large values?
Hon: if you're looking for a short-term solution you can always:
replicateM 48 $ threadDelay $ (half an hour)
This way you only have to wait half an hour to be sure there's no overflow or incorrect timing.
Tom
El 28 dic 2016, a las 18:47, Thomas DuBuisson < thomas.dubuisson@gmail.com> escribió:
Not to be infuriating, but I think you should check and re-check your tooling is not using 32 bit values at any particular point.
Notice:
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is your observation. Any time you depend on `Int` to represent numbers near or greater than 2^28, or perhaps 2^31 in practice, you should think hard about bounds and implications regarding portability anyway.
-Thomas
On Wed, Dec 28, 2016 at 4:05 PM, Lian Hung Hon < hon.lianhung@gmail.com> wrote: Dear Tom/Yitz,
Just tested, returns False. I'm on 64 bit by the way. What should I do from here?
Regards, Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
wrote: Tom wrote: > (86400000000 :: Integer) > (fromIntegral (maxBound :: Int)) > > If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz
_______________________________________________ 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.
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.
_______________________________________________ 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.
_______________________________________________ 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.

Hmm, I'm very confused that the Int maxBound wasn't smaller than the Integer, but that divMod with maxBound is working for you... Either way, I'd be happy to get rid of the Int-valued timeout and threadDelay. Tom
El 29 dic 2016, a las 07:19, Lian Hung Hon
escribió: Dear Tom,
That is a good workaround, now I'm using divMod with the max value of Int, and things are working again :) So it really is because of int overflow somewhere..
Since a workaround is available I guess I won't file a bug report yet. Thomas' comment also got me second guessing myself..
Thank you everyone for your help and guidance!
Regards, Hon
On 29 Dec 2016 09:47,
wrote: If their supplied code sample is failing, couldn't that indicate a bug in the Windows threadDelay implementation for very large values? Hon: if you're looking for a short-term solution you can always:
replicateM 48 $ threadDelay $ (half an hour)
This way you only have to wait half an hour to be sure there's no overflow or incorrect timing.
Tom
El 28 dic 2016, a las 18:47, Thomas DuBuisson
escribió: Not to be infuriating, but I think you should check and re-check your tooling is not using 32 bit values at any particular point.
Notice:
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is your observation. Any time you depend on `Int` to represent numbers near or greater than 2^28, or perhaps 2^31 in practice, you should think hard about bounds and implications regarding portability anyway.
-Thomas
On Wed, Dec 28, 2016 at 4:05 PM, Lian Hung Hon
wrote: Dear Tom/Yitz, Just tested, returns False. I'm on 64 bit by the way. What should I do from here?
Regards, Hon
On 29 Dec 2016 03:47, "Yitzchak Gale"
wrote: Tom wrote:
(86400000000 :: Integer) > (fromIntegral (maxBound :: Int))
If True, your machine (32-bit?) is probably overflowing the Int
Good point. Even if False on Lian's Windows machine, it could be there is some 32-bit value somewhere in the Windows implementation that causes this.
Yitz
_______________________________________________ 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.
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.

Thomas DuBuisson wrote:
Not to be infuriating, but I think you should check and re-check your tooling is not using 32 bit values at any particular point.
Eg, 32 bit ghc can run on 64 bit Windows.
(fromIntegral (86400000000 `mod` 2^32)) / 10^6 ~ 500 seconds which is your observation. Any time you depend on `Int` to represent numbers near or greater than 2^28, or perhaps 2^31 in practice, you should think hard about bounds and implications regarding portability anyway.
It's easy to write something like threadDelay (24*60*60*msPerSec) and not realize that's overflowed. The numbers involved seem small. And when if you're developing on 64 bit, it's easy to ship code with that bug and not realize until someone tries it on 32 bit. Since Haskell time types generally avoid problems with overflow (eg DiffTime isn't bounded), one can become complacent that this is another class of problems that the good data types in Haskell prevent, and stop worrying about time overflows, and then get bitten by this. It would perhaps be good for the documentation for threadDelay to point out that it can delay for a maximum of 71 minutes on 32 bit systems, and point to the unbounded-delays package. -- see shy jo

2016-12-29 17:27 GMT+01:00 Joey Hess
[...] It would perhaps be good for the documentation for threadDelay to point out that it can delay for a maximum of 71 minutes on 32 bit systems, and point to the unbounded-delays package.
... or even better: Absorb the functions from unbounded-delays into base. In their current state, I would consider both threadDelay and timeout API bugs, see http://www.aristeia.com/Papers/IEEE_Software_JulAug_2004_revised.htm (*"**Make interfaces easy to use correctly and hard to use incorrectly."). *Perhaps we should add: genericThreadDelay :: Integral https://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#t:Integra... i => i -> IO https://hackage.haskell.org/package/base-4.7.0.1/docs/System-IO.html#t:IO () genericTimeout :: Integral https://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#t:Integra... i => i -> IO https://hackage.haskell.org/package/base-4.7.0.1/docs/System-IO.html#t:IO a -> IO https://hackage.haskell.org/package/base-4.7.0.1/docs/System-IO.html#t:IO (Maybe https://hackage.haskell.org/package/base-4.7.0.1/docs/Data-Maybe.html#t:Mayb... a) to their respective modules, following Data.List's example. The *real* fix IMHO would be having the equivalent of C++'s <chrono> facilities in base, so we could use a duration data type here.

On 2016-12-29 19:54, Sven Panne wrote:
2016-12-29 17:27 GMT+01:00 Joey Hess
mailto:id@joeyh.name>: [...] It would perhaps be good for the documentation for threadDelay to point out that it can delay for a maximum of 71 minutes on 32 bit systems, and point to the unbounded-delays package.
.... or even better: Absorb the functions from unbounded-delays into base. In their current state, I would consider both threadDelay and timeout API bugs, see http://www.aristeia.com/Papers/IEEE_Software_JulAug_2004_revised.htm (/"//Make interfaces easy to use correctly and hard to use incorrectly."). /Perhaps we should add:
+1. Another, perhaps better, alternative would be to have something like a "TimeDiff" type in base, but an actual *duration* in *physical* time (no leap seconds, no calendar nonsense, etc.). This is one of those big mistakes almost everyone made in the past[1]. *Physical* time is so much different from *calendar* time that it really needs completely different representations and operations. (Of course there must be *some* way to 'convert', but those conversions are inherently dangerous and should be clearly marked as such.)
genericThreadDelay :: Integral i => i -> IO ()
I would be much happier with a signature of threadDelay :: Duration -> IO () with a few safe constructors for Duration, e.g. "daysToDuration :: Int -> Duration" and "millisToDuration :: ..." (etc.). We might arguably want "Maybe Duration" as the return type, but that may be pushing it. *THAT* is how you make this particular API hard to misuse. I don't know about you, but I always end up counting zeroes multiple times when writing a "threadDelay ..." line. Regards, [1] Bascially before JodaTime made ordinary developers aware of just how complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.

Am 29.12.2016 um 22:41 schrieb Bardur Arantsson:
(Of course there must be *some* way to 'convert', but those conversions are inherently dangerous and should be clearly marked as such.)
Actually you don't convert, but you can add physical time to a calendar date. It's not really dangerous, just complicated - leap years which follow a rule, leap seconds that you have to look up in a table. You don't do historic calendars; it's even dubious that you need Islamic or other calendars unless you do either religious or historic dates, in which case domain-specific code would probably be appropriate. Leap seconds are "unsafe" in the IO sense: they occur at irregular times and are not predictable, so this addition is not referentially transparent. I can't think of a use case for this kind of addition in application code though: Either you do calendar calculations, and then you add calendar seconds to a date, with the usual 24:60:60 factors for days/hours/minutes/seconds. Or you do timing-related code: timers that go off, benchmarks, and in both cases you start with a timestamp and add physical seconds, which is trivial. (In system code, the NTP stack or some local driver needs to keep track how physical time relates to calendar time, but that's nothing you'd need or want in a standard library.) tl;dr: physical time and calendar time are different concepts, have different uses, and the use cases for mixing the two are so rare that conversion code shouldn't go into any kind of standard library. IMHO.
[1] Bascially before JodaTime made ordinary developers aware of just how complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.
Yeah, that's a really awesome library, and well worth looking at if you want fresh time API ideas. Regards, Jo

On 2016-12-29 23:27, Joachim Durchholz wrote:
Am 29.12.2016 um 22:41 schrieb Bardur Arantsson:
(Of course there must be *some* way to 'convert', but those conversions are inherently dangerous and should be clearly marked as such.)
Actually you don't convert, but you can add physical time to a calendar date. It's not really dangerous, just complicated - leap years which follow a rule, leap seconds that you have to look up in a table.
True, but... it's *complicated*... which was my point. Add in the fact that the entries in that table may not even *exist* yet, depending on the duration! If you're programming with a Duration and you're counting on a machine to get leap seconds right -- you're doing something wrong.
You don't do historic calendars; it's even dubious that you need Islamic or other calendars unless you do either religious or historic dates, in which case domain-specific code would probably be appropriate.
My favorite observation is that there's actually a February 30th[1]... which anyone who *really* wants to be correct about calendar behavior has to observe. [1] https://en.wikipedia.org/wiki/February_30
Leap seconds are "unsafe" in the IO sense: they occur at irregular times and are not predictable, so this addition is not referentially transparent. I can't think of a use case for this kind of addition in application code though: Either you do calendar calculations, and then you add calendar seconds to a date, with the usual 24:60:60 factors for days/hours/minutes/seconds. Or you do timing-related code: timers that go off, benchmarks, and in both cases you start with a timestamp and add physical seconds, which is trivial.
Exacly, so I don't think *physical* time (like a Duration) should even attempt this. Beause the leap second is entirely artifical, invented to keep the *calendar* ("Earth" time) in sync with *physical* time.
(In system code, the NTP stack or some local driver needs to keep track how physical time relates to calendar time, but that's nothing you'd need or want in a standard library.)
We agree again!
tl;dr: physical time and calendar time are different concepts, have different uses, and the use cases for mixing the two are so rare that conversion code shouldn't go into any kind of standard library. IMHO.
[1] Bascially before JodaTime made ordinary developers aware of just how complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.
Yeah, that's a really awesome library, and well worth looking at if you want fresh time API ideas.
Actually, the Java 8 standard "time" library is -- in many ways -- even better, it's been simplified to account for the fact that 99% of people don't actually need to account for e.g. Julian (or $OTHER) chronologies. If you need that kind of functionality, you're already out in the weeds and you probably need to implement your own library *anyway*. (I'd argue that the 30th of July in Sweden falls into the same category, simply because going back to the 1700s is mostly *academic* to most people. I dunno. I know that it would take me a long time to flick through my Google Calendar to get back that far.) Regards,

Am 30.12.2016 um 01:14 schrieb Bardur Arantsson:
Beause the leap second is entirely artifical, invented to keep the *calendar* ("Earth" time) in sync with *physical* time.
Serving a practical purpose isn't "artificial" in my book.
[1] Bascially before JodaTime made ordinary developers aware of just how complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.
Yeah, that's a really awesome library, and well worth looking at if you want fresh time API ideas.
Actually, the Java 8 standard "time" library is -- in many ways -- even better, it's been simplified to account for the fact that 99% of people don't actually need to account for e.g. Julian (or $OTHER) chronologies. If you need that kind of functionality, you're already out in the weeds and you probably need to implement your own library *anyway*.
I haven't looked at Java 8 date/time yet, I hear it's heavily influenced by Jodatime so it's pretty likely that you can draw the same ideas from that. I'd still start with Jodatime, just to have a better chance of interoperability with needs for alternate calendar systems. Mostly to glean a list of potentially useful data types, and which data fields are relevant to each.

On 2016-12-30 11:09, Joachim Durchholz wrote:
Am 30.12.2016 um 01:14 schrieb Bardur Arantsson:
Beause the leap second is entirely artifical, invented to keep the *calendar* ("Earth" time) in sync with *physical* time.
Serving a practical purpose isn't "artificial" in my book.
I'm emphatically *not* saying that there's no such thing as "calendar time". I'm saying we need *separation* between "calendar" and "physical" time. (Which I thin we agree on?)
I haven't looked at Java 8 date/time yet, I hear it's heavily influenced by Jodatime so it's pretty likely that you can draw the same ideas from that.
Same principal developer :).
I'd still start with Jodatime, just to have a better chance of interoperability with needs for alternate calendar systems. Mostly to glean a list of potentially useful data types, and which data fields are relevant to each.
The developer of both Joda and the jdk8 time.* system decided against, so there's that. (And I think it's pretty much undisputed that he *is* an expert and can actually make these trade-offs.) Regards,

On 29 December 2016 at 22:27, Joachim Durchholz
Actually you don't convert, but you can add physical time to a calendar date. It's not really dangerous, just complicated - leap years which follow a rule, leap seconds that you have to look up in a table.
Hmm, I dunno, "complicated" implies it's at least possible to define a function which correctly add physical times to calendar times, which isn't true - you can't reliably calculate the calendar time exactly 400*86400 seconds from now because the result depends on whether there's a leap second or not and they're not announced that far ahead of time. I really think "dangerous" is a better word, although the word "unsafe" might be more Haskellish. I can't think of a use case for this kind of addition in application code
though: Either you do calendar calculations, and then you add calendar seconds to a date, with the usual 24:60:60 factors for days/hours/minutes/seconds. Or you do timing-related code: timers that go off, benchmarks, and in both cases you start with a timestamp and add physical seconds, which is trivial. (In system code, the NTP stack or some local driver needs to keep track how physical time relates to calendar time, but that's nothing you'd need or want in a standard library.)
tl;dr: physical time and calendar time are different concepts, have different uses, and the use cases for mixing the two are so rare that conversion code shouldn't go into any kind of standard library. IMHO.
+1 to this. Note that the distinction goes all the way down to the OS - see the CLOCK_REALTIME and CLOCK_MONOTONIC options to https://linux.die.net/man/3/clock_gettime for instance, and there is similar functionality within Windows. Doing any kind of timing-based things with CLOCK_REALTIME (and derivatives) is kinda flawed because it can run slow and/or jump backwards if NTP is fiddling with it. CLOCK_MONOTONIC is the right thing to use for that. OTOH sometimes I want to say "sleep for 50 seconds" and sometimes I want to say "sleep until the current (calendar) time is X". As the delay API doesn't currently support both of these, you have to do the unsafe conversion between calendar times and durations to do both kinds of sleep. Fortunately it's rare to care about waking up at a particular second 6 months into the future so this mostly works just fine. Some of these thoughts are implemented here: https://hackage.haskell.org/package/alarmclock Cheers, David
[1] Bascially before JodaTime made ordinary developers aware of just how
complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.
Yeah, that's a really awesome library, and well worth looking at if you want fresh time API ideas.
Regards, Jo
_______________________________________________ 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.

Bardur Arantsson wrote:
[1] Bascially before JodaTime made ordinary developers aware of just how complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.
By "ordinary developers", you mean non-Haskell developers? Because the standard Haskell time library used Haskell's rich type system to model the semantics of time correctly long before JodaTime existed. Some people like JodaTime, but I would be very hesitant to use it until I see a proof that it at least comes close to the Haskell time library, and I am skeptical. I have heard that the Smalltalk time library got the semantics of time right long before even the Haskell time library, but I have not seen it myself in detail. -Yitz

On 2017-01-01 10:42, Yitzchak Gale wrote:
Bardur Arantsson wrote:
[1] Bascially before JodaTime made ordinary developers aware of just how complex this Time/Date stuff really is and the importance of clearly separating the concept of "calendar" time vs. "physical" time.
By "ordinary developers", you mean non-Haskell developers? Because the standard Haskell time library used Haskell's rich type system to model the semantics of time correctly long before JodaTime existed.
(Citation needed.) E.g. is there any representation of a duration of physical time in the Haskell library?
Some people like JodaTime, but I would be very hesitant to use it until I see a proof that it at least comes close to the Haskell time library, and I am skeptical.
What problems do you see -- or are you just assuming? (I mean there *are* a few problems with Joda-time, most of which have been solved in java.time.* in JDK8.) Regards,

On 1/01/17 10:42 PM, Yitzchak Gale wrote:
I have heard that the Smalltalk time library got the semantics of time right long before even the Haskell time library, but I have not seen it myself in detail.
What do you mean by "the" Smalltalk library? The classic Smalltalk-80 library included Date and Time classes for calendar calculations and a Delay class for suspending. The Date and Time classes were not sophisticated. The ANSI Smalltalk standard includes a unified DateAndTime class and a Duration class. When I tried to implement the standard class I found it impossible, because the standard requires both that DateAndTime be in UTC and that arithmetic work for an unspecified range of timepoints, apparently requiring you to predict leap seconds indefinitely far into the future. Despite requiring UTC, it does not let you specify second=60 when creating a timestamp. You can specify the *offset* of local time from UTC, but implementations are allowed to impose a limit or -12 hours to +12 hours, which excludes part of my country. Worse, you specify an *offset*, not a *zone*, yet an implementation is required to intuit, possibly by some form of clairvoyance, the *zone* name relative to a time. Since offsets do not uniquely determine zones, this is of course impossible. Frankly, it's a mess that looks like it was designed by someone who thought they were expert but weren't. Of course actual Smalltalk implementations don't pay all that much attention to the standard. Possibly "the" Smalltalk library is the Chrono package, in which case ignore my rant about the standard.

Sven Panne wrote:
... or even better: Absorb the functions from unbounded-delays into base. In their current state, I would consider both threadDelay and timeout API bugs,
genericThreadDelay :: Integral i => i -> IO ()
There will be a speed difference between the current threadDelay and genericThreadDelay. If threadDelay is being used for a very small delay, such a speed difference could matter. That's the only reason I can see to keep the current threadDelay. I don't know if supporting Integral buys anything over supporting only Integer and Int. Seems like more opportunities for the user to use a type that overflows. -- see shy jo

On December 28, 2016 9:20:50 AM EST, Lian Hung Hon
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.
I believe I fixed this bug a few weeks ago. Indeed there was an integer overflow in then non-threaded Windows RTS. This should be fixed in GHC 8.2. See Trac #7325. Cheers, - Ben
participants (12)
-
amindfv@gmail.com
-
Bardur Arantsson
-
Ben Gamari
-
David Turner
-
Joachim Durchholz
-
Joey Hess
-
Lian Hung Hon
-
Richard A. O'Keefe
-
Sven Panne
-
Theodore Lief Gannon
-
Thomas DuBuisson
-
Yitzchak Gale