1:- module(flatten, [
    2  xml_flatten/2,
    3  node/4,
    4  node_attribute/4,
    5  text_node/3,
    6  remove_file/1
    7]).    8
    9:- use_module(library(sgml)).   10:- use_module(library(xsd/xsd_helper)).   11
   12/*
   13  node/4
   14  node(File_ID,ID,Namespace,Node_Type_Without_NS)
   15
   16  node_attribute/4
   17  node_attribute(File_ID,ID,Attribute,Value)
   18
   19  text_node/3
   20  text_node(File_ID,ID,Node)
   21
   22  file_id/1
   23  file_id(File_ID)
   24
   25*/
   26:- dynamic node/4, node_attribute/4, text_node/3, file_id/1.   27
   28
   29/*
   30  parse_options/1
   31  parse_options(List_Of_Options)
   32
   33  Define a `List_Of_Options` for parse a XML file by use
   34    of the built-in `load_structure/3`.
   35*/
   36parse_options([
   37  % read in XML file with handling of namespaces in mind
   38  dialect(xmlns),
   39
   40  % remove spaces before and after tags, ignore whitespace-only elements
   41  space(remove),
   42
   43  % quiet namespace handling
   44  % if a node has a namespace (like `xs` in `xs:element`) which hasn't
   45  %   been declared via `xmlns:xs="...URI..."` this will suppress the
   46  %   error message
   47  %xml_no_ns(quiet),
   48
   49  % create ns(xs, uri)
   50  keep_prefix(true)
   51]).
Load a XML file specified by Input and return the DOM tree in XML.

Examples: load_xml(stream(user_input),XML). %% binds XML to the DOM tree */

   64load_xml(Input,XML) :-
   65  parse_options(Parse_Options),
   66  load_structure(Input,XML,Parse_Options).
   67
   68
   69/*
   70  xml_flatten/2
   71  xml_flatten(Input, File_ID)
   72
   73  Load a XML file specified by `Input` and flatten
   74    its DOM tree. This will result in multiple `node/4`, `node_attribute/4`
   75    and `text_node/3` facts.
   76  `File_ID` can be user-defined, otherwise will be set to the next unused integer.
   77
   78  Examples:
   79    xml_flatten(string(input_as_atom),File_ID).
   80    xml_flatten(path_to_file,File_ID)
   81*/
   82xml_flatten(Input, File_ID) :-
   83  load_xml(Input,XML),
   84  root_id(Root_ID),
   85  register_file_id(File_ID),
   86  xml_flatten_nodes(File_ID,Root_ID,0,XML),
   87  !.
   88
   89
   90/*
   91  root_id/1
   92  root_id(ID)
   93
   94  Hold the default ID for the root element
   95*/
   96root_id([]).
   97
   98
   99/*
  100  new_id/3
  101  new_id(Parents_ID,Position,New_ID)
  102
  103  Create a new ID by the parent's ID and the element's
  104  position.
  105*/
  106new_id(Base_ID,Pos,ID) :-
  107  ID = [Pos|Base_ID].
  108
  109
  110/*
  111  register_file_id/2
  112  register_file_id(+Input, ?File_ID)
  113
  114  Register new File_ID (filename)
  115*/
  116register_file_id(File_ID) :-
  117  var(File_ID),
  118  % generate an (ascending) integer as ID ... (Starts at '1', corresponds to the TAP numbering)
  119  length(_,File_ID),
  120  File_ID > 0,
  121  % ... which isn't used yet.
  122  \+file_id(File_ID),!,
  123  assertz(file_id(File_ID)).
  124register_file_id(File_ID) :-
  125  \+var(File_ID),
  126  % user chosen ID mustn't be already in use by another file
  127  (\+file_id(File_ID),!; throw("File_ID is already in use.")),
  128  assertz(file_id(File_ID)).
  129
  130
  131/*
  132  xml_flatten_nodes/4
  133
  134  Flatten a XML DOM tree by creating `node/6`,
  135    `attribute/4`
  136    and `text_node/4` facts.
  137*/
  138xml_flatten_nodes(_File_ID,_Base_ID,_Pos,[]).
  139
  140xml_flatten_nodes(File_ID,Base_ID,Pos,[Node|Nodes]) :-
  141  Node = element(Node_Type,Node_Attributes,Child_Nodes),
  142  new_id(Base_ID,Pos,ID),
  143  namespace(Node_Type,Namespace,Node_Type_Without_NS),
  144  % flatten the node's attributes
  145  xml_flatten_attributes(File_ID,ID,Node_Attributes),
  146  assertz(node(File_ID,ID,Namespace,Node_Type_Without_NS)),
  147  % flatten sibling nodes
  148  Next_Pos is Pos+1,
  149  xml_flatten_nodes(File_ID,Base_ID,Next_Pos,Nodes),
  150  % flatten all children
  151  xml_flatten_nodes(File_ID,ID,0,Child_Nodes)
  151.
  152
  153xml_flatten_nodes(File_ID,Base_ID,Pos,[Node|Nodes]) :-
  154  atom(Node),
  155  new_id(Base_ID,Pos,ID),
  156  assertz(text_node(File_ID,ID,Node)),
  157  % flatten sibling nodes
  158  Next_Pos is Pos+1,
  159  xml_flatten_nodes(File_ID,Base_ID,Next_Pos,Nodes)
  159.
  160
  161
  162/*
  163  xml_flatten_attributes/3
  164  xml_flatten_attributes(File_ID,ID,List_Of_Attributes)
  165
  166  Flatten a `List_Of_Attributes` of the form
  167    [attribute1=valu1,attribute2=value2,...]
  168    by creating a `node_attribute/4` facts.
  169
  170  Examples:
  171    xml_flatten_attributes(filename,[0],[minOccurs='1'])
  172      ==> node_attribute(filename,[0],minOccurs,'1')
  173*/
  174xml_flatten_attributes(_File_ID,_ID,[]).
  175xml_flatten_attributes(File_ID,ID,[Attribute=Value|List_Of_Attributes]) :-
  176  assertz(node_attribute(File_ID,ID,Attribute,Value)),
  177  xml_flatten_attributes(File_ID,ID,List_Of_Attributes).
Deletes asserted node/5, node_attribute/4, text_node/3 for given File_ID from database. Deletes nodes for every asserted file, if File_ID left empty. */
  186remove_file(File_ID) :-
  187  retractall(node(File_ID,_,_,_)),
  188  retractall(text_node(File_ID,_,_)),
  189  retractall(node_attribute(File_ID,_,_,_)),
  190  retractall(file_id(File_ID))