diff --git a/library/date.pl b/library/date.pl index accaa2c64a..6d26f720c6 100644 --- a/library/date.pl +++ b/library/date.pl @@ -79,7 +79,7 @@ % representation Format. Currently supported formats are: % % * rfc_1123 -% Used for the HTTP protocol to represent time-stamps, e.g. +% Preferred for the HTTP protocol to represent time-stamps, e.g. % % Fri, 08 Dec 2006 15:29:44 GMT % @@ -87,6 +87,11 @@ % If the time zone is omitted, the time is interpreted as % _local time_. % +% * rfc_1036 +% (Outdated) alternative for HTTP Protocol, e.g. +% +% Sunday, 06-Nov-94 08:49:37 GMT +% % * iso_8601 % Commonly used in XML documents. Actually the XML RFC3339 % is a _profile_ of ISO8601. For example @@ -101,6 +106,14 @@ % To compute the start of a day in local time, use % e.g. ``2006-12-08T00``. % +% * asctime +% ANSI C's asctime() format, e.g. +% +% Sun Nov 6 08:49:37 1994 +% +% This format has no time zone and is interpreted as local +% time. +% % @arg Text is an atom, string or list of character _codes_. % @see xsd_time_string/3 from library(sgml) implements RFC3339 % strictly. @@ -139,8 +152,21 @@ day_of_the_month(D), ws, month_name(Mon), ws, year(Y), ws, - hour(H), ":", minute(M), ":", second(S), ws, + iso_time3(H, M, S), ws, + timezone(UTCOffset). +date(rfc_1036, Y, Mon, D, H, M, S, UTCOffset) --> + full_day_name(_), ", ", ws, % RFC 1036: "Friday, 08-Dec-2006 15:29:44 GMT" + day_of_the_month(D), "-", + month_name(Mon), "-", + year2d(Y), ws, + iso_time3(H, M, S), ws, timezone(UTCOffset). +date(asctime, Y, Mon, D, H, M, S, _UTCOffset) --> + day_name(_), " ", + month_name(Mon), " ", + asctime_day_of_the_month(D), " ", + iso_time3(H, M, S), " ", + year(Y). %! iso_8601_rest(+Year:int, -Mon, -Day, -H, -M, -S, -UTCOffset) % @@ -176,7 +202,7 @@ % TIMEX2 ISO: "2006-12-08T15:29:44 UTC" or "20061208T" iso_time(H, M, S) --> - hour(H), ":", minute(M), ":", second(S). + iso_time3(H, M, S). iso_time(H, M, _) --> hour(H), ":", minute(M). iso_time(H, M, S) --> @@ -186,6 +212,9 @@ iso_time(H, _, _) --> hour(H). +iso_time3(H, M, S) --> + hour(H), ":", minute(M), ":", second(S). + % FIXME: deal with leap seconds timezone(UTCOffset) --> "+", hour(H), ":", minute(M), { UTCOffset is -(H*3600+M*60) }. @@ -217,6 +246,15 @@ day_name(6) --> "Sat". day_name(7) --> "Sun". +full_day_name(0) --> "Sunday". +full_day_name(1) --> "Monday". +full_day_name(2) --> "Tuesday". +full_day_name(3) --> "Wednesday". +full_day_name(4) --> "Thursday". +full_day_name(5) --> "Friday". +full_day_name(6) --> "Saturday". +full_day_name(7) --> "Sunday". + month_name(1) --> "Jan". month_name(2) --> "Feb". month_name(3) --> "Mar". @@ -230,6 +268,11 @@ month_name(11) --> "Nov". month_name(12) --> "Dec". +asctime_day_of_the_month(D) --> + " ", !, digit(D), {D > 0}. +asctime_day_of_the_month(D) --> + day_of_the_month(D). + day_of_the_month(N) --> int2digit(N), { between(1, 31, N) }. day_of_the_week(N) --> digit(N), { between(1, 7, N) }. month(M) --> int2digit(M), { between(1, 12, M) }. @@ -264,6 +307,16 @@ digit(D3), { Y is D0*1000+D1*100+D2*10+D3 }. +year2d(Y) --> + digit(D0), + digit(D1), + { Y0 is D0*10+D1, + ( Y0 >= 70, Y0 =< 99 + -> Y is Y0+1900 + ; Y is Y0+2000 + ) + }. + ordinal(N) --> % Nth day of the year, jan 1 = 1, dec 31 = 365 or 366 digit(D0), digit(D1),