. (utf8) 2:- module( 3 xsd_grammar, 4 [ 5 dayTimeDurationCanonicalMap//1, % +Duration 6 dayTimeDurationMap//1, % -Duration 7 decimalLexicalMap//1, % -Decimal 8 decimalCanonicalMap//1, % +Decimal 9 durationCanonicalMap//1, % +Duration 10 durationMap//1 % -Duration 11 ] 12).
22:- use_module(library(arithmetic)). 23 24:- use_module(library(abnf)). 25:- use_module(library(dcg)). 26:- use_module(library(default)). 27:- use_module(library(list_ext)). 28:- use_module(library(math_ext)). 29 30:- arithmetic_function(xsd_div/2). 31:- arithmetic_function(xsd_mod/2). 32 33:- op(400, yfx, xsd_div). 34:- op(400, yfx, xsd_mod). 35 36% xsd_div(+M, +N, -Z) is det. 37% 38% If `M` and `N` are numbers, then `M div N` is the greatest integer 39% less than or equal to `M / N`. 40 41xsd_div(X, Y, Z):- 42 Z is floor(X rdiv Y).
M mod N
is m-n * (m div n)
.
48xsd_mod(X, Y, Z):-
49 Z is X - Y * (X xsd_div Y).
83dateCanonicalMap(date_time(Y,Mo,D,_,_,_,Off)) -->
84 yearCanonicalFragmentMap(Y),
85 "-",
86 monthCanonicalFragmentMap(Mo),
87 "-",
88 dayCanonicalFragmentMap(D),
89 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
Arguments
120dateLexicalMap(DT) -->
121 yearFragValue(Y),
122 "-",
123 monthFragValue(Mo),
124 "-",
125 dayFragValue(D),
126 ?(timezoneFragValue, Off),
127 {newDateTime(Y, Mo, D, _, _, _, Off, DT)}.
172dateTimeCanonicalMap(date_time(Y,Mo,D,H,Mi,S,Off)) -->
173 yearCanonicalFragmentMap(Y),
174 "-",
175 monthCanonicalFragmentMap(Mo),
176 "-",
177 dayCanonicalFragmentMap(D),
178 "T",
179 hourCanonicalFragmentMap(H),
180 ":",
181 minuteCanonicalFragmentMap(Mi),
182 ":",
183 secondCanonicalFragmentMap(S),
184 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
228dateTimeLexicalMap(DT) -->
229 yearFragValue(Y),
230 "-",
231 monthFragValue(Mo),
232 "-",
233 dayFragValue(D),
234 "T",
235 ( hourFragValue(H),
236 ":",
237 minuteFragValue(Mi),
238 ":",
239 secondFragValue(S)
240 ; endOfDayFrag(Y, Mi, S)
241 ), !,
242 ?(timezoneFragValue, Off),
243 {newDateTime(Y, Mo, D, H, Mi, S, Off, DT)}.
296dateTimePlusDuration(duration(Mo0,S0), date_time(Y1,Mo1,D1,H1,Mi1,S1,Off), DT) :-
297 Mo2_ is Mo1 + Mo0,
298 normalizeMonth(Y1, Mo2_, Y2, Mo2),
299 daysInMonth(Y2, Mo2, DaysInMonth),
300 D2 is min(D1, DaysInMonth),
301 S2 is S1 + S0,
302 normalizeSecond(Y2, Mo2, D2, H1, Mi1, S2, Y3, Mo3, D3, H3, Mi3, S3),
303 newDateTime(Y3, Mo3, D3, H3, Mi3, S3, Off, DT).
322dayCanonicalFragmentMap(D) -->
323 {between(1, 31, D)},
324 unsTwoDigitCanonicalFragmentMap(D).
[58] dayFrag ::= ('0' [1-9]) | ([12] digit) | ('3' [01])
346dayFragValue(Day) -->
347 #(2, digit_weight, Ns),
348 {
349 integer_weights(Day, Ns),
350 must_be(between(1, 31), Day)
351 }.
Return:
380% 28 when y is absent. 381daysInMonth(Y, 2, 28):- 382 var(Y), !. 383% 28 when m is 2 and y is not evenly divisible by 4. 384daysInMonth(Y, 2, 28):- 385 Y rem 4 =\= 0, !. 386% 28 when m is 2 and y is evenly divisible by 100 but not by 400. 387daysInMonth(Y, 2, 28):- 388 Y rem 100 =:= 0, 389 Y rem 400 =\= 0, !. 390% 29 when m is 2 and y is evenly divisible by 400. 391daysInMonth(Y, 2, 29):- 392 Y rem 400 =:= 0, !. 393% 29 when m is 2 and y is evenly divisible by 4 but not by 100. 394daysInMonth(Y, 2, 29):- 395 Y rem 4 =:= 0, 396 Y rem 100 =\= 0, !. 397% 30 when m is 4, 6, 9, or 11. 398daysInMonth(_, Month, 30):- 399 memberchk(Month, [4,6,9,11]), !. 400% 31 otherwise (m is 1, 3, 5, 7, 8, 10, or 12). 401daysInMonth(_, _, 31).
Let:
Return sgn & 'P' & duYearMonthCanonicalFragmentMap(|s|)
427dayTimeDurationCanonicalMap(duration(0,S)) -->
428 ({S < 0} -> "-", {SAbs is abs(S)} ; {SAbs is abs(S)}),
429 "P",
430 duDayTimeCanonicalFragmentMap(SAbs).
459dayTimeDurationMap(duration(0,S)) -->
460 ("-" -> {Sg = -1} ; {Sg = 1}),
461 "P", duDayTimeFragmentMap(Sabs),
462 {S is Sg * Sabs}.
480decimalCanonicalMap(N) --> 481 {integer(N)}, !, 482 noDecimalPtCanonicalMap(N). 483decimalCanonicalMap(N) --> 484 decimalPtCanonicalMap(N).
508decimalLexicalMap(N) --> 509 decimalPtMap(N), !. 510decimalLexicalMap(N) --> 511 noDecimalMap(N).
530decimalPtCanonicalMap(N) --> 531 {N < 0}, !, 532 "-", 533 {N0 is abs(N)}, 534 unsignedDecimalPtCanonicalMap(N0). 535decimalPtCanonicalMap(N) --> 536 unsignedDecimalPtCanonicalMap(N).
557decimalPtMap(N) -->
558 ("-" -> {Sg = -1} ; "+" -> {Sg = 1} ; {Sg = 1}),
559 unsignedDecimalPtMap(N0),
560 {N is copysign(N0, Sg)}.
In the XSD 1.1 specification this mapping is named digit
, thus
conflicting with the name of the grammar rule to which it is
related.
616digitRemainderSeq(0, L):- !, 617 inflist(0, L). 618digitRemainderSeq(I1, [I1|T]):- 619 I2 is I1 xsd_div 10, 620 digitRemainderSeq(I2, T).
642digitSeq(0, L):- !, 643 inflist(0, L). 644digitSeq(I1, [I|T]):- 645 I is I1 xsd_mod 10, 646 I2 is I1 xsd_div 10, 647 digitSeq(I2, T).
668digitSequenceValue(Ds, N) :-
669 length(Ds, Len),
670 aggregate(
671 sum(D * 10 ^ (Len - I)),
672 nth1(I, Ds, D),
673 N
674 ).
694digitValue(N) -->
695 digit_weight(N).
716duDayFragmentMap(D) -->
717 noDecimalMap(D),
718 "D".
740duDayCanonicalFragmentMap(0) --> !, []. 741duDayCanonicalFragmentMap(D) --> 742 unsignedNoDecimalPtCanonicalMap(D), 743 "D".
776duDayTimeCanonicalFragmentMap(0) --> !, 777 "T0S". 778duDayTimeCanonicalFragmentMap(S0) --> 779 { 780 % Days 781 xsd_div(S0, 86400, D), 782 783 % Hours 784 xsd_mod(S0, 86400, H0), 785 xsd_div(H0, 3600, H), 786 787 % Minutes 788 xsd_mod(S0, 3600, Mi0), 789 xsd_div(Mi0, 60, Mi), 790 791 % Seconds 792 xsd_mod(S0, 60, S) 793 }, 794 duDayCanonicalFragmentMap(D), 795 duTimeCanonicalFragmentMap(H, Mi, S).
Second A nonnegative decimal number.
DT necessarily consists of an instance D of duDayFrag//1 and/or an instance T of duTimeFrag//1.
Let:
duDayFragmentMap(D)
(or 0 if D is not present)duTimeFragmentMap(T)
(or 0 if T is not present)Return 86400 Ã d + t
821duDayTimeFragmentMap(S) -->
822 ( duDayFragmentMap(D0)
823 -> (duTimeFragmentMap(S0) -> "" ; {S0 = 0})
824 ; {D0 = 0},
825 duTimeFragmentMap(S0)
826 ),
827 {S is 86400 * D0 + S0}.
849duHourCanonicalFragmentMap(0) --> !, []. 850duHourCanonicalFragmentMap(H) --> 851 unsignedNoDecimalPtCanonicalMap(H), 852 "H".
875duHourFragmentMap(H) -->
876 noDecimalMap(H),
877 "H".
899duMinuteCanonicalFragmentMap(0) --> !, []. 900duMinuteCanonicalFragmentMap(M) --> 901 unsignedNoDecimalPtCanonicalMap(M), 902 "M".
923duMinuteFragmentMap(Mi) -->
924 noDecimalMap(Mi),
925 "M".
946duMonthFragmentMap(Mo) -->
947 noDecimalMap(Mo),
948 "M".
982durationCanonicalMap(duration(Mo,S)) -->
983 ({(Mo < 0 ; S < 0.0)} -> "-" ; ""),
984 "P",
985 ( {Mo =:= 0}
986 -> {SAbs is abs(S)},
987 duDayTimeCanonicalFragmentMap(SAbs)
988 ; {S =:= 0}
989 -> {MoAbs is abs(Mo)},
990 duYearMonthCanonicalFragmentMap(MoAbs)
991 ; {
992 MoAbs is abs(Mo),
993 SAbs is abs(S)
994 },
995 duYearMonthCanonicalFragmentMap(MoAbs),
996 duDayTimeCanonicalFragmentMap(SAbs)
997 ).
1040durationMap(duration(Mo,S)) -->
1041 ("-" -> {Sg = -1} ; {Sg = 1}),
1042 "P",
1043 ( duYearMonthFragmentMap(MoAbs)
1044 -> (duDayTimeFragmentMap(SAbs) -> "" ; {SAbs = 0})
1045 ; {MoAbs = 0},
1046 duDayTimeFragmentMap(SAbs)
1047 ),
1048 {
1049 Mo is copysign(MoAbs, Sg),
1050 S is copysign(SAbs, Sg)
1051 }.
1076duSecondCanonicalFragmentMap(S) --> 1077 {S =:= 0}, !, []. 1078duSecondCanonicalFragmentMap(S) --> 1079 {integer(S)}, !, 1080 unsignedNoDecimalPtCanonicalMap(S), 1081 "S". 1082duSecondCanonicalFragmentMap(S) --> 1083 unsignedDecimalPtCanonicalMap(S), 1084 "S".
1107duSecondFragmentMap(S) -->
1108 (decimalPtMap(S) ; noDecimalMap(S)),
1109 "S".
1142duTimeCanonicalFragmentMap(0, 0, 0) --> !, []. 1143duTimeCanonicalFragmentMap(H, Mi, S) --> 1144 "T", 1145 duHourCanonicalFragmentMap(H), 1146 duMinuteCanonicalFragmentMap(Mi), 1147 duSecondCanonicalFragmentMap(S).
1178duTimeFragmentMap(S) -->
1179 "T",
1180 ( duHourFragmentMap(H0)
1181 -> (duMinuteFragmentMap(Mi0) -> "" ; {Mi0 = 0}),
1182 (duSecondFragmentMap(S0) -> "" ; {S0 = 0})
1183 ; duMinuteFragmentMap(Mi0)
1184 -> {H0 = 0},
1185 (duSecondFragmentMap(S0) -> "" ; {S0 = 0})
1186 ; {H0 = 0, Mi0 = 0},
1187 duSecondFragmentMap(S0)
1188 ),
1189 {S is 3600 * H0 + 60 * Mi0 + S0}.
1222duYearMonthCanonicalFragmentMap(YM) -->
1223 {
1224 Y is YM xsd_div 12,
1225 Mo is YM xsd_mod 12
1226 },
1227 ( {Y =:= 0}
1228 -> unsignedNoDecimalPtCanonicalMap(Mo),
1229 "M"
1230 ; {Mo =:= 0}
1231 -> unsignedNoDecimalPtCanonicalMap(Y),
1232 "Y"
1233 ; unsignedNoDecimalPtCanonicalMap(Y),
1234 "Y",
1235 unsignedNoDecimalPtCanonicalMap(Mo),
1236 "M"
1237 ).
1258duYearFragmentMap(Y) -->
1259 noDecimalMap(Y),
1260 "Y".
1286duYearMonthFragmentMap(Mo) -->
1287 ( duYearFragmentMap(Y0)
1288 -> (duMonthFragmentMap(Mo0) -> "" ; {Mo0 = 0})
1289 ; {Y0 = 0},
1290 duMonthFragmentMap(Mo0)
1291 ),
1292 {Mo is 12 * Y0 + Mo0}.
endOfDayFrag ::= '24:00:00' ('.' '0'+)?
1304endOfDayFrag(24, 0, 0) -->
1305 "24:00:00",
1306 ("." -> +("0") ; "").
1329fourDigitCanonicalFragmentMap(N) -->
1330 ({N < 0} -> "-", {N0 is -N} ; {N0 = N}),
1331 {N1 is N0 xsd_div 100},
1332 unsTwoDigitCanonicalFragmentMap(N1),
1333 {N2 is N0 xsd_mod 100},
1334 unsTwoDigitCanonicalFragmentMap(N2).
1358'FractionDigitRemainderSeq'(0, L):- !, 1359 inflist(0, L). 1360'FractionDigitRemainderSeq'(F1, [F0|T]):- 1361 F0 is F1 * 10, 1362 F2 is F0 xsd_mod 1, 1363 'FractionDigitRemainderSeq'(F2, T).
1385fractionDigitSeq(0, L):- !, 1386 inflist(0, L). 1387fractionDigitSeq(F1, [F0|T]):- 1388 F_ is F1 * 10, 1389 F0 is F_ xsd_div 1, 1390 F2 is F_ xsd_mod 1, 1391 fractionDigitSeq(F2, T).
1415fractionDigitsCanonicalFragmentMap(Frac) -->
1416 {
1417 fractionDigitSeq(Frac, Seq),
1418 'FractionDigitRemainderSeq'(Frac, RemSeq),
1419 lastSignificantDigit(RemSeq, Last),
1420 length(Ds, Last),
1421 prefix(Ds, Seq)
1422 },
1423 '*!'(digit_weight, Ds), !.
1444fractionDigitSequenceValue(Ds, F):-
1445 aggregate(
1446 % @bug The brackets are needed in the exponent.
1447 sum(rdiv(D,10^I)),
1448 nth1(I, Ds, D),
1449 F
1450 ).
1469fractionFragValue(Frac) -->
1470 '*!'(digit_weight, Ds), !,
1471 {fractionDigitSequenceValue(Ds, Frac)}.
1493gDayCanonicalMap(date_time(_,_,D,_,_,_,Off)) -->
1494 "---",
1495 dayCanonicalFragmentMap(D),
1496 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
1523gDayLexicalMap(DT) -->
1524 "---",
1525 dayFragValue(D),
1526 ?(timezoneFragValue, Off),
1527 {newDateTime(_, _, D, _, _, _, Off, DT)}.
1549gMonthCanonicalMap(date_time(_,Mo,_,_,_,_,Off)) -->
1550 "--",
1551 monthCanonicalFragmentMap(Mo),
1552 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
1583gMonthDayCanonicalMap(date_time(_,Mo,D,_,_,_,Off)) -->
1584 "--",
1585 monthCanonicalFragmentMap(Mo),
1586 "-",
1587 dayCanonicalFragmentMap(D),
1588 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
1611gMonthDayLexicalMap(DT) -->
1612 "--",
1613 monthFragValue(Mo),
1614 "-",
1615 dayFragValue(D),
1616 ?(timezoneFragValue, Off),
1617 {newDateTime(_, Mo, D, _, _, _, Off, DT)}.
1639gMonthLexicalMap(DT) -->
1640 "--",
1641 monthFragValue(Mo),
1642 ?(timezoneFragValue, Off),
1643 {newDateTime(_, Mo, _, _, _, _, Off, DT)}.
1665gYearCanonicalMap(date_time(Y,_,_,_,_,_,Off)) -->
1666 yearCanonicalFragmentMap(Y),
1667 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
1689gYearLexicalMap(DT) -->
1690 yearFragValue(Y),
1691 ?(timezoneFragValue, Off),
1692 {newDateTime(Y, _, _, _, _, _, Off, DT)}.
1721gYearMonthCanonicalMap(date_time(Y,Mo,_,_,_,_,Off)) -->
1722 yearCanonicalFragmentMap(Y),
1723 "-",
1724 monthCanonicalFragmentMap(Mo),
1725 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
1752gYearMonthLexicalMap(DT) -->
1753 yearFragValue(Y),
1754 "-",
1755 monthFragValue(Mo),
1756 ?(timezoneFragValue, Off),
1757 {newDateTime(Y, Mo, _, _, _, _, Off, DT)}.
1775hourCanonicalFragmentMap(H) -->
1776 {between(0, 23, H)},
1777 unsTwoDigitCanonicalFragmentMap(H).
1798hourFragValue(Hour) -->
1799 #(2, digit_weight, Ns),
1800 {
1801 integer_weights(Hour, Ns),
1802 must_be(between(0, 23), Hour)
1803 }.
This is zero iff the sequence consists of only zeros. This is a non-zero, count-by-1 index into Seq otherwise.
1826lastSignificantDigit(Seq, J):-
1827 nth0(J, Seq, N),
1828 N =:= 0, !.
1846minuteCanonicalFragmentMap(Mi) -->
1847 {between(0, 59, Mi)},
1848 unsTwoDigitCanonicalFragmentMap(Mi).
1866minuteFragValue(Minute) -->
1867 #(2, digit_weight, Ns),
1868 {
1869 integer_weights(Minute, Ns),
1870 must_be(between(0, 59), Minute)
1871 }.
1889monthCanonicalFragmentMap(Mo) -->
1890 {between(1, 12, Mo)},
1891 unsTwoDigitCanonicalFragmentMap(Mo).
1909monthFragValue(Month) -->
1910 #(2, digit_weight, Ns),
1911 {
1912 integer_weights(Month, Ns),
1913 must_be(between(1, 12), Month)
1914 }.
1996newDateTime(
1997 Y1, Mo1, D1, H1, Mi1, S1, Off,
1998 date_time(Y4,Mo4,D4,H4,Mi4,S4,Off)
1999) :-
2000 % Set the values that are used for performing the normalization.
2001 default_value(Y1, 1, Y2),
2002 default_value(Mo1, 1, Mo2),
2003 default_value(D1, 1, D2),
2004 default_value(H1, 0, H2),
2005 default_value(Mi1, 0, Mi2),
2006 default_value(S1, 0, S2),
2007 normalizeSecond(Y2, Mo2, D2, H2, Mi2, S2, Y3, Mo3, D3, H3, Mi3, S3),
2008 % Variables stay variable. Non-variables get the normalized value.
2009 var_or_val(Y1, Y3, Y4),
2010 var_or_val(Mo1, Mo3, Mo4),
2011 var_or_val(D1, D3, D4),
2012 var_or_val(H1, H3, H4),
2013 var_or_val(Mi1, Mi3, Mi4),
2014 var_or_val(S1, S3, S4).
Arguments
2035noDecimalMap(N) -->
2036 ("-" -> {Sg = -1} ; "+" -> {Sg = 1} ; {Sg = 1}),
2037 unsignedNoDecimalMap(N0),
2038 {N is copysign(N0, Sg)}.
2060noDecimalPtCanonicalMap(N) --> 2061 {N < 0}, !, 2062 "-", 2063 {N0 is abs(N)}, 2064 unsignedNoDecimalPtCanonicalMap(N0). 2065noDecimalPtCanonicalMap(N) --> 2066 unsignedNoDecimalPtCanonicalMap(N).
normalizeMonth(yr, mo)
daysInMonth(yr,
mo)
:
daysInMonth(yr, mo)
then:
normalizeMonth(yr, mo)
normalizeMonth(yr, mo)
2101normalizeDay(Y1, Mo1, D1, Y3, Mo3, D3):- 2102 normalizeMonth(Y1, Mo1, Y2, Mo2), 2103 normalizeDay0(Y2, Mo2, D1, Y3, Mo3, D3). 2104 2105 2106normalizeDay0(Y1, Mo1, D1, Y3, Mo3, D3):- 2107 daysInMonth(Y1, Mo1, D1_max), 2108 ( D1 > D1_max 2109 -> D2 is D1 - D1_max, 2110 Mo1_succ is Mo1 + 1, 2111 normalizeMonth(Y1, Mo1_succ, Y2, Mo2), 2112 normalizeDay0(Y2, Mo2, D2, Y3, Mo3, D3) 2113 ; D1 < 0 2114 -> Mo1_pred is Mo1 - 1, 2115 normalizeMonth(Y1, Mo1_pred, Y2, Mo2), 2116 daysInMonth(Y2, Mo2, D1_max), 2117 D2 is D1 + D1_max, 2118 normalizeDay0(Y2, Mo2, D2, Y3, Mo3, D3) 2119 ; Y3 = Y1, 2120 Mo3 = Mo1, 2121 D3 = D1 2122 ).
Algorithm:
normalizeDay(yr, mo, da)
2146normalizeMinute(Y1, Mo1, D1, H1, Mi1, Y2, Mo2, D2, H2, Mi2):-
2147 H1a is H1 + Mi1 xsd_div 60,
2148 Mi2 is Mi1 xsd_mod 60,
2149 D1a is D1 + H1a xsd_div 24,
2150 H2 is H1a xsd_mod 24,
2151 normalizeDay(Y1, Mo1, D1a, Y2, Mo2, D2).
2166normalizeMonth(Y1, Mo1, Y2, Mo2):-
2167 % Add (mo - 1) div 12 to yr.
2168 Y2 is Y1 + (Mo1 - 1) xsd_div 12,
2169 % Set mo to (mo - 1) mod 12 + 1.
2170 Mo2 is (Mo1 - 1) xsd_mod 12 + 1.
Algorithm:
normalizeMinute(yr, mo, da, hr, mi)
2190normalizeSecond(Y1, Mo1, D1, H1, Mi1, S1, Y2, Mo2, D2, H2, Mi2, S2):-
2191 Mi0 is Mi1 + S1 xsd_div 60,
2192 S2 is S1 xsd_mod 60,
2193 normalizeMinute(Y1, Mo1, D1, H1, Mi0, Y2, Mo2, D2, H2, Mi2).
2219scientificCanonicalMap(N) --> 2220 {N < 0}, !, 2221 "-", 2222 {N0 is abs(N)}, 2223 unsignedScientificCanonicalMap(N0). 2224scientificCanonicalMap(N) --> 2225 unsignedScientificCanonicalMap(N).
2254scientificMap(N) -->
2255 (decimalPtMap(C) -> "" ; noDecimalMap(C)),
2256 ("e" -> "" ; "E"),
2257 noDecimalMap(E),
2258 {N is C * 10 ^ E}.
2281secondCanonicalFragmentMap(S) --> 2282 {integer(S)}, !, 2283 unsTwoDigitCanonicalFragmentMap(S). 2284secondCanonicalFragmentMap(S) --> 2285 { 2286 I is S xsd_div 1, 2287 between(0, 59, I) 2288 }, 2289 unsTwoDigitCanonicalFragmentMap(I), 2290 ".", 2291 {Frac is S xsd_mod 1}, 2292 fractionDigitsCanonicalFragmentMap(Frac).
2314secondFragValue(S) --> 2315 unsignedDecimalPtMap(S), !, 2316 { 2317 0 =< S, 2318 S < 60 2319 }. 2320secondFragValue(S) --> 2321 unsignedNoDecimalMap(S), 2322 {between(0, 59, S)}.
2346specialRepCanonicalMap(positiveInfinity) --> !, "INF". 2347specialRepCanonicalMap(negativeInfinity) --> !, "-INF". 2348specialRepCanonicalMap(notANumber) --> "NaN".
2369specialRepValue(positiveInfinity) --> "INF", !. 2370specialRepValue(positiveInfinity) --> "+INF", !. 2371specialRepValue(negativeInfinity) --> "-INF", !. 2372specialRepValue(notANumber) --> "NaN".
2404timeCanonicalMap(date_time(_,_,_,H,Mi,S,Off)) -->
2405 hourCanonicalFragmentMap(H),
2406 ":",
2407 minuteCanonicalFragmentMap(Mi),
2408 ":",
2409 secondCanonicalFragmentMap(S),
2410 ({var(Off)} -> "" ; timezoneCanonicalFragmentMap(Off)).
2445timeLexicalMap(DT) -->
2446 ( hourFragValue(H),
2447 ":",
2448 minuteFragValue(Mi),
2449 ":",
2450 secondFragValue(S)
2451 ; endOfDayFrag(H, Mi, S)
2452 ), !,
2453 ?(timezoneFragValue, Off),
2454 {newDateTime(_, _, _, H, Mi, S, Off, DT)}.
dt
) to the decimal number denoting its position on the time
line in seconds.
Let:
daysInMonth(yr + 1, mo)
- 1 or (dt's day) - 1,
similarlySteps:
daysInMonth(yr + 1, m)
to ToTl
2510timeOnTimeline(dt(Y1,Mo1,D1,H,Mi1,S,Off), ToTl5) :-
2511 % Let âyrâ be 1971 when dt's year is absent, and (dt's year)-1
2512 % otherwise.
2513 (var(Y1) -> Y2 = 1971 ; Y2 is Y1 - 1),
2514 % Let âmoâ be 12 or (dt's month), similarly.
2515 default_value(Mo1, Mo2, 12),
2516 % Let âdaâ be daysInMonth(yr+1,mo)-1 or (dt's day)-1, similarly.
2517 Y3 is Y2 + 1,
2518 ( var(D1)
2519 -> daysInMonth(Y3, Mo2, D3),
2520 D2 is D3 - 1
2521 ; D2 is D1 - 1
2522 ),
2523 % Let âhrâ be 0 or (dt's hour), similarly.
2524 default_value(H, 0),
2525 % Let âmiâ be 0 or (dt's minute), similarly.
2526 default_value(Mi1, 0),
2527 % Let âseâ be 0 or (dt's second), similarly.
2528 default_value(S, 0),
2529 % Subtract âtimezoneOffsetâ from âmiâ when âtimezoneOffsetâ is not
2530 % absent.
2531 (var(Off) -> Mi2 = Mi1 ; Mi2 is Mi1 - Off),
2532 % Set ToTl to 31536000 Ã yr.
2533 ToTl1 is 31536000 * Y2,
2534 % Leap-year, month, and day.
2535 % Add 86400 ⨯ (yr div 400 - yr div 100 + yr div 4) to ToTl.
2536 ToTl2 is ToTl1 + 86400 * ((Y2 xsd_div 400) - (Y2 xsd_div 100) + (Y2 xsd_div 4)),
2537 % Add 86400 Ã Sum_{m < mo} daysInMonth(yr+1,m) to ToTl.
2538 Mo3 is Mo2 - 1,
2539 aggregate_all(
2540 sum(D0),
2541 (
2542 between(1, Mo3, Mo0),
2543 daysInMonth(Y3, Mo0, D0)
2544 ),
2545 DaysInMonth
2546 ),
2547 ToTl3 is ToTl2 + 86400 * DaysInMonth,
2548 % Add 86400 ⨯ âdaâ to ToTl.
2549 ToTl4 is ToTl3 + 86400 * D2,
2550 % Hour, minute, and second.
2551 % Add 3600 ⨯ hr + 60 ⨯ mi + se to ToTl.
2552 ToTl5 is ToTl4 + 3600 * H + 60 * Mi2 + S.
2578timezoneCanonicalFragmentMap(0) --> !, 2579 "Z". 2580timezoneCanonicalFragmentMap(Off) --> 2581 ({Off < 0} -> "-", {OffAbs is abs(Off)} ; "+", {OffAbs = Off}), 2582 {H is OffAbs xsd_div 60}, 2583 unsTwoDigitCanonicalFragmentMap(H), 2584 ":", 2585 {Mi is OffAbs xsd_mod 60}, 2586 unsTwoDigitCanonicalFragmentMap(Mi).
2619timezoneFragValue(0) --> 2620 "Z", !. 2621timezoneFragValue(Off) --> 2622 ("-" -> {Sg = -1} ; "+" -> {Sg = 1}), 2623 hourFragValue(H), 2624 ":", 2625 minuteFragValue(Mi), 2626 {Off is copysign(H * 60 + Mi, Sg)}.
2646unsignedDecimalPtCanonicalMap(N) -->
2647 {N1 is N xsd_div 1},
2648 unsignedNoDecimalPtCanonicalMap(N1),
2649 ".",
2650 {N2 is N xsd_mod 1},
2651 ({N2 =:= 0} -> "" ; fractionDigitsCanonicalFragmentMap(N2)).
2681unsignedDecimalPtMap(N) --> 2682 unsignedNoDecimalMap(I), !, 2683 ".", 2684 (fractionFragValue(F) -> {N is I + F} ; {N is I}). 2685unsignedDecimalPtMap(N) --> 2686 ".", 2687 fractionFragValue(N).
Maps an unsignedNoDecimalPtNumeral//1 to its numerical value.
2708unsignedNoDecimalMap(N) -->
2709 '*!'(digit_weight, Ds), !,
2710 {digitSequenceValue(Ds, N)}.
2732unsignedNoDecimalPtCanonicalMap(N) -->
2733 {
2734 digitRemainderSeq(N, RemainderSeq),
2735 lastSignificantDigit(RemainderSeq, Last),
2736 digitSeq(N, Seq),
2737 % Count-by-1.
2738 length(Ds0, Last),
2739 prefix(Ds0, Seq),
2740 reverse(Ds0, Ds)
2741 },
2742 ({Ds == []} -> "0" ; '+!'(digit_weight, Ds), !).
2762unsignedScientificCanonicalMap(N) -->
2763 {( N =:= 0
2764 -> N1 = 0
2765 ; N1 is rationalize(N / 10 ^ (log10(N) xsd_div 1))
2766 )},
2767 unsignedDecimalPtCanonicalMap(N1),
2768 "E",
2769 {(N =:= 0 -> N2 = 0 ; N2 is rationalize(log10(N) xsd_div 1))},
2770 noDecimalPtCanonicalMap(N2).
2787unsTwoDigitCanonicalFragmentMap(N) -->
2788 {N1 is N xsd_div 10},
2789 digit_weight(N1),
2790 {N2 is N xsd_mod 10},
2791 digit_weight(N2).
2813yearCanonicalFragmentMap(Y) --> 2814 {abs(Y) > 9999}, !, 2815 noDecimalPtCanonicalMap(Y). 2816yearCanonicalFragmentMap(Y) --> 2817 fourDigitCanonicalFragmentMap(Y).
2835yearFragValue(YR) -->
2836 noDecimalMap(YR).
2861yearMonthDurationCanonicalMap(duration(Mo,0)) -->
2862 ({Mo < 0} -> "-", {MoAbs = -Mo} ; {MoAbs = Mo}),
2863 "P",
2864 duYearMonthCanonicalFragmentMap(MoAbs).
2898yearMonthDurationMap(duration(Mo,0)) --> 2899 ("-" -> {Sg = -1} ; {Sg = 1}), 2900 "P", duYearMonthFragmentMap(Moabs), 2901 {Mo is Sg * Moabs}. 2902 2903 2904 2905 2906 2907% HELPERS %
2914var_or_val(Arg, _, _):- 2915 var(Arg), !. 2916var_or_val(_, Val, Val)
XSD grammar
XSD grammar rules for parsing decimals and durations.
*/