1:- module(xsd_helper, [
    2  /* ### node type translation ### */
    3  node_type/3,
    4  /* ### node relations ### */
    5  /* --- parent-child --- */
    6  parent/2,
    7  split_id/3,
    8  child/3,
    9  get_children/3,
   10  get_n_children/4,
   11  get_nth_child/4,
   12  count_children/3,
   13  /* --- sibling --- */
   14  sibling/3,
   15  next_sibling/3,
   16  last_sibling/3,
   17  count_remaining_siblings/3,
   18  get_n_siblings/4,
   19  get_nth_sibling/4,
   20  /* --- ancestor/descendant --- */
   21  descendant/3,
   22  descendant_or_self/3,
   23  /* ### namespace handling ### */
   24  resolve_namespace/4,
   25  namespace/3
   26]).   27
   28:- use_module(library(xsd/flatten)).   29
   30/*
   31  HELPER
   32  Various predicates for data traversal, receiving children and siblings and namespace handling using nodes created by `flatten_xml/2` inside the Module `xml_flatten`
   33
   34  parent(ID, Parent_ID)
   35  child(File,ID,Child_ID)
   36  sibling(File,ID,Sibling_ID)
   37
   38  ?- child("test/schema.xsd", [0], [0,0]).
   39  true.
   40  ?- child("test/schema.xsd", [0,0], _).
   41  false.
   42*/
   43
   44
   45/* ### node type translation ### */
   46
   47node_type(File, ID, node) :-
   48  node(File, ID, _NS, _Name).
   49node_type(File, ID, text_node) :-
   50  text_node(File, ID, _).
   51
   52
   53/* ### node relations ### */
   54
   55/* --- parent-child --- */
   56
   57parent(ID, Parent_ID) :-
   58  split_id(ID, _, Parent_ID).
   59split_id(ID, Pos, Parent_ID) :-
   60  ID = [Pos|Parent_ID].
   61
   62child(File, ID, Child_ID) :-
   63  Child_ID = [_|ID],
   64  node_type(File, Child_ID, _).
   65
   66get_children(File, ID, Children_IDs) :-
   67  findall(Child_ID, child(File, ID, Child_ID), Children_IDs).
   68
   69get_n_children(File, ID, N, Children_IDs) :-
   70  get_children(File, ID, All_Children_IDs),
   71  length(Children_IDs, N),
   72  append(Children_IDs, _, All_Children_IDs).
   77get_nth_child(File, ID, Nth, Child_ID) :-
   78  Nth0 is Nth - 1,
   79  Nth0 >= 0,
   80  split_id(Child_ID, Nth0, ID),
   81  node_type(File, Child_ID, _).
   82
   83count_children(File, ID, N_Children) :-
   84  get_children(File, ID, Children),
   85  length(Children, N_Children).
   86
   87/* --- sibling --- */
   88
   89sibling(File, ID, Sibling_ID) :-
   90  parent(ID, Parent_ID),
   91  child(File, Parent_ID, Sibling_ID),
   92  ID \= Sibling_ID.
   93
   94next_sibling(File, ID, Next_Sibling_ID) :-
   95  split_id(ID, Pos, Parent_ID),
   96  Next is Pos + 1,
   97  split_id(Next_Sibling_ID, Next, Parent_ID),
   98  child(File, Parent_ID, Next_Sibling_ID).
   99
  100last_sibling(File, ID, Last_Sibling_ID) :-
  101  parent(ID, Parent_ID),
  102  child(File, Parent_ID, Last_Sibling_ID),
  103  \+next_sibling(File, Last_Sibling_ID, _).
  108count_remaining_siblings(File, ID, Remaining) :-
  109  split_id(ID, Pos0, Parent_ID),
  110  last_sibling(File, ID, Last_ID),
  111  split_id(Last_ID, Pos1, Parent_ID),
  112  Remaining is Pos1 - Pos0 + 1.
  113
  114get_n_siblings(_File, _ID, 0, []).
  115get_n_siblings(_File, ID, 1, [ID]).
  116get_n_siblings(File, ID, N, [ID|Sibling_IDs]) :-
  117  count_remaining_siblings(File, ID, Remaining),
  118  between(2, Remaining, N),
  119  split_id(ID, Pos, Parent_ID),
  120  Pos0 is Pos + 1,
  121  N0 is N - 1,
  122  split_id(ID0, Pos0, Parent_ID),
  123  node_type(File, ID0, _),
  124  get_n_siblings(File, ID0, N0, Sibling_IDs).
  132get_nth_sibling(D_File, ID, Nth, Nth_ID) :-
  133  split_id(ID, Pos, Parent_ID),
  134  N is Pos + Nth - 1,
  135  split_id(Nth_ID, N, Parent_ID),
  136  node_type(D_File, Nth_ID, _).
  137
  138/* --- ancestor/descendant --- */
  139
  140descendant(File, ID, Desc_ID) :-
  141  child(File, ID, Desc_ID).
  142descendant(File, ID, Desc_ID) :-
  143  child(File, Inter_ID, Desc_ID),
  144  descendant(File, ID, Inter_ID).
  145
  146descendant_or_self(File, ID, ID) :-
  147  node(File, ID, _NS, _Name).
  148descendant_or_self(File, ID, Desc_ID) :-
  149  descendant(File, ID, Desc_ID).
  150
  151
  152/* ### namespace handling ### */
  159resolve_namespace(File, ID, Prefix, URI) :-
  160  node(File, ID, ns(Prefix, URI), _),
  161  !.
  162resolve_namespace(File, ID, Prefix, URI) :-
  163  node_attribute(File, ID, xmlns:Prefix, URI),
  164  !.
  165resolve_namespace(File, ID, '', URI) :-
  166  node_attribute(File, ID, xmlns, URI),
  167  !.
  168resolve_namespace(File, ID, Prefix, URI) :-
  169  parent(ID, Parent_ID),
  170  resolve_namespace(File, Parent_ID, Prefix, URI).
Predicate to split a Name into its Namespace and Name_Without_Namespace.

Examples: namespace(xs:element,xs,element). namespace(element,'',element). /

  182namespace(Name,Namespace,Name_Without_NS) :-
  183  Name = Namespace:Name_Without_NS,
  184  !.
  185% Namespace in 'single:quotes'
  186namespace(Name_String,Namespace,Name_Without_NS) :-
  187  atom(Name_String),
  188  atomic_list_concat([Namespace,Name_Without_NS], ':', Name_String),
  189  !.
  190% no namespace present
  191namespace(Name,'',Name)