1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8% 
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License. 
13% 
14% The Original Code is  The ECLiPSe Constraint Logic Programming System. 
15% The Initial Developer of the Original Code is  Cisco Systems, Inc. 
16% Portions created by the Initial Developer are
17% Copyright (C) 1999 - 2006 Cisco Systems, Inc.  All Rights Reserved.
18% 
19% Contributor(s): Joachim Schimpf, IC-Parc
20% 
21% END LICENSE BLOCK
22%
23% $Id: umscalendar.tex,v 1.1 2006/09/23 01:50:40 snovello Exp $
24%
25% Joachim Schimpf, IC-Parc
26%
27
28\section{Calendar Library}
29\label{chapcal}
30This library contains a set of predicates to assist with the handling
31of dates and times.  It is loaded using
32\begin{quote}\begin{verbatim}
33:- use_module(library(calendar)).
34\end{verbatim}\end{quote}
35The library represents time points as {\em Modified Julian Dates} (MJD).
36Julian Dates (JD) and Modified Julian Dates (MJD) are a
37consecutive day numbering scheme widely used in astronomy,
38space travel etc.
39That means that every day has a unique integer number, and consecutive
40days have consecutive numbers.
41Note that you can also use fractional MJDs to denote the time of day.
42Then every time point has a unique floating point representation!
43With this normalised representation, distances between times are
44obviously trivial to compute, and so are weekdays (by simple mod(7)
45operation).
46
47The predicates provided are
48\begin{description}
49\item[date_to_mjd(+D/M/Y, -MJD)] converts a Day/Month/Year structure into
50	its unique integer MJD number.
51\item[mjd_to_date(+MJD, -D/M/Y)] converts an MJD
52	(integer or float) into the corresponding Day/Month/Year.
53\item[time_to_mjd(+H:M:S, -MJD)] returns a float MJD \lt 1.0 encoding the
54	time of day (UTC/GMT). This can be added to an integral day number
55	to obtain a full MJD.
56\item[mjd_to_time(+MJD, -H:M:S)] returns the time of day (UTC/GMT)
57	corresponding to the given MJD as Hour:Minute:Seconds structure,
58	where Hour and Minute are integers and Seconds is a float.
59\item[mjd_to_weekday(+MJD, -DayName)] returns the weekday of the
60	specified MJD as atom monday, tuesday etc.
61\item[mjd_to_dow(+MJD, -DoW)] returns the weekday of the
62	specified MJD as an integer (1 for monday up to 7 for sunday).
63\item[mjd_to_dow(+MJD, +FirstWeekday, -DoW)] as above, but allows to choose
64	a different starting day for weeks, specified as atom monday,
65	tuesday etc.
66\item[mjd_to_dy(+MJD, -DoY/Y), dy_to_mjd(+DoY/Y, -MJD)] convert MJDs
67	to or from a DayOfYear/Year representation, where DayOfYear is
68	the relative day number starting with 1 on every January 1st.
69\item[mjd_to_dwy(+MJD, -DoW/WoY/Y), dwy_to_mjd(+DoW/WoY/Y, -MJD)] convert
70	MJDs to or from a DayOfWeek/WeekOfYear/Year representation, where
71	DayOfWeek is the day number within the week (1 for monday up to
72	7 for sunday), and WeekOfYear is the week number within the year
73	(starting with 1 for the week that contains January 1st).
74\item[mjd_to_dwy(+MJD, +FirstWeekday, -DoW/WoY/Y)]
75\item[dwy_to_mjd(+DoW/WoY/Y, +FirstWeekday, -MJD)]
76	As above, but allows to choose a different starting day for weeks,
77	specified as atom monday, tuesday etc.
78\item[unix_to_mjd(+UnixSec, -MJD)] convert the UNIX time representation
79	into a (float) MJD.
80\item[mjd_now(-MJD)] returns the current date/time as (float) MJD.
81\item[jd_to_mjd(+JD, -MJD), mjd_to_jd(+MJD, -JD)] convert MJDs to or
82	from JDs. The relationship is simply MJD = JD-2400000.5.
83\end{description}
84The library code is valid for dates between
85	 1 Mar 0004 = MJD -677422 = JD 1722578.5
86and
87	22 Jan 3268 = MJD  514693 = JD 2914693.5.
88
89\subsection{Examples}
90What day of the week was the 29th of December 1959?
91\begin{quote}\begin{verbatim}
92[eclipse 1]: lib(calendar).
93[eclipse 2]: date_to_mjd(29/12/1959, MJD), mjd_to_weekday(MJD,W).
94MJD = 36931
95W = tuesday
96\end{verbatim}\end{quote}
97What date and time is it now?
98\begin{quote}\begin{verbatim}
99[eclipse 3]: mjd_now(MJD), mjd_to_date(MJD,Date), mjd_to_time(MJD,Time).
100Date = 19 / 5 / 1999
101MJD = 51317.456238425926
102Time = 10 : 56 : 59.000000017695129
103\end{verbatim}\end{quote}
104How many days are there in the 20th century?
105\begin{quote}\begin{verbatim}
106[eclipse 4]: N is date_to_mjd(1/1/2001) - date_to_mjd(1/1/1901).
107N = 36525
108\end{verbatim}\end{quote}
109The library code does not detect invalid dates,
110but this is easily done by converting a date to its MJD and back
111and checking whether they match:
112\begin{quote}\begin{verbatim}
113[eclipse 5]: [user].
114valid_date(Date) :-
115        date_to_mjd(Date,MJD),
116        mjd_to_date(MJD,Date).
117
118[eclipse 6]: valid_date(29/2/1900).   % 1900 is not a leap year!
119no (more) solution.
120\end{verbatim}\end{quote}
121