1:- module(xpath, [
    2  assert/5
    3]).    4
    5:- use_module(library(regex)).    6:- use_module(library(url)).    7:- use_module(library(xsd/flatten)).    8:- use_module(library(xsd/simpletype)).    9:- use_module(library(xsd/xsd_helper)).   10:- use_module(library(xsd/xsd_messages)).   11
   12:- op(1, fx, user:($)).   13:- op(400, fy, user:(@)).   14:- op(400, yf, user:([])).   15:- op(400, yfx, user:(::)).   16:- op(400, yf, user:(::*)).   17:- op(400, yfx, user:(idiv)).   18:- op(400, yfx, user:(/)).   19:- op(700, xfx, user:(eq)).   20:- op(700, xfx, user:(ne)).   21:- op(700, xfx, user:(le)).   22:- op(700, xfx, user:(lt)).   23:- op(700, xfx, user:(ge)).   24:- op(700, xfx, user:(gt)).   25
   26:- set_prolog_flag(allow_variable_name_as_functor, true).   27
   28
   29% this is the exported predicate, which is used in validate.pl
   30assert(D_File, D_ID, D_Text, XPathString, Documentation) :-
   31  validate_xpath(D_File, D_ID, D_Text, XPathString, Documentation).
   32
   33% evaluate the xpath expression and check the result
   34validate_xpath(D_File, D_ID, D_Text, XPathString, Documentation) :-
   35  term_string(XPathExpr, XPathString),
   36  !,
   37  (
   38    xpath_expr(context(D_File, D_ID, D_Text), XPathExpr, Result), !, isValid(Result) ->
   39      true
   40      ;
   41      (
   42        Documentation = null ->
   43          warning('An assert is not fulfilled.')
   44          ;
   45          warning('The following assert is not fulfilled: ~w', Documentation)
   46      ),
   47      false
   48  ).
   49
   50
   51/* ### Special Cases ### */
   52
   53/* --- atomic values --- */
   54% atomic values are converted to our internal data structure with a suitable constructor
   55xpath_expr(Context, Value, Result) :-
   56  \+ compound(Value),
   57  (
   58    number(Value) ->
   59      atom_number(ValueAtom, Value)
   60      ;
   61      ValueAtom = Value
   62  ),
   63  (
   64    member(ValueAtom, ['false', 'true']) ->
   65      xpath_expr(Context, boolean(ValueAtom), Result);
   66      (
   67        xpath_expr(Context, string(ValueAtom), Result);
   68        xpath_expr(Context, decimal(ValueAtom), Result);
   69        xpath_expr(Context, float(ValueAtom), Result);
   70        xpath_expr(Context, double(ValueAtom), Result);
   71        xpath_expr(Context, duration(ValueAtom), Result);
   72        xpath_expr(Context, dateTime(ValueAtom), Result);
   73        xpath_expr(Context, time(ValueAtom), Result);
   74        xpath_expr(Context, date(ValueAtom), Result);
   75        xpath_expr(Context, gYearMonth(ValueAtom), Result);
   76        xpath_expr(Context, gYear(ValueAtom), Result);
   77        xpath_expr(Context, gMonthDay(ValueAtom), Result);
   78        xpath_expr(Context, gDay(ValueAtom), Result);
   79        xpath_expr(Context, gMonth(ValueAtom), Result);
   80        xpath_expr(Context, hexBinary(ValueAtom), Result);
   81        xpath_expr(Context, base64Binary(ValueAtom), Result);
   82        xpath_expr(Context, anyURI(ValueAtom), Result);
   83        xpath_expr(Context, QName(ValueAtom), Result);
   84        xpath_expr(Context, normalizedString(ValueAtom), Result);
   85        xpath_expr(Context, token(ValueAtom), Result);
   86        xpath_expr(Context, language(ValueAtom), Result);
   87        xpath_expr(Context, NMTOKEN(ValueAtom), Result);
   88        xpath_expr(Context, NCName(ValueAtom), Result);
   89        xpath_expr(Context, Name(ValueAtom), Result);
   90        xpath_expr(Context, ID(ValueAtom), Result);
   91        xpath_expr(Context, IDREF(ValueAtom), Result);
   92        xpath_expr(Context, ENTITY(ValueAtom), Result);
   93        xpath_expr(Context, integer(ValueAtom), Result);
   94        xpath_expr(Context, nonPositiveInteger(ValueAtom), Result);
   95        xpath_expr(Context, negativeInteger(ValueAtom), Result);
   96        xpath_expr(Context, long(ValueAtom), Result);
   97        xpath_expr(Context, int(ValueAtom), Result);
   98        xpath_expr(Context, short(ValueAtom), Result);
   99        xpath_expr(Context, byte(ValueAtom), Result);
  100        xpath_expr(Context, nonNegativeInteger(ValueAtom), Result);
  101        xpath_expr(Context, unsignedLong(ValueAtom), Result);
  102        xpath_expr(Context, unsignedInt(ValueAtom), Result);
  103        xpath_expr(Context, unsignedShort(ValueAtom), Result);
  104        xpath_expr(Context, unsignedByte(ValueAtom), Result);
  105        xpath_expr(Context, positiveInteger(ValueAtom), Result);
  106        xpath_expr(Context, yearMonthDuration(ValueAtom), Result);
  107        xpath_expr(Context, dayTimeDuration(ValueAtom), Result);
  108        xpath_expr(Context, untypedAtomic(ValueAtom), Result)
  109      )
  110  ).
  111
  112/* --- $value --- */
  113xpath_expr(context(D_File, D_ID, D_Text), $value, Result) :-
  114  D_Text \= false,
  115  xpath_expr(context(D_File, D_ID, D_Text), D_Text, Result).
  116
  117
  118/* ### Location path expressions ### */
  119
  120/* --- steps --- */
  121/* -- axes -- */
  122xpath_expr(Context, Nodename, Result) :-
  123  \+compound(Nodename),
  124  xpath_expr(Context, child::Nodename, Result).
  125xpath_expr(context(D_File, D_ID, _), Axe::Nodename, data('node', [D_Node_ID])) :-
  126  (
  127    Axe = child, child(D_File, D_ID, D_Node_ID)
  128    % TODO: implement other axes
  129  ),
  130  node(D_File, D_Node_ID, _, Nodename).
  131xpath_expr(context(D_File, D_ID, _), Axe::*, data('node', [D_Node_ID])) :-
  132  (
  133    Axe = child, child(D_File, D_ID, D_Node_ID)
  134    % TODO: implement other axes
  135  ).
  136xpath_expr(Context, Node/Nodename, Result) :-
  137  \+compound(Nodename),
  138  xpath_expr(Context, Node/child::Nodename, Result).
  139xpath_expr(context(D_File, D_ID, D_Text), Node/Axe::Nodename, data('node', [D_Node_ID])) :-
  140  xpath_expr(context(D_File, D_ID, D_Text), Node, data('node', [D_Parent_ID])),
  141  (
  142    Axe = child, child(D_File, D_Parent_ID, D_Node_ID)
  143    % TODO: implement other axes
  144  ),
  145  node(D_File, D_Node_ID, _, Nodename).
  146xpath_expr(context(D_File, D_ID, D_Text), Node/Axe::*, data('node', [D_Node_ID])) :-
  147  xpath_expr(context(D_File, D_ID, D_Text), Node, data('node', [D_Parent_ID])),
  148  (
  149    Axe = child, child(D_File, D_Parent_ID, D_Node_ID)
  150    % TODO: implement other axes
  151  ).
  152
  153/* --- predicates --- */
  154xpath_expr(context(D_File, D_ID, D_Text), Node[Predicate], data('node', [D_Node_ID])) :-
  155  xpath_expr(context(D_File, D_ID, D_Text), Node, data('node', [D_Node_ID])),
  156  xpath_expr(context(D_File, D_Node_ID, D_Text), Predicate, PredicateResult),
  157  isValid(PredicateResult).
  158
  159/* --- attributes --- */
  160xpath_expr(context(D_File, D_ID, D_Text), @Attribute, Result) :-
  161  node_attribute(D_File, D_ID, Attribute, AttributeValue),
  162  xpath_expr(context(D_File, D_ID, D_Text), AttributeValue, Result).
  163
  164
  165/* ### Operators ### */
  166
  167xpath_expr(Context, Value1 + Value2, Result) :-
  168  xpath_expr(Context, numeric-add(Value1, Value2), Result).
  169
  170xpath_expr(Context, Value1 - Value2, Result) :-
  171  /* the next two lines are there to avoid performance issues caused by recursion */
  172  (compound(Value1); number(Value1); Value1 =~ '^(\\+|-)?INF|NaN$'),
  173  (compound(Value2); number(Value2); Value2 =~ '^(\\+|-)?INF|NaN$'),
  174  xpath_expr(Context, numeric-subtract(Value1, Value2), Result).
  175
  176xpath_expr(Context, Value1 * Value2, Result) :-
  177  xpath_expr(Context, numeric-multiply(Value1, Value2), Result).
  178
  179xpath_expr(Context, Value1 div Value2, Result) :-
  180  xpath_expr(Context, numeric-divide(Value1, Value2), Result).
  181
  182xpath_expr(Context, Value1 idiv Value2, Result) :-
  183  xpath_expr(Context, numeric-integer-divide(Value1, Value2), Result).
  184
  185xpath_expr(Context, Value1 mod Value2, Result) :-
  186  /* the next two lines are there to avoid performance issues caused by recursion */
  187  (compound(Value1); number(Value1); Value1 =~ '^(\\+|-)?INF|NaN$'),
  188  (compound(Value2); number(Value2); Value2 =~ '^(\\+|-)?INF|NaN$'),
  189  xpath_expr(Context, numeric-mod(Value1, Value2), Result).
  190
  191xpath_expr(Context, +Value, Result) :-
  192  xpath_expr(Context, numeric-unary-plus(Value), Result).
  193
  194xpath_expr(Context, -Value, Result) :-
  195  xpath_expr(Context, numeric-unary-minus(Value), Result).
  196
  197xpath_expr(Context, Value1 eq Value2, Result) :-
  198  % TODO: other types
  199  xpath_expr(Context, numeric-equal(Value1, Value2), Result).
  200xpath_expr(Context, Value1 ne Value2, data('boolean', [ResultValue])) :-
  201  % TODO: other types
  202  xpath_expr(Context, numeric-equal(Value1, Value2), data('boolean', [EqualValue])),
  203  (
  204    EqualValue = true ->
  205      ResultValue = false;
  206      ResultValue = true
  207  ).
  208xpath_expr(Context, Value1 le Value2, data('boolean', [ResultValue])) :-
  209  xpath_expr(Context, numeric-less-than(Value1, Value2), data('boolean', [ResultValue1])),
  210  xpath_expr(Context, numeric-equal(Value1, Value2), data('boolean', [ResultValue2])),
  211  (
  212    ResultValue1 = true; ResultValue2 = true ->
  213      ResultValue = true;
  214      ResultValue = false
  215  ).
  216xpath_expr(Context, Value1 lt Value2, Result) :-
  217  xpath_expr(Context, numeric-less-than(Value1, Value2), Result).
  218xpath_expr(Context, Value1 ge Value2, data('boolean', [ResultValue])) :-
  219  xpath_expr(Context, numeric-greater-than(Value1, Value2), data('boolean', [ResultValue1])),
  220  xpath_expr(Context, numeric-equal(Value1, Value2), data('boolean', [ResultValue2])),
  221  (
  222    ResultValue1 = true; ResultValue2 = true ->
  223      ResultValue = true;
  224      ResultValue = false
  225  ).
  226xpath_expr(Context, Value1 gt Value2, Result) :-
  227  xpath_expr(Context, numeric-greater-than(Value1, Value2), Result).
  228
  229
  230/* ### constructors ### */
  231
  232xpath_expr(_, data(T, VL), data(T, VL)).
  233/* --- string --- */
  234xpath_expr(_, string(Value), data('string', [Value])) :-
  235  validate_xsd_simpleType('string', Value).
  236/* --- boolean --- */
  237xpath_expr(_, boolean(Value), data('boolean', [ResultValue])) :-
  238  member(Value, ['false', '0']) ->
  239    ResultValue = false;
  240    ResultValue = true.
  241/* --- decimal --- */
  242xpath_expr(_, decimal(Value), data('decimal', [ResultValue])) :-
  243  validate_xsd_simpleType('decimal', Value),
  244  ( % add leading 0 in front of decimal point, as prolog cannot handle decimals like ".32"
  245  Value =~ '^(\\+|-)?\\..*$' ->
  246    (
  247      atomic_list_concat(TMP, '.', Value),
  248      atomic_list_concat(TMP, '0.', ProcValue)
  249    );
  250    ProcValue = Value
  251  ),
  252  atom_number(ProcValue, ResultValue).
  253/* --- float --- */
  254xpath_expr(_, float(Value), data('float', [ResultValue])) :-
  255  validate_xsd_simpleType('float', Value),
  256  parse_float(Value, ResultValue).
  257/* --- double --- */
  258xpath_expr(_, double(Value), data('double', [ResultValue])) :-
  259  validate_xsd_simpleType('double', Value),
  260  % double values are internally handled as float values
  261  parse_float(Value, ResultValue).
  262/* --- duration --- */
  263xpath_expr(_, duration(Value), data('duration', DurationValue)) :-
  264  validate_xsd_simpleType('duration', Value),
  265  parse_duration(Value, DurationValue).
  266/* --- dateTime --- */
  267xpath_expr(Context, dateTime(Value), data('dateTime', [Year, Month, Day, Hour, Minute, Second, TimeZoneOffset])) :-
  268  validate_xsd_simpleType('dateTime', Value),
  269  atom_string(Value, ValueString),
  270  split_string(ValueString, 'T', '', TSplit),
  271  TSplit = [DateString, TimeString],
  272  atom_string(Date, DateString),
  273  atom_string(Time, TimeString),
  274  xpath_expr(Context, date(Date), data('date', [Year, Month, Day, _, _, _, _])),
  275  xpath_expr(Context, time(Time), data('time', [_, _, _, Hour, Minute, Second, TimeZoneOffset])).
  276xpath_expr(Context, dateTime(Date,Time), data('dateTime', [Year, Month, Day, Hour, Minute, Second, TimeZoneOffset])) :-
  277  validate_xsd_simpleType('date', Date),
  278  validate_xsd_simpleType('time', Time),
  279  xpath_expr(Context, date(Date), data('date', [Year, Month, Day, _, _, _, TimeZoneOffsetDate])),
  280  xpath_expr(Context, time(Time), data('time', [_, _, _, Hour, Minute, Second, TimeZoneOffsetTime])),
  281  (
  282    % both date and time have the same or no TC
  283    TimeZoneOffsetDate = TimeZoneOffsetTime, TimeZoneOffset = TimeZoneOffsetDate;
  284    % only date has TC
  285    TimeZoneOffsetDate \= 0, TimeZoneOffsetTime = 0, TimeZoneOffset = TimeZoneOffsetDate;
  286    % only time has TC
  287    TimeZoneOffsetDate = 0, TimeZoneOffsetTime \= 0, TimeZoneOffset = TimeZoneOffsetTime
  288  ).
  289/* --- time --- */
  290xpath_expr(_, time(Value), data('time', [0, 0, 0, Hour, Minute, Second, TimeZoneOffset])) :-
  291  validate_xsd_simpleType('time', Value),
  292  atom_string(Value, ValueString),
  293  (
  294    % negative TC
  295    split_string(ValueString, '-', '', MinusSplit),
  296    MinusSplit = [TimeTMP, TimeZoneTMP],
  297    TimeZoneSign = '-'
  298    ;
  299    % positive TC
  300    split_string(ValueString, '+', '', PlusSplit),
  301    PlusSplit = [TimeTMP, TimeZoneTMP],
  302    TimeZoneSign = '+'
  303    ;
  304    % UTC TC
  305    split_string(ValueString, 'Z', '', ZSplit),
  306    ZSplit = [TimeTMP, _],
  307    TimeZoneSign = '+',
  308    TimeZoneTMP = '00:00'
  309    ;
  310    % no TC
  311    split_string(ValueString, 'Z+-', '', AllSplit),
  312    AllSplit = [TimeTMP],
  313    TimeZoneSign = '+',
  314    TimeZoneTMP = '00:00'
  315  ),
  316  split_string(TimeTMP, ':', '', TimeSplit),
  317  TimeSplit = [HourTMP, MinuteTMP, SecondTMP],
  318  split_string(TimeZoneTMP, ':', '', TimeZoneSplit),
  319  TimeZoneSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  320  number_string(Hour, HourTMP),
  321  number_string(Minute, MinuteTMP),
  322  number_string(Second, SecondTMP),
  323  number_string(TimeZoneHour, TimeZoneHourTMP),
  324  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  325  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  326/* --- date --- */
  327xpath_expr(_, date(Value), data('date', [Year, Month, Day, 0, 0, 0, TimeZoneOffset])) :-
  328  validate_xsd_simpleType('date', Value),
  329  atom_string(Value, ValueString),
  330  split_string(ValueString, '-', '', MinusSplit),
  331  (
  332    % BC, negative TZ
  333    MinusSplit = [_, YearString, MonthTMP, DayTMP, TimeZoneTMP], string_concat('-', YearString, YearTMP), TimeZoneSign = '-';
  334    % BC, UTC, positive, no TZ
  335    MinusSplit = [_, YearString, MonthTMP, DayTimeZoneTMP], string_concat('-', YearString, YearTMP), TimeZoneSign = '+',
  336    timezone_split(DayTMP, TimeZoneTMP, DayTimeZoneTMP);
  337    % AD, negative TZ
  338    MinusSplit = [YearTMP, MonthTMP, DayTMP, TimeZoneTMP], TimeZoneSign = '-';
  339    % AD, UTC, positive, no TZ
  340    MinusSplit = [YearTMP, MonthTMP, DayTimeZoneTMP], TimeZoneSign = '+',
  341    timezone_split(DayTMP, TimeZoneTMP, DayTimeZoneTMP)
  342  ),
  343  split_string(TimeZoneTMP, ':', '', ColonSplit),
  344  ColonSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  345  number_string(Year, YearTMP),
  346  number_string(Month, MonthTMP),
  347  number_string(Day, DayTMP),
  348  number_string(TimeZoneHour, TimeZoneHourTMP),
  349  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  350  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  351/* --- gYearMonth --- */
  352xpath_expr(_, gYearMonth(Value), data('gYearMonth', [Year, Month, 0, 0, 0, 0, TimeZoneOffset])) :-
  353  validate_xsd_simpleType('gYearMonth', Value),
  354  atom_string(Value, ValueString),
  355  split_string(ValueString, '-', '', MinusSplit),
  356  (
  357    % BC, negative TZ
  358    MinusSplit = [_, YearString, MonthTMP, TimeZoneTMP], string_concat('-', YearString, YearTMP), TimeZoneSign = '-';
  359    % BC, UTC, positive, no TZ
  360    MinusSplit = [_, YearString, MonthTimeZoneTMP], string_concat('-', YearString, YearTMP), TimeZoneSign = '+',
  361    timezone_split(MonthTMP, TimeZoneTMP, MonthTimeZoneTMP);
  362    % AD, negative TZ
  363    MinusSplit = [YearTMP, MonthTMP, TimeZoneTMP], TimeZoneSign = '-';
  364    % AD, UTC, positive, no TZ
  365    MinusSplit = [YearTMP, MonthTimeZoneTMP], TimeZoneSign = '+',
  366    timezone_split(MonthTMP, TimeZoneTMP, MonthTimeZoneTMP)
  367  ),
  368  split_string(TimeZoneTMP, ':', '', ColonSplit),
  369  ColonSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  370  number_string(Year, YearTMP),
  371  number_string(Month, MonthTMP),
  372  number_string(TimeZoneHour, TimeZoneHourTMP),
  373  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  374  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  375/* --- gYear --- */
  376xpath_expr(_, gYear(Value), data('gYear', [Year, 0, 0, 0, 0, 0, TimeZoneOffset])) :-
  377  validate_xsd_simpleType('gYear', Value),
  378  atom_string(Value, ValueString),
  379  split_string(ValueString, '-', '', MinusSplit),
  380  (
  381    % BC, negative TZ
  382    MinusSplit = [_, YearString, TimeZoneTMP], string_concat('-', YearString, YearTMP), TimeZoneSign = '-';
  383    % BC, UTC, positive, no TZ
  384    MinusSplit = [_, YearTimeZoneTMP], TimeZoneSign = '+',
  385    timezone_split(YearString, TimeZoneTMP, YearTimeZoneTMP), string_concat('-', YearString, YearTMP);
  386    % AD, negative TZ
  387    MinusSplit = [YearTMP, TimeZoneTMP], TimeZoneSign = '-';
  388    % AD, UTC, positive, no TZ
  389    MinusSplit = [YearTimeZoneTMP], TimeZoneSign = '+',
  390    timezone_split(YearTMP, TimeZoneTMP, YearTimeZoneTMP)
  391  ),
  392  split_string(TimeZoneTMP, ':', '', ColonSplit),
  393  ColonSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  394  number_string(Year, YearTMP),
  395  number_string(TimeZoneHour, TimeZoneHourTMP),
  396  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  397  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  398/* --- gMonthDay --- */
  399xpath_expr(_, gMonthDay(Value), data('gMonthDay', [0, Month, Day, 0, 0, 0, TimeZoneOffset])) :-
  400  validate_xsd_simpleType('gMonthDay', Value),
  401  atom_string(Value, ValueString),
  402  split_string(ValueString, '-', '', MinusSplit),
  403  (
  404    % negative TZ
  405    MinusSplit = [_, _, MonthTMP, DayTMP, TimeZoneTMP], TimeZoneSign = '-';
  406    % UTC, positive, no TZ
  407    MinusSplit = [_, _, MonthTMP, DayTimeZoneTMP], TimeZoneSign = '+',
  408    timezone_split(DayTMP, TimeZoneTMP, DayTimeZoneTMP)
  409  ),
  410  split_string(TimeZoneTMP, ':', '', ColonSplit),
  411  ColonSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  412  number_string(Month, MonthTMP),
  413  number_string(Day, DayTMP),
  414  number_string(TimeZoneHour, TimeZoneHourTMP),
  415  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  416  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  417/* --- gDay --- */
  418xpath_expr(_, gDay(Value), data('gDay', [0, 0, Day, 0, 0, 0, TimeZoneOffset])) :-
  419  validate_xsd_simpleType('gDay', Value),
  420  atom_string(Value, ValueString),
  421  split_string(ValueString, '-', '', MinusSplit),
  422  (
  423    % negative TZ
  424    MinusSplit = [_, _, _, DayTMP, TimeZoneTMP], TimeZoneSign = '-';
  425    % UTC, positive, no TZ
  426    MinusSplit = [_, _, _, DayTimeZoneTMP], TimeZoneSign = '+',
  427    timezone_split(DayTMP, TimeZoneTMP, DayTimeZoneTMP)
  428  ),
  429  split_string(TimeZoneTMP, ':', '', ColonSplit),
  430  ColonSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  431  number_string(Day, DayTMP),
  432  number_string(TimeZoneHour, TimeZoneHourTMP),
  433  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  434  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  435/* --- gMonth --- */
  436xpath_expr(_, gMonth(Value), data('gMonth', [0, Month, 0, 0, 0, 0, TimeZoneOffset])) :-
  437  validate_xsd_simpleType('gMonth', Value),
  438  atom_string(Value, ValueString),
  439  split_string(ValueString, '-', '', MinusSplit),
  440  (
  441    % negative TZ
  442    MinusSplit = [_, _, MonthTMP, TimeZoneTMP], TimeZoneSign = '-';
  443    % UTC, positive, no TZ
  444    MinusSplit = [_, _, MonthTimeZoneTMP], TimeZoneSign = '+',
  445    timezone_split(MonthTMP, TimeZoneTMP, MonthTimeZoneTMP)
  446  ),
  447  split_string(TimeZoneTMP, ':', '', ColonSplit),
  448  ColonSplit = [TimeZoneHourTMP, TimeZoneMinuteTMP],
  449  number_string(Month, MonthTMP),
  450  number_string(TimeZoneHour, TimeZoneHourTMP),
  451  number_string(TimeZoneMinute, TimeZoneMinuteTMP),
  452  timezone_offset(TimeZoneSign, TimeZoneHour, TimeZoneMinute, TimeZoneOffset).
  453/* --- hexBinary --- */
  454xpath_expr(_, hexBinary(Value), data('hexBinary', [ResultValue])) :-
  455  validate_xsd_simpleType('hexBinary', Value),
  456  atom_string(Value, ValueString),
  457  string_upper(ValueString, UpperCaseValue),
  458  atom_string(ResultValue, UpperCaseValue).
  459/* --- base64Binary --- */
  460xpath_expr(_, base64Binary(Value), data('base64Binary', [ResultValue])) :-
  461  validate_xsd_simpleType('base64Binary', Value),
  462  atom_string(Value, ValueString),
  463  string_upper(ValueString, UpperCaseValue),
  464  atomic_list_concat(TMP, ' ', UpperCaseValue),
  465  atomic_list_concat(TMP, '', ResultValue).
  466/* --- anyURI --- */
  467xpath_expr(_, anyURI(Value), data('anyURI', [Value])) :-
  468  validate_xsd_simpleType('anyURI', Value).
  469/* --- QName --- */
  470xpath_expr(_, QName(Value), data('QName', [Value])) :-
  471  validate_xsd_simpleType('QName', Value).
  472/* --- normalizedString --- */
  473xpath_expr(_, normalizedString(Value), data('normalizedString', [Value])) :-
  474  validate_xsd_simpleType('normalizedString', Value).
  475/* --- token --- */
  476xpath_expr(_, token(Value), data('token', [Value])) :-
  477  validate_xsd_simpleType('token', Value).
  478/* --- language --- */
  479xpath_expr(_, language(Value), data('language', [Value])) :-
  480  validate_xsd_simpleType('language', Value).
  481/* --- NMTOKEN --- */
  482xpath_expr(_, NMTOKEN(Value), data('NMTOKEN', [ValueSanitized])) :-
  483  normalize_space(atom(ValueSanitized), Value),
  484  validate_xsd_simpleType('NMTOKEN', ValueSanitized).
  485/* --- NCName --- */
  486xpath_expr(_, NCName(Value), data('NCName', [Value])) :-
  487  validate_xsd_simpleType('NCName', Value).
  488/* --- Name --- */
  489xpath_expr(_, Name(Value), data('Name', [Value])) :-
  490  validate_xsd_simpleType('Name', Value).
  491/* --- ID --- */
  492xpath_expr(_, ID(Value), data('ID', [Value])) :-
  493  validate_xsd_simpleType('ID', Value).
  494/* --- IDREF --- */
  495xpath_expr(_, IDREF(Value), data('IDREF', [Value])) :-
  496  validate_xsd_simpleType('IDREF', Value).
  497/* --- ENTITY --- */
  498xpath_expr(_, ENTITY(Value), data('ENTITY', [Value])) :-
  499  validate_xsd_simpleType('ENTITY', Value).
  500/* --- integer --- */
  501xpath_expr(_, integer(Value), data('integer', [NumberValue])) :-
  502  validate_xsd_simpleType('integer', Value),
  503  atom_number(Value, NumberValue).
  504/* --- nonPositiveInteger --- */
  505xpath_expr(_, nonPositiveInteger(Value), data('nonPositiveInteger', [NumberValue])) :-
  506  validate_xsd_simpleType('nonPositiveInteger', Value),
  507  atom_number(Value, NumberValue).
  508/* --- negativeInteger --- */
  509xpath_expr(_, negativeInteger(Value), data('negativeInteger', [NumberValue])) :-
  510  validate_xsd_simpleType('negativeInteger', Value),
  511  atom_number(Value, NumberValue).
  512/* --- long --- */
  513xpath_expr(_, long(Value), data('long', [NumberValue])) :-
  514  validate_xsd_simpleType('long', Value),
  515  atom_number(Value, NumberValue).
  516/* --- int --- */
  517xpath_expr(_, int(Value), data('int', [NumberValue])) :-
  518  validate_xsd_simpleType('int', Value),
  519  atom_number(Value, NumberValue).
  520/* --- short --- */
  521xpath_expr(_, short(Value), data('short', [NumberValue])) :-
  522  validate_xsd_simpleType('short', Value),
  523  atom_number(Value, NumberValue).
  524/* --- byte --- */
  525xpath_expr(_, byte(Value), data('byte', [NumberValue])) :-
  526  validate_xsd_simpleType('byte', Value),
  527  atom_number(Value, NumberValue).
  528/* --- nonNegativeInteger --- */
  529xpath_expr(_, nonNegativeInteger(Value), data('nonNegativeInteger', [NumberValue])) :-
  530  validate_xsd_simpleType('nonNegativeInteger', Value),
  531  atom_number(Value, NumberValue).
  532/* --- unsignedLong --- */
  533xpath_expr(_, unsignedLong(Value), data('unsignedLong', [NumberValue])) :-
  534  validate_xsd_simpleType('unsignedLong', Value),
  535  atom_number(Value, NumberValue).
  536/* --- unsignedInt --- */
  537xpath_expr(_, unsignedInt(Value), data('unsignedInt', [NumberValue])) :-
  538  validate_xsd_simpleType('unsignedInt', Value),
  539  atom_number(Value, NumberValue).
  540/* --- unsignedShort --- */
  541xpath_expr(_, unsignedShort(Value), data('unsignedShort', [NumberValue])) :-
  542  validate_xsd_simpleType('unsignedShort', Value),
  543  atom_number(Value, NumberValue).
  544/* --- unsignedByte --- */
  545xpath_expr(_, unsignedByte(Value), data('unsignedByte', [NumberValue])) :-
  546  validate_xsd_simpleType('unsignedByte', Value),
  547  atom_number(Value, NumberValue).
  548/* --- positiveInteger --- */
  549xpath_expr(_, positiveInteger(Value), data('positiveInteger', [NumberValue])) :-
  550  validate_xsd_simpleType('positiveInteger', Value),
  551  atom_number(Value, NumberValue).
  552/* --- yearMonthDuration --- */
  553xpath_expr(_, yearMonthDuration(Value), data('yearMonthDuration', DurationValue)) :-
  554  validate_xsd_simpleType('yearMonthDuration', Value),
  555  parse_duration(Value, DurationValue).
  556/* --- dayTimeDuration --- */
  557xpath_expr(_, dayTimeDuration(Value), data('dayTimeDuration', DurationValue)) :-
  558  validate_xsd_simpleType('dayTimeDuration', Value),
  559  parse_duration(Value, DurationValue).
  560/* --- untypedAtomic --- */
  561xpath_expr(_, untypedAtomic(Value), data('untypedAtomic', [Value])) :-
  562  validate_xsd_simpleType('untypedAtomic', Value).
  563
  564
  565/* ### numerics ### */
  566
  567xpath_expr(Context, numeric-add(Value1, Value2), data(Type, [ResultValue])) :-
  568  xpath_expr(Context, Value1, Inter1),
  569  xpath_expr(Context, Value2, Inter2),
  570  !,
  571  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  572  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  573  member(Type, ['decimal', 'double', 'float']),
  574  (
  575    % if one operand is nan, return it
  576    (InternalValue1 = nan; InternalValue2 = nan), ResultValue = nan;
  577    % if one operand is infinite, return it
  578    \+is_inf(InternalValue1), is_inf(InternalValue2), ResultValue = InternalValue2;
  579    is_inf(InternalValue1), \+is_inf(InternalValue2), ResultValue = InternalValue1;
  580    % if both operands are infinite, return them if they are equal, otherwise return nan
  581    is_inf(InternalValue1), is_inf(InternalValue2), (InternalValue1 = InternalValue2 -> ResultValue = InternalValue1; ResultValue = nan);
  582    % if both operands are finite, perform an arithmetic addition.
  583    \+is_inf(InternalValue1), \+is_inf(InternalValue2), ResultValue is InternalValue1 + InternalValue2
  584  ).
  585xpath_expr(Context, numeric-subtract(Value1, Value2), data(Type, [ResultValue])) :-
  586  xpath_expr(Context, Value1, Inter1),
  587  xpath_expr(Context, Value2, Inter2),
  588  !,
  589  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  590  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  591  member(Type, ['decimal', 'double', 'float']),
  592  (
  593    % if one operand is nan, return it
  594    (InternalValue1 = nan; InternalValue2 = nan), ResultValue = nan;
  595    % if the first operand is not inf and the second one is, return the second one's negation
  596    \+is_inf(InternalValue1), is_inf(InternalValue2),
  597      xpath_expr(Context, -Value2, data(Type, [ResultValue]));
  598    % if the first operand is inf and the second is not, return the first one
  599    is_inf(InternalValue1), \+is_inf(InternalValue2), ResultValue = InternalValue1;
  600    % if both operands are inf, return nan if they are equal, otherwise the appropriate inf value
  601    is_inf(InternalValue1), is_inf(InternalValue2), (InternalValue1 = InternalValue2 -> ResultValue = nan; ResultValue = InternalValue1);
  602    % if both operands are finite, perform a regular subtraction
  603    \+is_inf(InternalValue1), \+is_inf(InternalValue2), ResultValue is InternalValue1 - InternalValue2
  604  ).
  605xpath_expr(Context, numeric-multiply(Value1, Value2), data(Type, [ResultValue])) :-
  606  xpath_expr(Context, Value1, Inter1),
  607  xpath_expr(Context, Value2, Inter2),
  608  !,
  609  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  610  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  611  member(Type, ['decimal', 'double', 'float']),
  612  (
  613    % if one operand is nan, return it
  614    (InternalValue1 = nan; InternalValue2 = nan), ResultValue = nan;
  615    % if one operand is zero and the other is an infinity, return nan
  616    InternalValue1 =:= 0, is_inf(InternalValue2), ResultValue = nan;
  617    is_inf(InternalValue1), InternalValue2 =:= 0, ResultValue = nan;
  618    % if one operand is an infinity and the other one is a finite number != 0, return the effective infinity
  619    InternalValue1 =\= 0, \+is_inf(InternalValue1), is_inf(InternalValue2),
  620      (InternalValue1 < 0 ->
  621        xpath_expr(Context, -Value2, data(_, [ResultValue]))
  622        ;
  623        ResultValue = InternalValue2
  624      );
  625    is_inf(InternalValue1), InternalValue2 =\= 0, \+is_inf(InternalValue2),
  626      (InternalValue2 < 0 ->
  627        xpath_expr(Context, -Value1, data(_, [ResultValue]))
  628        ;
  629        ResultValue = InternalValue1
  630      );
  631    % if both operands are infinities, multiply them
  632    is_inf(InternalValue1), is_inf(InternalValue2), (InternalValue1 = InternalValue2 -> ResultValue = inf; ResultValue = -inf);
  633    % if no operand is an infinity, perform a regular arithmetic multiplication
  634    \+is_inf(InternalValue1), \+is_inf(InternalValue2), ResultValue is InternalValue1 * InternalValue2
  635  ).
  636xpath_expr(Context, numeric-divide(Value1, Value2), data(Type, [ResultValue])) :-
  637  xpath_expr(Context, Value1, Inter1),
  638  xpath_expr(Context, Value2, Inter2),
  639  !,
  640  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  641  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  642  member(Type, ['decimal', 'double', 'float']),
  643  (
  644    % if one operand is nan, return it
  645    (InternalValue1 = nan; InternalValue2 = nan), ResultValue = nan;
  646    % if a positive number is divided by a zero, return inf with the same sign as the zero
  647    % PROBLEM: prolog cannot decide between -0 and 0, so return inf.
  648    InternalValue1 > 0, InternalValue2 =:= 0, ResultValue = inf;
  649    % if a negative number is divided by a zero, return inf with the opposite sign as the zero
  650    % PROBLEM: prolog cannot decide between -0 and 0, so return -inf.
  651    InternalValue1 < 0, InternalValue2 =:= 0, ResultValue = -inf;
  652    % if a zero is divided by a zero, return nan
  653    InternalValue1 =:= 0, InternalValue2 =:= 0, ResultValue = nan;
  654    % if an inf is divided by an inf, return nan
  655    is_inf(InternalValue1), is_inf(InternalValue2), ResultValue = nan;
  656    % else perform a regular arithmetic division
  657    ResultValue is InternalValue1 / InternalValue2
  658  ).
  659xpath_expr(Context, numeric-integer-divide(Value1, Value2), data('integer', [ResultValue])) :-
  660  xpath_expr(Context, Value1, Inter1),
  661  xpath_expr(Context, Value2, Inter2),
  662  !,
  663  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  664  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  665  member(Type, ['decimal', 'double', 'float']),
  666  (
  667    % the first operand may not be an inf or nan
  668    \+is_inf(InternalValue1),
  669    InternalValue1 \= nan,
  670    % the second operand may not be zero or nan
  671    InternalValue2 =\= 0,
  672    InternalValue2 \= nan,
  673    (
  674      % if the second operand is an inf, return 0
  675      is_inf(InternalValue2), ResultValue = 0
  676      ;
  677      % $a idiv $b is the same as ($a div $b) cast as xs:integer (flooring)
  678      xpath_expr(Context, numeric-divide(Value1, Value2), data(_, [DivisionResultValue])),
  679      !,
  680      ResultValue is truncate(DivisionResultValue)
  681    )
  682  ).
  683xpath_expr(Context, numeric-mod(Value1, Value2), data(Type, [ResultValue])) :-
  684  xpath_expr(Context, Value1, Inter1),
  685  xpath_expr(Context, Value2, Inter2),
  686  !,
  687  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  688  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  689  member(Type, ['decimal', 'double', 'float']),
  690  (
  691    % if the type is decimal, a zero as second operator is not allowed
  692    Type \= 'decimal';
  693    InternalValue2 \= 0
  694  ),
  695  (
  696    % if at least one operand is nan, return nan
  697    (InternalValue1 = nan; InternalValue2 = nan), ResultValue = nan, !;
  698    % if the first operand is an infinity, return nan
  699    is_inf(InternalValue1), ResultValue = nan;
  700    % if the second operand is a zero, return nan
  701    InternalValue2 =:= 0, ResultValue = nan;
  702    % if the first operand is finite and the second is an infinity, return the first operand
  703    is_inf(InternalValue2), ResultValue = InternalValue1;
  704    % if the first operand is a zero and the second is finite, return the first operand
  705    InternalValue1 =:= 0, \+is_inf(InternalValue2), ResultValue = InternalValue1;
  706    % else perform regular modulo operation
  707    InternalValue1 =\= 0,
  708    InternalValue1 \= nan,
  709    \+is_inf(InternalValue1),
  710    InternalValue2 =\= 0,
  711    InternalValue2 \= nan,
  712    \+is_inf(InternalValue2),
  713    xpath_expr(Context, numeric-integer-divide(InternalValue1, InternalValue2), data(_, [Divident])),
  714    !,
  715    ResultValue is InternalValue1 - InternalValue2 * Divident
  716  ).
  717xpath_expr(Context, numeric-unary-plus(Value), data(Type, [ResultValue])) :-
  718  xpath_expr(Context, Value, data(Type, [ResultValue])),
  719  xsd_simpleType_is_a(Type, AllowedType),
  720  member(AllowedType, ['decimal', 'double', 'float']).
  721
  722xpath_expr(Context, numeric-unary-minus(Value), data(Type, [ResultValue])) :-
  723  xpath_expr(Context, Value, data(Type, [InternalValue])),
  724  xsd_simpleType_is_a(Type, AllowedType),
  725  member(AllowedType, ['decimal', 'double', 'float']),
  726  (
  727    % if the operand is nan, return it
  728    InternalValue = nan, ResultValue = InternalValue;
  729    % inf is negated separately
  730    InternalValue = inf, ResultValue = -inf;
  731    InternalValue = -inf, ResultValue = inf;
  732    % otherwise the negation is equal to 0 - value
  733    ResultValue is 0 - InternalValue
  734  ).
  735xpath_expr(Context, numeric-equal(Value1, Value2), data('boolean', [ResultValue])) :-
  736  xpath_expr(Context, Value1, Inter1),
  737  xpath_expr(Context, Value2, Inter2),
  738  !,
  739  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  740  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  741  member(Type, ['decimal', 'double', 'float']),
  742  (
  743    % +0 equals -0, but it is the same for prolog anyway
  744    % nan does not equal itself, all other values do equal themselves
  745    InternalValue1 \= nan, InternalValue1 = InternalValue2 ->
  746      ResultValue = true;
  747      ResultValue = false
  748  ).
  749xpath_expr(Context, numeric-less-than(Value1, Value2), data('boolean', [ResultValue])) :-
  750  xpath_expr(Context, Value1, Inter1),
  751  xpath_expr(Context, Value2, Inter2),
  752  !,
  753  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  754  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  755  member(Type, ['decimal', 'double', 'float']),
  756  (
  757    % positive inf is greater than everything else, except nan and itself
  758    InternalValue1 \= inf, InternalValue1 \= nan, InternalValue2 = inf;
  759    % negative inf is less than everything else, except nan and itself
  760    InternalValue1 = -inf, InternalValue2 \= nan, InternalValue2 \= -inf;
  761    % if both values are neither an inf nor nan, return true if operand1 < operand2
  762    \+is_inf(InternalValue1), \+is_inf(InternalValue2),
  763    InternalValue1 \= nan, InternalValue2 \= nan,
  764    InternalValue1 < InternalValue2
  765  ) -> ResultValue = true; ResultValue = false.
  766xpath_expr(Context, numeric-greater-than(Value1, Value2), data('boolean', [ResultValue])) :-
  767  xpath_expr(Context, Value1, Inter1),
  768  xpath_expr(Context, Value2, Inter2),
  769  !,
  770  xpath_expr_cast(Context, Inter1, data(Type, [InternalValue1])),
  771  xpath_expr_cast(Context, Inter2, data(Type, [InternalValue2])),
  772  member(Type, ['decimal', 'double', 'float']),
  773  (
  774    % positive inf is greater than everything else, except nan and itself
  775    InternalValue1 = inf, InternalValue2 \= inf, InternalValue2 \= nan;
  776    % negative inf is less than everything else, except nan and itself
  777    InternalValue1 \= nan, InternalValue1 \= -inf, InternalValue2 = -inf;
  778    % if both values are neither an inf nor nan, return true if operand1 < operand2
  779    \+is_inf(InternalValue1), \+is_inf(InternalValue2),
  780    InternalValue1 \= nan, InternalValue2 \= nan,
  781    InternalValue1 > InternalValue2
  782  ) -> ResultValue = true; ResultValue = false.
  783xpath_expr(Context, abs(Value), data(Type, [ResultValue])) :-
  784  xpath_expr(Context, Value, Inter),
  785  !,
  786  xpath_expr_cast(Context, Inter, data(Type, [InternalValue])),
  787  member(Type, ['decimal', 'double', 'float']),
  788  (
  789    % return nan for nan operands
  790    InternalValue = nan, ResultValue = nan;
  791    % return positive infinity for infinity operands
  792    is_inf(InternalValue), ResultValue = inf;
  793    % return the negation for negative values
  794    InternalValue < 0, xpath_expr(Context, numeric-unary-minus(Value), data(Type, [ResultValue]));
  795    % return the operand itself for positive operands
  796    InternalValue >= 0, ResultValue = InternalValue
  797  ).
  798xpath_expr(Context, ceiling(Value), data(Type, [ResultValue])) :-
  799  xpath_expr(Context, Value, Inter),
  800  !,
  801  xpath_expr_cast(Context, Inter, data(Type, [InternalValue])),
  802  member(Type, ['decimal', 'double', 'float']),
  803  (
  804    % return the operand itself for nan and any inf
  805    member(InternalValue, [nan, inf, -inf]), ResultValue = InternalValue;
  806    % otherwise return the ceiling of the operand
  807    ResultValue is ceiling(InternalValue)
  808  ).
  809xpath_expr(Context, floor(Value), data(Type, [ResultValue])) :-
  810  xpath_expr(Context, Value, Inter),
  811  !,
  812  xpath_expr_cast(Context, Inter, data(Type, [InternalValue])),
  813  member(Type, ['decimal', 'double', 'float']),
  814  (
  815    % return the operand itself for nan and any inf
  816    member(InternalValue, [nan, inf, -inf]), ResultValue = InternalValue;
  817    % otherwise return the floor of the operand
  818    ResultValue is floor(InternalValue)
  819  ).
  820xpath_expr(Context, round(Value), data(Type, [ResultValue])) :-
  821  xpath_expr(Context, Value, Inter),
  822  !,
  823  xpath_expr_cast(Context, Inter, data(Type, [InternalValue])),
  824  member(Type, ['decimal', 'double', 'float']),
  825  (
  826    % return the operand itself for nan and any inf
  827    member(InternalValue, [nan, inf, -inf]), ResultValue = InternalValue;
  828    % otherwise return the rounded value of the operand
  829    (
  830      xpath_expr(Context, numeric-mod(InternalValue, 1), data(_, [-0.5])) ->
  831        % -.5 is rounded towards positive infinity, so it is ceiled
  832        ResultValue is ceiling(InternalValue);
  833        ResultValue is round(InternalValue)
  834    )
  835  ).
  836xpath_expr(Context, round-half-to-even(Value), Result) :-
  837  xpath_expr(Context, round-half-to-even(Value, 0), Result).
  838xpath_expr(Context, round-half-to-even(Value, Precision), data(Type, [ResultValue])) :-
  839  xpath_expr(Context, Value, Inter),
  840  !,
  841  xpath_expr_cast(Context, Inter, data(Type, [InternalValue])),
  842  member(Type, ['decimal', 'double', 'float']),
  843  (
  844    % return the operand itself for nan and any inf
  845    member(InternalValue, [nan, inf, -inf]), ResultValue = InternalValue
  846    ;
  847    % otherwise return the rounded value of the operand with respect to the precision
  848    % apply precision
  849    PrecisionedValue is InternalValue * 10 ** Precision,
  850    (
  851      xpath_expr(Context, numeric-mod(PrecisionedValue, 1), data(_, [Mod])),
  852      member(Mod, [0.5, -0.5]) ->
  853        % -.5 is rounded towards the adjacent even number
  854        Ceil is ceiling(PrecisionedValue),
  855        Floor is floor(PrecisionedValue),
  856        (
  857          Ceil mod 2 =:= 0 ->
  858            PrecisionedResultValue = Ceil;
  859            PrecisionedResultValue = Floor
  860        )
  861        ;
  862        % otherwise it is rounded as usual
  863        PrecisionedResultValue is round(PrecisionedValue)
  864    ),
  865    % reverse precision
  866    ResultValue is PrecisionedResultValue * 10 ** (0-Precision)
  867  ).
  868
  869
  870/* ### strings ### */
  871xpath_expr(Context, IN, Result) :-
  872  IN =.. [concat|Tail],
  873  string_concat(Tail, ResultString),
  874  atom_string(ResultAtom, ResultString),
  875  xpath_expr(Context, string(ResultAtom), Result).
  876xpath_expr(Context, matches(Value, Pattern), Result) :-
  877  xpath_expr(Context, matches(Value, Pattern, ''), Result).
  878xpath_expr(Context, matches(Value, Pattern, Flags), data('boolean', [ResultValue])) :-
  879  % TODO: add support for providing nodes as the value
  880  xpath_expr(Context, Value, data(_, [InternalValue])),
  881  !,
  882  (
  883    InternalValue =~ Pattern/Flags ->
  884      ResultValue = true;
  885      ResultValue = false
  886  ).
  887
  888
  889/* ### anyURI ### */
  890xpath_expr(Context, resolve-uri(Relative), Result) :-
  891  % TODO: replace with fn:static-base-uri when implemented
  892  xpath_expr(Context, resolve-uri(Relative, 'http://localhost'), Result).
  893xpath_expr(Context, resolve-uri(Relative, Base), data('anyURI', [ResultValue])) :-
  894  xpath_expr(Context, Relative, data(_, [InternalRelativeValue])),
  895  xpath_expr(Context, Base, data(_, [InternalBaseValue])),
  896  !,
  897  (
  898    % TODO: return Relative, if it is the empty sequence
  899    xpath_expr(Context, matches(InternalRelativeValue,'^[a-z]+:'), data(_, [true])) ->
  900      ResultValue = InternalRelativeValue
  901      ;
  902      xpath_expr(Context, matches(InternalBaseValue,'^[a-z]+:'), data(_, [true])),
  903      parse_url(InternalBaseValue, UrlList),
  904      (
  905        member(protocol(Protocol), UrlList) ->
  906          BaseUrlProtocol = Protocol
  907          ;
  908          BaseUrlProtocol = ''
  909      ),
  910      (
  911        member(host(Host), UrlList) ->
  912          atomic_list_concat([BaseUrlProtocol, Host], ://, BaseUrlHost)
  913          ;
  914          BaseUrlHost = BaseUrlProtocol
  915      ),
  916      (
  917        member(port(Port), UrlList) ->
  918          atomic_list_concat([BaseUrlHost, Port], :, BaseUrl)
  919          ;
  920          BaseUrl = BaseUrlHost
  921      ),
  922      (
  923        InternalRelativeValue = '' ->
  924          ResultValue = BaseUrl
  925          ;
  926          atomic_list_concat([BaseUrl, InternalRelativeValue], /, ResultValue)
  927      )
  928  ).
  929
  930
  931
  932/* ~~~ Parsing ~~~ */
E.g. an unsignedLong with value 3 can be casted to a float with value 3, although the type unsignedLong is no direct descendant of type float, but it can be casted to it due to its value space. /
  942xpath_expr_cast(Context, data(_, [InternalValue]), Result) :-
  943  number(InternalValue),
  944  xpath_expr(Context, InternalValue, Result).
  945xpath_expr_cast(Context, data(_, [-inf]), Result) :-
  946  xpath_expr(Context, '-INF', Result).
  947xpath_expr_cast(Context, data(_, [inf]), Result) :-
  948  xpath_expr(Context, 'INF', Result).
  949xpath_expr_cast(Context, data(_, [nan]), Result) :-
  950  xpath_expr(Context, 'NaN', Result).
  951xpath_expr_cast(Context, data(_, [InternalValue]), Result) :-
  952  \+number(InternalValue),
  953  xpath_expr(Context, InternalValue, Result).
  954
  955parse_duration(Value, Result) :-
  956  atom_string(Value, ValueString),
  957  split_string(ValueString, 'P', '', PSplit),
  958  (
  959    PSplit = [Sign, PSplitR], Sign = '-';
  960    PSplit = [_, PSplitR], Sign = '+'
  961  ),
  962  split_string(PSplitR, 'Y', '', YSplit),
  963  (
  964    YSplit = [YSplitR], Years = 0;
  965    YSplit = [YearsTMP, YSplitR], number_string(Years, YearsTMP)
  966  ),
  967  split_string(YSplitR, 'M', '', MoSplit),
  968  (
  969    MoSplit = [MoSplitR], Months = 0;
  970    MoSplit = [MonthsTMP, MoSplitR], \+sub_string(MonthsTMP, _, _, _, 'T'), number_string(Months, MonthsTMP);
  971    MoSplit = [MoSplitR0, MoSplitR1], sub_string(MoSplitR0, _, _, _, 'T'), string_concat(MoSplitR0, 'M', TMP), string_concat(TMP, MoSplitR1, MoSplitR), Months = 0;
  972    MoSplit = [MonthsTMP, MoSplitR0, MoSplitR1], string_concat(MoSplitR0, 'M', TMP), string_concat(TMP, MoSplitR1, MoSplitR), number_string(Months, MonthsTMP)
  973  ),
  974  split_string(MoSplitR, 'D', '', DSplit),
  975  (
  976    DSplit = [DSplitR], Days = 0;
  977    DSplit = [DaysTMP, DSplitR], number_string(Days, DaysTMP)
  978  ),
  979  split_string(DSplitR, 'T', '', TSplit),
  980  (
  981    TSplit = [TSplitR];
  982    TSplit = [_, TSplitR]
  983  ),
  984  split_string(TSplitR, 'H', '', HSplit),
  985  (
  986    HSplit = [HSplitR], Hours = 0;
  987    HSplit = [HoursTMP, HSplitR], number_string(Hours, HoursTMP)
  988  ),
  989  split_string(HSplitR, 'M', '', MiSplit),
  990  (
  991    MiSplit = [MiSplitR], Minutes = 0;
  992    MiSplit = [MinutesTMP, MiSplitR], number_string(Minutes, MinutesTMP)
  993  ),
  994  split_string(MiSplitR, 'S', '', SSplit),
  995  (
  996    SSplit = [_], Seconds = 0;
  997    SSplit = [SecondsTMP, _], number_string(Seconds, SecondsTMP)
  998  ),
  999  normalize_duration(
 1000    data('duration', [Sign, Years, Months, Days, Hours, Minutes, Seconds]),
 1001    data('duration', Result)
 1002  ).
 1003
 1004parse_float(Value, nan) :-
 1005  Value =~ '^(\\+|-)?NaN$'.
 1006parse_float(Value, inf) :-
 1007  Value =~ '^\\+?INF$'.
 1008parse_float(Value, -inf) :-
 1009  Value =~ '^-INF$'.
 1010parse_float(Value, ResultValue) :-
 1011  atom_number(Value, ResultValue).
 1012
 1013
 1014/* ~~~ Normalization ~~~ */
 1015
 1016normalize_duration(
 1017  data('duration', [USign, UYears, UMonths, UDays, UHours, UMinutes, USeconds]),
 1018  data('duration', [NSign, NYears, NMonths, NDays, NHours, NMinutes, NSeconds])) :-
 1019  % 0 =< Seconds < 60
 1020  % seconds are (in constrast to the other values) given as float
 1021  number_string(USeconds, SUSeconds),
 1022  split_string(SUSeconds, '.', '', LUSeconds),
 1023  (
 1024    LUSeconds = [SIntegerSeconds], number_string(IntegerSeconds, SIntegerSeconds), NSeconds is IntegerSeconds mod 60;
 1025    LUSeconds = [SIntegerSeconds,SFractionalSeconds], number_string(IntegerSeconds, SIntegerSeconds),
 1026      TSeconds is IntegerSeconds mod 60, number_string(TSeconds, STSeconds),
 1027      atomic_list_concat([STSeconds,SFractionalSeconds], '.', ANSeconds), atom_string(ANSeconds, SNSeconds), number_string(NSeconds, SNSeconds)
 1028  ),
 1029  MinutesDiv is IntegerSeconds div 60,
 1030  % 0 =< Minutes < 60
 1031  MinutesTMP is UMinutes + MinutesDiv,
 1032  HoursDiv is MinutesTMP div 60, NMinutes is MinutesTMP mod 60,
 1033  % 0 =< Hours < 24
 1034  HoursTMP is UHours + HoursDiv,
 1035  DaysDiv is HoursTMP div 24, NHours is HoursTMP mod 24,
 1036  % 0 =< Days < 31
 1037  DaysTMP is UDays + DaysDiv,
 1038  MonthsDiv is DaysTMP div 31, NDays is DaysTMP mod 31,
 1039  % 0 =< Months < 12
 1040  MonthsTMP is UMonths + MonthsDiv,
 1041  YearsDiv is MonthsTMP div 12, NMonths is MonthsTMP mod 12,
 1042  % Years have no restrictions
 1043  YearsTMP is UYears + YearsDiv,
 1044  (
 1045    % negative year values lead to a flipping of the sign
 1046    YearsTMP < 0 ->
 1047      (
 1048        USign = '+' ->
 1049          NSign = '-';
 1050          NSign = '+'
 1051      );
 1052      (
 1053        % durations of 0 are always positive
 1054        UYears = 0, UMonths = 0, UDays = 0, UHours = 0, UMinutes = 0, USeconds = 0 ->
 1055          NSign = '+';
 1056          NSign = USign
 1057      )
 1058  ),
 1059  NYears is abs(YearsTMP).
 1060
 1061
 1062/* ~~~ Helping Functions ~~~ */
 1063/* --- checks if data structure is valid ("true / not empty ...") --- */
 1064isValid(data(T, R)) :-
 1065  T \= 'boolean'; R = [true].
 1066/* --- recursive string concatenation function --- */
 1067string_concat([], "").
 1068string_concat([H|T], OUT) :-
 1069  string_concat(T, IN),
 1070  !,
 1071  xpath_expr(_, H, data(_, [InternalValue])),
 1072  !,
 1073  string_concat(InternalValue, IN, OUT).
 1074/* --- checks if the given value is a positive or negative infinity --- */
 1075is_inf(V) :-
 1076  V = inf.
 1077is_inf(V) :-
 1078  V = -inf.
 1079/* --- convert time zone parts to compact time zone offset --- */
 1080timezone_offset('-', TimeZoneHour, TimeZoneMinute, TimeZoneOffset) :-
 1081  TimeZoneOffset is (-1 * (60 * TimeZoneHour + TimeZoneMinute)).
 1082timezone_offset('+', TimeZoneHour, TimeZoneMinute, TimeZoneOffset) :-
 1083  TimeZoneOffset is (60 * TimeZoneHour + TimeZoneMinute).
 1084/* --- splits RestTimeZoneTMP into RestTMP (e.g. MonthTMP - '02') and TimeZoneTMP (e.g. '-13:30') --- */
 1085timezone_split(RestTMP, TimeZoneTMP, RestTimeZoneTMP) :-
 1086  % UTC TC
 1087  split_string(RestTimeZoneTMP, 'Z', '', ZSplit), ZSplit = [RestTMP, _], TimeZoneTMP = '00:00'.
 1088timezone_split(RestTMP, TimeZoneTMP, RestTimeZoneTMP) :-
 1089  % positive TC
 1090  split_string(RestTimeZoneTMP, '+', '', PlusSplit), PlusSplit = [RestTMP, TimeZoneTMP].
 1091timezone_split(RestTMP, TimeZoneTMP, RestTimeZoneTMP) :-
 1092  % no TZ
 1093  \+sub_string(RestTimeZoneTMP, _, _, _, 'Z'), \+sub_string(RestTimeZoneTMP, _, _, _, '+'),
 1094  RestTMP = RestTimeZoneTMP, TimeZoneTMP = '00:00'