View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker and Willem Robert van Hage
    4    E-mail:        wielemak@science.uva.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2006-2014, University of Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(date,
   36          [ date_time_value/3,          % ?Field, ?DaTime, ?Value
   37            parse_time/2,               % +Date, -Stamp
   38            parse_time/3,               % +Date, ?Format, -Stamp
   39            day_of_the_week/2,          % +Date, -DayOfTheWeek
   40            day_of_the_year/2           % +Date, -DayOfTheYear
   41          ]).   42
   43/** <module> Process dates and times
   44*/
   45
   46%!  date_time_value(?Field:atom, +Struct:datime, -Value) is nondet.
   47%
   48%   Extract values from a date-time structure.  Provided fields are
   49%
   50%           | year | integer | |
   51%           | month | 1..12 | |
   52%           | day | 1..31 | |
   53%           | hour | 0..23 | |
   54%           | minute | 0..59 | |
   55%           | second | 0.0..60.0 | |
   56%           | utc_offset | integer | Offset to UTC in seconds (positive is west) |
   57%           | daylight_saving | bool | Name of timezone; fails if unknown |
   58%           | date | date(Y,M,D) | |
   59%           | time | time(H,M,S) | |
   60
   61date_time_value(year,            date(Y,_,_,_,_,_,_,_,_), Y).
   62date_time_value(month,           date(_,M,_,_,_,_,_,_,_), M).
   63date_time_value(day,             date(_,_,D,_,_,_,_,_,_), D).
   64date_time_value(hour,            date(_,_,_,H,_,_,_,_,_), H).
   65date_time_value(minute,          date(_,_,_,_,M,_,_,_,_), M).
   66date_time_value(second,          date(_,_,_,_,_,S,_,_,_), S).
   67date_time_value(utc_offset,      date(_,_,_,_,_,_,O,_,_), O).
   68date_time_value(time_zone,       date(_,_,_,_,_,_,_,Z,_), Z) :- Z \== (-).
   69date_time_value(daylight_saving, date(_,_,_,_,_,_,_,_,D), D) :- D \== (-).
   70
   71date_time_value(date,            date(Y,M,D,_,_,_,_,_,_), date(Y,M,D)).
   72date_time_value(time,            date(_,_,_,H,M,S,_,_,_), time(H,M,S)).
   73
   74%!  parse_time(+Text, -Stamp) is semidet.
   75%!  parse_time(+Text, ?Format, -Stamp) is semidet.
   76%
   77%   Stamp is a  timestamp  created  from   parsing  Text  using  the
   78%   representation Format. Currently supported formats are:
   79%
   80%       * rfc_1123
   81%       Used for the HTTP protocol to represent time-stamps
   82%       * iso_8601
   83%       Commonly used in XML documents.
   84
   85parse_time(Text, Stamp) :-
   86    parse_time(Text, _Format, Stamp).
   87
   88parse_time(Text, Format, Stamp) :-
   89    atom_codes(Text, Codes),
   90    phrase(date(Format, Y,Mon,D,H,Min,S,UTCOffset), Codes),
   91    !,
   92    date_time_stamp(date(Y,Mon,D,H,Min,S,UTCOffset,-,-), Stamp).
   93
   94date(iso_8601, Yr, Mon, D, H, Min, S, 0) --> % BC
   95    "-", date(iso_8601, Y, Mon, D, H, Min, S, 0),
   96    { Yr is -1 * Y }.
   97date(iso_8601, Y, Mon, D, H, Min, S, 0) -->
   98    year(Y),
   99    iso_8601_rest(Y, Mon, D, H, Min, S).
  100date(rfc_1123, Y, Mon, D, Hr, Min, Sec, 0) --> % RFC 1123: "Fri, 08 Dec 2006 15:29:44 GMT"
  101    day_name(_), ", ", ws,
  102    day_of_the_month(D), ws,
  103    month_name(Mon), ws,
  104    year(Y), ws,
  105    hour(H), ":", minute(M), ":", second(S), ws,
  106    timezone(DH, DM, DS),
  107    { Hr is H + DH, Min is M + DM, Sec is S + DS }.
  108
  109
  110%!  iso_8601_rest(+Year:int, -Mon, -Day, -H, -M, -S)
  111%
  112%   Process ISO 8601 time-values after parsing the 4-digit year.
  113
  114iso_8601_rest(_, Mon, D, H, Min, S) -->
  115    "-", month(Mon), "-", day(D),
  116    opt_time(H, Min, S).
  117iso_8601_rest(_, Mon, 0, 0, 0, 0) -->
  118    "-", month(Mon).
  119iso_8601_rest(_, Mon, D, H, Min, S) -->
  120    month(Mon), day(D),
  121    opt_time(H, Min, S).
  122iso_8601_rest(_, 1, D, H, Min, S) -->
  123    "-", ordinal(D),
  124    opt_time(H, Min, S).
  125iso_8601_rest(Yr, 1, D, H, Min, S) -->
  126    "-W", week(W), "-", day_of_the_week(DW),
  127    opt_time(H, Min, S),
  128    { week_ordinal(Yr, W, DW, D) }.
  129iso_8601_rest(Yr, 1, D, H, Min, S) -->
  130    "W", week(W), day_of_the_week(DW),
  131    opt_time(H, Min, S),
  132    { week_ordinal(Yr, W, DW, D) }.
  133iso_8601_rest(Yr, 1, D, 0, 0, 0) -->
  134    "W", week(W),
  135    { week_ordinal(Yr, W, 1, D) }.
  136
  137opt_time(Hr, Min, Sec) -->
  138    ("T";" "), !, iso_time(Hr, Min, Sec).
  139opt_time(0, 0, 0) --> "".
  140
  141
  142% TIMEX2 ISO: "2006-12-08T15:29:44 UTC" or "20061208T"
  143iso_time(Hr, Min, Sec) -->
  144    hour(H), ":", minute(M), ":", second(S),
  145    timezone(DH, DM, DS),
  146    { Hr is H + DH, Min is M + DM, Sec is S + DS }.
  147iso_time(Hr, Min, Sec) -->
  148    hour(H), ":", minute(M),
  149    timezone(DH, DM, DS),
  150    { Hr is H + DH, Min is M + DM, Sec is DS }.
  151iso_time(Hr, Min, Sec) -->
  152    hour(H), minute(M), second(S),
  153    timezone(DH, DM, DS),
  154    { Hr is H + DH, Min is M + DM, Sec is S + DS }.
  155iso_time(Hr, Min, Sec) -->
  156    hour(H), minute(M),
  157    timezone(DH, DM, DS),
  158    { Hr is H + DH, Min is M + DM, Sec is DS }.
  159iso_time(Hr, Min, Sec) -->
  160    hour(H),
  161    timezone(DH, DM, DS),
  162    { Hr is H + DH, Min is DM, Sec is DS }.
  163
  164% FIXME: deal with leap seconds
  165timezone(Hr, Min, 0) -->
  166    "+", hour(H), ":", minute(M), { Hr is -1 * H, Min is -1 * M }.
  167timezone(Hr, Min, 0) -->
  168    "+", hour(H), minute(M), { Hr is -1 * H, Min is -1 * M }.
  169timezone(Hr, 0, 0) -->
  170    "+", hour(H), { Hr is -1 * H }.
  171timezone(Hr, Min, 0) -->
  172    "-", hour(H), ":", minute(M), { Hr is H, Min is M }.
  173timezone(Hr, Min, 0) -->
  174    "-", hour(H), minute(M), { Hr is H, Min is M }.
  175timezone(Hr, 0, 0) -->
  176    "-", hour(H), { Hr is H }.
  177timezone(0, 0, 0) -->
  178    "Z".
  179timezone(0, 0, 0) -->
  180    ws, "UTC".
  181timezone(0, 0, 0) -->
  182    ws, "GMT". % remove this?
  183timezone(0, 0, 0) -->
  184    [].
  185
  186day_name(0) --> "Sun".
  187day_name(1) --> "Mon".
  188day_name(2) --> "Tue".
  189day_name(3) --> "Wed".
  190day_name(4) --> "Thu".
  191day_name(5) --> "Fri".
  192day_name(6) --> "Sat".
  193day_name(7) --> "Sun".
  194
  195month_name(1) --> "Jan".
  196month_name(2) --> "Feb".
  197month_name(3) --> "Mar".
  198month_name(4) --> "Apr".
  199month_name(5) --> "May".
  200month_name(6) --> "Jun".
  201month_name(7) --> "Jul".
  202month_name(8) --> "Aug".
  203month_name(9) --> "Sep".
  204month_name(10) --> "Oct".
  205month_name(11) --> "Nov".
  206month_name(12) --> "Dec".
  207
  208day_of_the_month(N) --> int2digit(N), { between(1, 31, N) }.
  209day_of_the_week(N)  --> digit(N),     { between(1,  7, N) }.
  210month(M)            --> int2digit(M), { between(1, 12, M) }.
  211week(W)             --> int2digit(W), { between(1, 53, W) }.
  212day(D)              --> int2digit(D), { between(1, 31, D) }.
  213hour(N)             --> int2digit(N), { between(0, 23, N) }.
  214minute(N)           --> int2digit(N), { between(0, 59, N) }.
  215second(S)           --> int2digit(N), { between(0, 60, N) }, % leap second
  216    opt_fraction(N, S).
  217
  218opt_fraction(I, F) -->
  219    ( "." ; "," ),
  220    !,
  221    digits(D),
  222    { length(D, N),
  223      N > 0,
  224      number_codes(FP, D),
  225      F is I + FP/(10^N)
  226    }.
  227opt_fraction(I, I) -->
  228    [].
  229
  230int2digit(N) -->
  231    digit(D0),
  232    digit(D1),
  233    { N is D0*10+D1 }.
  234
  235year(Y) -->
  236    digit(D0),
  237    digit(D1),
  238    digit(D2),
  239    digit(D3),
  240    { Y is D0*1000+D1*100+D2*10+D3 }.
  241
  242ordinal(N) --> % Nth day of the year, jan 1 = 1, dec 31 = 365 or 366
  243    digit(D0),
  244    digit(D1),
  245    digit(D2),
  246    { N is D0*100+D1*10+D2, between(1, 366, N) }.
  247
  248digit(D) -->
  249    [C],
  250    { code_type(C, digit(D)) }.
  251
  252digits([C|T]) -->
  253    [C],
  254    { code_type(C, digit) },
  255    !,
  256    digits(T).
  257digits([]) --> [].
  258
  259ws -->
  260    " ",
  261    !,
  262    ws.
  263ws -->
  264    [].
  265
  266%!  day_of_the_week(+Date, -DayOfTheWeek) is det.
  267%
  268%   Computes the day of the week for a  given date. Days of the week
  269%   are numbered from one to seven: monday   =  1, tuesday = 2, ...,
  270%   sunday = 7.
  271%
  272%   @param Date is a term of the form date(+Year, +Month, +Day)
  273
  274day_of_the_week(date(Year, Mon, Day), DotW) :-
  275    format_time(atom(A), '%u', date(Year, Mon, Day, 0, 0, 0, 0, -, -)),
  276    atom_number(A, DotW).
  277
  278week_ordinal(Year, Week, Day, Ordinal) :-
  279    format_time(atom(A), '%w', date(Year, 1, 1, 0, 0, 0, 0, -, -)),
  280    atom_number(A, DotW0),
  281    Ordinal is ((Week-1) * 7) - DotW0 + Day + 1.
  282
  283%!  day_of_the_year(+Date, -DayOfTheYear) is det.
  284%
  285%   Computes the day of the year for a  given date. Days of the year
  286%   are numbered from 1 to 365 (366 for a leap year).
  287%
  288%   @param Date is a term of the form date(+Year, +Month, +Day)
  289
  290day_of_the_year(date(Year, Mon, Day), DotY) :-
  291    format_time(atom(A), '%j', date(Year, Mon, Day, 0, 0, 0, 0, -, -)),
  292    atom_number(A, DotY)