Time Library Date Normalisation and Arithmetic

I'm thinking of something along these lines: Normalisation ------------- class (Eq a,Ord a) => Normalisable a where isNormal :: a -> Bool normaliseTruncate :: a -> a normaliseRollover :: a -> a The normalise functions would work like this: normaliseTruncate 2005/14/32 -> 2005/12/32 -> 2005/12/31 2005/-2/-4 -> 2005/01/-4 -> 2005/01/01 normaliseRollover 2005/14/32 -> 2006/02/32 -> 2006/03/04 2005/-2/-4 -> 2004/10/-4 -> 2004/09/26 (doing both steps in each call) Calendar Arithmetic ------------------- This is one way of providing arithmetic for such things as Gregorian dates: data TimeUnit d = TimeUnit addTimeUnitTruncate :: Integer -> d -> d addTimeUnitRollover :: Integer -> d -> d diffTimeUnitFloor :: d -> d -> Integer days :: (DayEncoding d) => TimeUnit d gregorianMonths :: (DayEncoding d) => TimeUnit d gregorianYears :: (DayEncoding d) => TimeUnit d So for instance, to add three months to a date d, you do this: d' = addTimeUnitTruncate gregorianMonths 3 d This might also be used for minutes and so forth. And you might also be able to do this: multipleTimeUnit :: Integer -> TimeUnit d -> TimeUnit d weeks = multipleTimeUnit 7 days There's an alternative way using classes, for days only: class (Integral u) => TimeUnit u where addTimeUnitTruncate :: (DayEncoding d) => u -> d -> d addTimeUnitRollover :: (DayEncoding d) => u -> d -> d diffTimeUnitFloor :: (DayEncoding d) => d -> d -> u newtype Days = Days Integer instance TimeUnit Days newtype GregorianMonths = GregorianMonths Integer instance TimeUnit GregorianMonths newtype GregorianYears = GregorianYears Integer instance TimeUnit GregorianYears d' = addTimeUnitTruncate (GregorianMonths 3) d My preference is for the former. -- Ashley Yakeley, Seattle WA

Hi Ashley,
I have some ideas about how to make the API simpler and easier to learn.
Please see my comments below.
On 7/9/05, Ashley Yakeley
I'm thinking of something along these lines:
Normalisation -------------
class (Eq a,Ord a) => Normalisable a where isNormal :: a -> Bool normaliseTruncate :: a -> a normaliseRollover :: a -> a
The normalise functions would work like this:
normaliseTruncate 2005/14/32 -> 2005/12/32 -> 2005/12/31 2005/-2/-4 -> 2005/01/-4 -> 2005/01/01
Usually people want normalization to happen automatically when doing date arithmetic and I/O. What is the use case for having a representation for invalid dates? I think it should not even be possible to have a date 2005/12/32 or 2005/01/-4. Why not make GregorianDay, ISOWeek, YearDay abstract, and then provide explicit construction functions that normalize and/or check validity automatically?
Calendar Arithmetic -------------------
This is one way of providing arithmetic for such things as Gregorian dates:
data TimeUnit d = TimeUnit addTimeUnitTruncate :: Integer -> d -> d addTimeUnitRollover :: Integer -> d -> d diffTimeUnitFloor :: d -> d -> Integer
days :: (DayEncoding d) => TimeUnit d
gregorianMonths :: (DayEncoding d) => TimeUnit d gregorianYears :: (DayEncoding d) => TimeUnit d
Fisrly, why provide gregorianMonths and gregorianYears functions that work for all day encodings? I think it is enough to have then defined only for GregorianDay. If I am working with Julian days, I probably don't care about what month it is in. And if I DO care, then I probably also want the year and day too. So, I would just convert the julian day to a gregorian day. Secondly, does date arithmetic really need to be this complicated? I have managed with the following two date arithmetic functions for quite a while:
--| 'addMonthsTruncated x d' adds 'x' months to date 'd'. The resultant date is --| truncated to the last day of the month if necessary. For example, --| addMonthsTruncated 1 (GregorianDay 2001 1 31) results in --| (GregorianDay 2001 2 28). --| (This function does arithmetic identically to the Oracle Add_Months --| function, the Microsoft .NET Calendar.AddMonths method, and the --| Java GregorianCalendar.add method (using Calendar.MONTH) addMonthsTruncated :: Int -> GregorianDay -> GregorianDay
--| 'addDays x d' adds x days to 'd'. --| examples: --| addDays 1 (GregorianDay 2001 1 31) ==> GregorianDay 2001 2 1 --| addDays -1 (GregorianDay 2001 1 1) ==> GregorianDay 2000 12 31 addDays :: Int -> GregorianDay -> GregorianDay
You can define year and week arithmetic in terms of day and month arithmetic:
addYears n = addMonths (12*n) addWeeks n = addDays (7*n)
So for instance, to add three months to a date d, you do this:
d' = addTimeUnitTruncate gregorianMonths 3 d
I think that 'addMonthsTruncated 3' is a lot clearer. Below is an untested interface (and some untested implementations) specific to the Gregorian calendar that codifies some of my suggestions.
module System.Calendar.Gregorian ( Date -- abstract , DateTime -- synonym
--* Constructing a Date , fromYMD , normalizedFromYMD
--* Deconstruction and arithmetic , Gregorian
--* Misc , lastDayOfMonth ) import System.Time(DayEncoding,DayAndTime)
In the Gregorian calendar, a Date is represented by a year, a month, and a day. The Date type given here always holds a valid, normalized date. For example, it is not possible for Date to contain "2005/06/31" because June only has 30 days.
data Date = Date Integer Int Int type DateTime = DayAndTime Date
* Constructing a Date There are 12 months, 1=January...12=December. Each month has a variable number of days, starting with 1. Dates with positive years are A.D., and dates with negative years are B.C. TODO: what about year 0? | Returns Nothing if the year, month, and day of month given do not | represent a valid date. The following law holds: | fromJust (fromYMD (ymd d)) == d | Examples: | isJust (fromYMD 1979 12 9) == True | isJust (fromYMD -1 1 1) == True -- 1 BC | isJust (fromYMD 2004 2 29) == True -- leap year | isNothing (fromYMD 1979 2 29) == True -- not a leap year | isNothing (fromYMD 0 1 1) == True -- TODO: year 0? | isNothing (fromYMD 1900 13 2) == True -- no 13th month | isNothing (fromYMD 1900 0 5) == True -- Months start at 1
fromYMD :: Integer -> Int -> Int -> Maybe Date fromYMD _ _ _ = undefined -- TODO:
| Like fromYMD, but the given year, month, and day are | normalized to become a valid date. This function is | equivalent to (fromJust . fromYMD) when the given year, month, | and day are already valid. | | Examples: | normalizedFromYMD 1979 12 9 = fromJust (fromYMD 1979 12 9) | normalizedFromYMD -1 1 1 = fromJust (fromYMD -1 1 1) | normalizedFromYMD 2004 2 29 = fromJust (fromYMD 2004 2 29) | normalizedFromYMD 0 1 1 = TODO: ???? | normalizedFromYMD 1979 2 29 = fromJust (fromYMD 1979 3 1) | normalizedFromYMD 1900 13 2 = fromJust (fromYMD 1901 1 2) | normalizedFromYMD 1900 0 5 = fromJust (fromYMD 1899 12 5) | normalizedFromYMD 1 1 -1 = fromJust (fromYMD -1 13 31)
normalizedFromYMD :: Integer -> Int -> Int -> Date normalizedFromYMD y m d -- TODO: I didn't test this code. In particular, I don't know -- how it works for the B.C./A.D. line | y == 0 = TODO: | otherwise = let withYear = Date y 1 1 withMonth = addMonths m withYear withDay = addDays d withMonth in withDay
Deconstruction and arithmetic on Gregorian dates are defined for Date, DateTime, and Zoned DateTime. Examples:
class Gregorian d where
| 'addMonthsTruncated x d' adds 'x' months to date 'd'. | The resultant date is truncated to the last day of the month | if necessary. | | Examples: | | (ymd $ addMonthsTruncated 1 (fromYMD 2001 1 31)) == (2001,2,28) | | This function does arithmetic identically to the Oracle Add_Months | function, the Microsoft .NET Calendar.AddMonths method, and the | Java GregorianCalendar.add method (using Calendar.MONTH).
addMonthsTruncated :: Integer -> d -> d
| 'addDays x d' adds x days to 'd'. | | Examples: | (ymd $ addDays 1 (fromYMD 2001 1 31)) == (2001, 2, 1) | (ymd $ addDays -1 (fromYMD 2001 1 1)) == (2000,12,31)
addDays :: Integer -> d -> d
| Extracts the (year,month,day) from the date. | | Examples: | getMonth d = m where (_,m,_) = ymd d | getEra d = if y >= 1 then "AD" else "BC" where (y,_,_) = ymd d | isNewYearsDay = (m,d) == (1,1) where (_,m,d) = ymd d
ymd :; d -> (Integer,Int,Int)
instance Gregorian Date where addMonthsTruncated _ _ = undefined -- TODO: addDays _ _ = undefined -- TODO: ymd (Date y m d) = (y,m,d)
instance (Gregorian d) => Gregorian (DayAndTime d) where addMonthsTruncated n (DayAndTime d t) = DayAndTime (addMonthsTruncated d) t addDays n (DayAndTime d t) = DayAndTime (addDays d) t ymd (DayAndTime d _) = ymd d
instance Gregorian (Zoned DateTime) where addMonthsTruncated _ (Zoned _) = undefined -- TODO: DST!!! addDays _ (Zoned _) = undefined -- TODO: DST!!! ymd (Zoned (DayAndTime d _)) = ymd d
| 'lastDayOfMonth d' Finds the last day of the month that d is in. | | Examples: | (ymd $ lastDayOfMonth (fromYMD 2003 2 12)) == (2002, 2,28) | (ymd $ lastDayOfMonth (fromYMD 2004 2 12)) == (2004, 2,29) | (ymd $ lastDayOfMonth (fromYMD 1999,12, 9)) == (1999,12,31)
lastDayOfMonth :: Date -> Date lastDayOfMonth (Date _ _ _) = undefined -- TODO:
Gregorian dates can be converted to and from Julian Dates.
instance DayEncoding Date where TODO:... ... ...

In article
Usually people want normalization to happen automatically when doing date arithmetic and I/O. What is the use case for having a representation for invalid dates? I think it should not even be possible to have a date 2005/12/32 or 2005/01/-4. Why not make GregorianDay, ISOWeek, YearDay abstract, and then provide explicit construction functions that normalize and/or check validity automatically?
A normalising construction function is a good idea. But if we hide the GregorianDay constructor, two of your use cases become slightly harder: "How do I truncate a date to the first of the month?" "How do I truncate a date to the first day of the year it occurred in?" Also bear in mind that all the instances of DayEncoding are isomorphic (considering only normalised values). So if GregorianDay is abstract, we might as well use ModJulianDay or somesuch (but a newtype rather than a synonym of Integer): newtype Day = ModJulianDay Integer gregorianYear :: Day -> Integer gregorianMonth :: Day -> Int gregorianDay :: Day -> Int gregorianDayOfYear :: Day -> Int gregorian :: Day -> (Integer,Int,Int) showGregorian :: Day -> String -- probably 'show' also makeGregorianTruncate :: Integer -> Int -> Int -> Day makeGregorianCheck :: Integer -> Int -> Int -> Maybe Day isoWeekYear :: Day -> Integer isoWeekNumber :: Day -> Int etc. This is actually quite appealing, though it's a rather radical change. The answers to the use-cases above become d' = makeGregorianTruncate (gregorianYear d) (gregorianMonth d) 1 d' = makeGregorianTruncate (gregorianYear d) 1 1 Opinions?
Secondly, does date arithmetic really need to be this complicated? I have managed with the following two date arithmetic functions for quite a while:
addMonthsTruncated :: Int -> GregorianDay -> GregorianDay
addDays :: Int -> GregorianDay -> GregorianDay
d' = addTimeUnitTruncate gregorianMonths 3 d
I think that 'addMonthsTruncated 3' is a lot clearer.
Mine is just one symbol longer: addMonthsTruncated = addTimeUnitTruncate gregorianMonths I want to reduce the number of exposed symbols. The time-units to deal with are: days & weeks Gregorian months & years ISO numbered-week years (units of other calendars) For each we want to: add with truncation add with rolling over find the number in difference between two dates Is it better to have simple functions for each combination (your scheme) or selector functions (my original scheme)? I don't know. Perhaps I could shorten the name to "addTruncate" or somesuch.
module System.Calendar.Gregorian ( Date -- abstract , DateTime -- synonym
--* Constructing a Date , fromYMD , normalizedFromYMD
--* Deconstruction and arithmetic , Gregorian
--* Misc , lastDayOfMonth ) import System.Time(DayEncoding,DayAndTime)
I like fromYMD, normalizedFromYMD, and lastDayOfMonth, though we might also consider this: gregorianMonthLength :: Integer -> Int -> Int
Dates with positive years are A.D., and dates with negative years are B.C. TODO: what about year 0?
ISO 8601 has year 0 for 1 BCE, year -1 for 2 BCE, and so on, so we can just stick to that. The extension of the Gregorian calendar to before its adoption is known as the "Proleptic Gregorian calendar".
Deconstruction and arithmetic on Gregorian dates are defined for Date, DateTime, and Zoned DateTime. Examples:
class Gregorian d
I'm not so sure about this one. It introduces a new class that means "contains a GregorianDay". I think doing the transformation in constructors in simpler. I would prefer this: addDays :: (DayEncoding d) => Integer -> d -> d diffDays :: (DayEncoding d) => d -> d -> Integer addGregorianMonthsTruncate :: Integer -> GregorianDay -> GregorianDay addGregorianMonthsRollover :: Integer -> GregorianDay -> GregorianDay diffGregorianMonths :: GregorianDay -> GregorianDay -> Integer My current approach to ease of use is to replicate some of this functionality with the CalendarTime type. I also wonder if I shouldn't put the modules in Data.Time instead of System.Time. -- Ashley Yakeley, Seattle WA

On Mon, Jul 11, 2005 at 02:53:25AM -0700, Ashley Yakeley wrote:
A normalising construction function is a good idea. But if we hide the GregorianDay constructor, two of your use cases become slightly harder:
"How do I truncate a date to the first of the month?"
"How do I truncate a date to the first day of the year it occurred in?"
I dislike the "let the user muck with the data structure and expect the library to figure out what he meant" style. For one thing, it means that at some point, there is an intermediate value whose semantics are unclear. (Can you document what will happen if it is passed to all functions?) For another, the reader of the code has to look ahead to see what kind of normalization is eventually done. There are enough ambiguous cases in date handling that I would prefer to be explicit about everything. As a date API user, I think that those use cases become more clear in the style that Brian suggested. d2 = d1 `changeDayOfMonth` 1 d2 = d1 `changeDayOfYear` 1 Now, I've only followed this thread loosely (these examples may be inconsistent with the proposed API, sorry), and I realize that this style has disadvantages: it may be tedious or slow if you have to combine many operations. But I fear the alternative is a mess of difficult-to-document-and-remember normalization rules for invalid dates.
This is actually quite appealing, though it's a rather radical change. The answers to the use-cases above become
d' = makeGregorianTruncate (gregorianYear d) (gregorianMonth d) 1
d' = makeGregorianTruncate (gregorianYear d) 1 1
Opinions?
Nobody's going to like that. :-)
Is it better to have simple functions for each combination (your scheme) or selector functions (my original scheme)?
I tend to like the former, because the ambiguous cases for the different units are different, and can be documented separately. Easier for the programmer to understand what he's asking for. Andrew

Have you read "Calendrical Calculations"?
http://www.cup.cam.ac.uk/catalogue/catalogue.asp?isbn=0521777526
Tony.
--
f.a.n.finch

In article
Have you read "Calendrical Calculations"? http://www.cup.cam.ac.uk/catalogue/catalogue.asp?isbn=0521777526
Yes, I highly recommend it. It discusses the relevant astronomy and background of each calendar and avoids the more common pitfalls in understanding calendars, such as equating the mean tropical year and the vernal equinox year. I have time this coming week (between work contracts) during which I hope to do some more work on TimeLib. There are two big changes I want to make. Speak now if you thing these are bad ideas: 1. Moving modules to Data.Time.* I believe this makes more sense because most of the library is calculation and only functions that obtain the current time and time zone use the system. We also avoid the existing System.Time so there's less confusion. This is not such a big change as far as authoring is concerned. 2. Unifying day types Right now ModJulianDay and the valid subset of GregorianDay (and other instances of DayEncoding) are isomorphic and represent the same thing. This leads to two problems: how to deal with invalid GregorianDays, and confusion arising from redundancy. I was doubtless influenced by C/C++, where a field accessor is "cheaper" in some sense than a function, and so having a separate "broken down" type makes sense. Haskell is different of course. I intend to have a single type to represent days, probably called Day or Date, which will be a newtype of Integer to represent the MJD number. There will be functions to obtain (year,month,day) values as well as construct from that (truncating to correct ranges). This will simplify the type system: the DayEncoding class with its confusingly-named members will be removed, DayAndTime and ZonedTime will no longer need a type parameter, and so on. Anyone wishing to create functionality for some other calendar (Hebrew, for instance), can just create functions without needing a new type. -- Ashley Yakeley, Seattle WA
participants (4)
-
Andrew Pimlott
-
Ashley Yakeley
-
Brian Smith
-
Tony Finch