1:- module(dia,
    2	  [
    3	   load_diagram/1,    % +File
    4	   load_diagrams/1,   % +ListOfFiles
    5	   close_diagram/1,   % +File
    6	   close_diagrams/1,  % +ListOfFiles
    7	   close_all_diagrams/0,
    8	   import_diagram/1,  % File
    9
   10	   write_facts/2, % File ListOfOptions
   11	   write_facts/1, % File
   12	   write_facts/0,
   13
   14	   assert_facts/2, % ModuleIdentifier ListOfOptions
   15	   assert_facts/1, % ModuleIdentifier
   16	   assert_facts/0,
   17	   erase_facts/1,  % ModuleIdentifier
   18	   copy_facts/2,   % ModuleIdentifier(s) ModuleIdentifier
   19
   20	   import_facts/0,
   21	   import_facts/1, % ModuleIdentifier
   22
   23	   clauses/1, % -List
   24	   predicates_list/1 % -List
   25	  ]
   26	 ).

A prolog-interface to dia-uml-files

This module provides predicates to load .dia files containing UML diagrams and make queries against it and/or save the data contained in the form of prolog-source files.

Example

  load_diagram('Diagram.dia'). % Load the diagram
  import_facts.                % Tell prolog to work directly on the
                               % data - see import_facts/1.
  class_name(X, 'Class').      %  A Query

Example using a module:

load_diagram('Diagram.dia').     % Load the diagram
assert_facts(diagram, [export]). % Assert all facts into module
                                 % 'diagram' and mark them as exports.
diagram:association(A).          % A Query to the asserted data.
import_facts(diagram). % Delegate queries to the diagram-module
class_operation(Class, Op) % Queries can now be made without prefix

Example writing to a file

load_diagrams(['diagram1.dia','diagram2.dia']). % Load two diagrams
write_facts('d.pl').                % Write all facts to d.pl
write_facts('mod.pl',[module, export]). % Like above but
                                        % generates a module and exports
                                        % the facts
author
- Heiko Lewin
license
- GPL
To be done
-
  • A package_contains predicate
  • Constraints on relationships
  • Compressed diagrams
  • NOTES
    • This works with official dia-releases (at least with 0.97.2 as avaiable from http://live.gnome.org/Dia ) but contains some query predicates official dia-releases have no diagram elements (yet) that correspond to them (branch-names, association-stereotypes and the containment-relation ). These are defined here as those are more or less part of the UML-standard and likely to be in one of the next dia-releases.
    • Though exporting any rules or facts for querying diagram data directly may seem clumsy this way clauses holding the diagram data can be merged into the user-module from different source modules and be worked with there without name-clashes.
    • This does not really follow the UML- or XMI-standards in how diagram data is represented but is close to the layout of dia-files.
    • This currently only works with SWI-Prolog without further extensions when it comes down to free software. GNU-Prolog is missing a xml-parser and the code_type/2 relation. This has not been tested with commerical Prolog-systems.

    */

   88:- use_module(library(sgml)).
   89:- dynamic(model/2).
 predicates_list(-List)
Unified List with a list of Predicate/Arity tuples that define the predicates that are used to make queries against the diagram-data.

The predicate names should be self-explanatory. The predicates that take one argument are used to query for existence and unify their argument with a term representing the model-element, all other predicates unify the first argument with such a term and the second with the thing asked for.

existential_query(?ElementOrHandle)
query_for_an_attribute(?ElementOrHandle, ?VariableOrTerm)
NOTE: The first argument can either be an atomic identifier ( in cases facts got asserted ) or an xml-element if working directly on the xml-file, so best is to look at it as black box.
  110predicates_list(
  111    [
  112    association/1,
  113    association_direction/2,
  114    association_id/2,
  115    association_name/2,
  116    association_from_arrow/2,
  117    association_from_id/2,
  118    association_from_multiplicity/2,
  119    association_from_role/2,
  120    association_from_visibility/2,
  121    association_stereotype/2,
  122    association_text/2,
  123    association_to_arrow/2,
  124    association_to_id/2,
  125    association_to_multiplicity/2,
  126    association_to_role/2,
  127    association_to_visibility/2,
  128    association_type/2,
  129
  130    attribute/1,
  131    attribute_abstract/2,
  132    attribute_comment/2,
  133    attribute_id/2,
  134    attribute_name/2,
  135    attribute_static/2,
  136    attribute_type/2,
  137    attribute_value/2,
  138    attribute_visibility/2,
  139    attribute_inherited/2,
  140
  141    branch/1,
  142    branch_id/2,
  143    branch_name/2,
  144    branch_stereotype/2,
  145
  146    constraint/1,
  147    constraint_id/2,
  148    constraint_what/2,
  149    constraint_expression/2,
  150
  151    class/1,
  152    class_abstract/2,
  153    class_attribute/2,
  154    class_attributes/2,
  155    class_comment/2,
  156    class_id/2,
  157    class_name/2,
  158    class_operation/2,
  159    class_operations/2,
  160    class_stereotype/2,
  161    class_template/2,
  162    class_template_parameter/2,
  163    class_template_parameters/2,
  164
  165    operation/1,
  166    operation_abstract/2,
  167    operation_comment/2,
  168    operation_id/2,
  169    operation_inheritance/2,
  170    operation_name/2,
  171    operation_parameter/2,
  172    operation_parameters/2,
  173    operation_static/2,
  174    operation_stereotype/2,
  175    operation_type/2,
  176    operation_visibility/2,
  177    operation_query/2,
  178
  179    package/1,
  180    package_id/2,
  181    package_name/2,
  182    package_stereotype/2,
  183
  184    parameter/1,
  185    parameter_comment/2,
  186    parameter_direction/2,
  187    parameter_id/2,
  188    parameter_name/2,
  189    parameter_type/2,
  190    parameter_value/2,
  191
  192    template_parameter/1,
  193    template_parameter_id/2,
  194    template_parameter_name/2,
  195    template_parameter_type/2
  196
  197    ]).
  198
  199element_type(element(Tag, _, _), Tag).
  200element_attributes(element(_,Attributes,_), Attributes).
  201element_attribute(Element, Attribute) :-
  202	element_attributes(Element, Attributes),
  203	member(Attribute, Attributes),
  204	Attribute = (_=_).
  205element_content(element(_,_,Content), Content).
  206element_element(Element, ContainedElement) :-
  207	ContainedElement = element(_,_,_),
  208	element_content(Element, Content),
  209	member(ContainedElement, Content).
  210
  211filespec(FileSpec, Extension, Base, AbsoluteFilename) :-
  212	nonvar(FileSpec),
  213	nonvar(Extension),
  214	file_base_name(FileSpec, FilePart),
  215	(   atom_concat(Base, Extension, FilePart)
  216	->  Filename = FileSpec
  217	;   Base = FilePart,
  218	    atom_concat(FileSpec, Extension, Filename)),
  219	absolute_file_name(Filename, AbsoluteFilename).
 load_diagrams(+ListOfFiles:list)
Calls load_diagram/1 for each file in ListOfFiles.
  224load_diagrams([]).
  225load_diagrams([M|L]) :- load_diagram(M), load_diagrams(L).
 load_diagram(+FileSpec)
Loads the diagram contents of FileSpec which has to be an uncompressed .dia file and asserts the raw data in the dia-module.
  232load_diagram(FileSpec) :-
  233	filespec(FileSpec, '.dia', _, File),
  234	load_xml_file(File, [M]),
  235	retractall(model(File,_)),
  236	assert(model(File,M)).
 close_diagram(+FileSpec)
Retracts the diagram data loaded from FileSpec from the dia-module.
  242close_diagram(N) :-
  243	filespec(N, '.dia', _, File),
  244	retractall(model(File, _)).
 close_diagrams(+ListOfFiles)
Calls close_diagram/1 for each member of ListOfFiles.
  249close_diagrams(L) :- foreach(member(X, L), close_diagram(X)).
 close_all_diagrams
Retracts all diagram-data from the dia-module.
  254close_all_diagrams :- retractall(model(_,_)).
  255
  256model(M) :- model(_,M).
  257
  258model_id(M, I) :-
  259	model(_, M),
  260	term_hash(M, I).
  261
  262dia_string(NameElement, Name) :-
  263	element_element(NameElement, StringElement),
  264	element_type(StringElement, 'dia:string'),
  265	element_content(StringElement, [DecName]),
  266/*
  267	append("#", NameCodes, HlfDecName),
  268	append(HlfDecName, "#", DecName),
  269	atom_codes(Name, NameCodes). */

  270
  271	atom_concat('#', HlfDecName, DecName),
  272	atom_concat(Name, '#', HlfDecName).
  273
  274
  275element_string(Elem, String) :- dia_string(Elem, String).
  276element_boolean(Elem, Boolean) :-
  277	element_element(Elem, ValElem),
  278	element_type(ValElem, 'dia:boolean'),
  279	element_attribute(ValElem, val=Boolean).
  280element_enum(Elem, Enum) :-
  281	element_element(Elem, ValElem),
  282	element_type(ValElem, 'dia:enum'),
  283	element_attribute(ValElem, val=Enum).
  284
  285element_string_attribute(Elem, AttrName, String) :-
  286	element_element(Elem, Elem2),
  287	element_type(Elem2, 'dia:attribute'),
  288	element_attribute(Elem2, name=AttrName),
  289	element_string(Elem2, String).
  290element_boolean_attribute(Elem, AttrName, Boolean) :-
  291	element_element(Elem, Elem2),
  292	element_type(Elem2, 'dia:attribute'),
  293	element_attribute(Elem2, name=AttrName),
  294	element_boolean(Elem2, Boolean).
  295element_enum_attribute(Elem, AttrName, Enum) :-
  296	element_element(Elem, Elem2),
  297	element_type(Elem2, 'dia:attribute'),
  298	element_attribute(Elem2, name=AttrName),
  299	element_enum(Elem2, Enum).
  300
  301
  302dia_visibility('0', public).
  303dia_visibility('1', private).
  304dia_visibility('2', protected).
  305dia_visibility('3', implementation).
  306
  307dia_inheritance('2', final).
  308dia_inheritance('1', virtual).
  309dia_inheritance('0', abstract).
  310
  311dia_parameter_kind('0', undefined).
  312dia_parameter_kind('1', in).
  313dia_parameter_kind('2', out).
  314dia_parameter_kind('3', inout).
  315
  316dia_direction('0', undefined).
  317dia_direction('1', a_to_b).
  318dia_direction('2', b_to_a).
  319
  320dia_assoc_type('0', association).
  321dia_assoc_type('1', aggregation).
  322dia_assoc_type('2', composition).
  323
  324
  325element_hash(Element, Hash) :- term_hash(Element, Hash).
  326
  327dia_layer(Diagram, LayerElement) :-
  328	model(Diagram),
  329	element_element(Diagram, LayerElement),
  330	element_type(LayerElement, 'dia:layer').
  331
  332dia_layer(L) :- dia_layer(_,L).
  333
  334class(Model, C) :-
  335	dia_layer(Model, L),
  336	element_element(L, C),
  337	element_type(C, 'dia:object'),
  338	element_attribute(C, type='UML - Class').
  339
  340class(C) :- class(_, C).
  341
  342class_id(Class, Id) :-
  343	class(Model, Class),
  344	element_attribute(Class, id=ClassId),
  345	model_id(Model, ModelId),
  346	atom_concat(ModelId, ClassId, Id).
  347
  348class_name(Class, Name) :-
  349	class(Class),
  350	element_string_attribute(Class, name, Name).
  351
  352class_stereotype(Class, Stereo) :-
  353	class(Class),
  354	element_string_attribute(Class, stereotype, Stereo).
  355
  356class_comment(Class, Comment) :-
  357	class(Class),
  358	element_string_attribute(Class, comment, Comment).
  359
  360class_abstract(Class, Abstract) :-
  361	class(Class),
  362	element_boolean_attribute(Class, abstract, Abstract).
  363
  364class_template(Class, Abstract) :-
  365	class(Class),
  366	element_boolean_attribute(Class, template, Abstract).
  367
  368class_template_parameters(Class, Abstract) :-
  369	class(Class),
  370	element_element(Class, Abstract),
  371	element_type(Abstract, 'dia:attribute'),
  372	element_attribute(Abstract, name=templates).
  373
  374class_template_parameter(Class, Abstract) :-
  375	class_template_parameters(Class, P),
  376	element_element(P, Abstract),
  377	element_type(Abstract, 'dia:composite'),
  378	element_attribute(Abstract, type=umlformalparameter).
  379
  380class_attributes(Class, Attributes) :-
  381	class(Class),
  382	element_element(Class, Attributes),
  383	element_type(Attributes, 'dia:attribute'),
  384	element_attribute(Attributes, name=attributes).
  385
  386class_attribute(Class, Attribute) :-
  387	class_attributes(Class, Attributes),
  388	element_element(Attributes, Attribute),
  389	element_type(Attribute, 'dia:composite'),
  390	element_attribute(Attribute, type=umlattribute).
  391
  392class_operations(Class, Operations) :-
  393	class(Class),
  394	element_element(Class, Operations),
  395	element_type(Operations, 'dia:attribute'),
  396	element_attribute(Operations, name=operations).
  397
  398class_operation(Class, Operation) :-
  399	class_operations(Class, Operations),
  400	element_element(Operations, Operation),
  401	element_type(Operation, 'dia:composite'),
  402	element_attribute(Operation, type=umloperation).
  403
  404template_parameter(P) :- class_template_parameter(_,P).
  405
  406template_parameter_id(A, Id) :-
  407	class_template_parameter(Class, A),
  408	class_id(Class,ClassId),
  409	term_hash(A, H),
  410	atom_number(Ha, H),
  411	atom_concat(ClassId, 'T', X),
  412	atom_concat(X, Ha, Id).
  413
  414template_parameter_name(TP, N) :-
  415	template_parameter(TP),
  416	element_string_attribute(TP, name, N).
  417
  418template_parameter_type(TP, N) :-
  419	template_parameter(TP),
  420	element_string_attribute(TP, type, N).
  421
  422attribute(A) :-
  423	class(Class),
  424	class_attribute(Class, A).
  425
  426attribute_id(A, Id) :-
  427	class_attribute(Class, A),
  428	class_id(Class,ClassId),
  429	term_hash(A, H),
  430	atom_number(Ha, H),
  431	atom_concat(ClassId, 'A', X),
  432	atom_concat(X, Ha, Id).
  433
  434attribute_name(Attribute, Name, IsInherited) :-
  435	class(Class),
  436	class_attribute(Class, Attribute),
  437	element_string_attribute(Attribute, name, FullName),
  438	(   atom_concat('/', Name, FullName)
  439	->  IsInherited = true
  440	;   Name = FullName,
  441	    IsInherited = false).
  442
  443attribute_inherited(Attribute, IsInherited) :-
  444	attribute_name(Attribute, _, IsInherited).
  445
  446attribute_name(Attribute, Name) :- attribute_name(Attribute, Name, _).
  447
  448attribute_type(Attribute, Name) :-
  449	attribute(Attribute),
  450	element_string_attribute(Attribute, type, AName),
  451	(   AName == ''
  452	->  var(Name)
  453	;   Name = AName).
  454
  455attribute_value(Attribute, Name) :-
  456	attribute(Attribute),
  457	element_string_attribute(Attribute, value, AName),
  458	(   AName == ''
  459	->  var(Name)
  460	;   Name = '').
  461
  462attribute_comment(Attribute, Name) :-
  463	attribute(Attribute),
  464	element_string_attribute(Attribute, comment, Name).
  465
  466attribute_visibility(Attribute, Name) :-
  467	attribute(Attribute),
  468	element_enum_attribute(Attribute, visibility, X),
  469	dia_visibility(X,Name).
  470
  471attribute_static(Attribute, Static) :-
  472	attribute(Attribute),
  473	element_boolean_attribute(Attribute, class_scope, Static).
  474
  475attribute_abstract(Attribute, Static) :-
  476	attribute(Attribute),
  477	element_boolean_attribute(Attribute, abstract, Static).
  478
  479operation(Operation) :-
  480	class_operation(_, Operation).
  481
  482operation_id(A, Id) :-
  483	class_operation(Class, A),
  484	class_id(Class,ClassId),
  485	term_hash(A, H),
  486	atom_number(Ha, H),
  487	atom_concat(ClassId, 'O', X),
  488	atom_concat(X, Ha, Id).
  489
  490operation_name(Attribute, Name) :-
  491	operation(Attribute),
  492	element_string_attribute(Attribute, name, Name).
  493
  494operation_stereotype(Attribute, Name) :-
  495	operation(Attribute),
  496	element_string_attribute(Attribute, stereotype, Name).
  497
  498operation_type(Attribute, Name) :-
  499	operation(Attribute),
  500	element_string_attribute(Attribute, type, AName),
  501	(   AName == ''
  502	->  var(Name)
  503	;   Name = AName).
  504
  505
  506operation_comment(Attribute, Name) :-
  507	operation(Attribute),
  508	element_string_attribute(Attribute, comment, Name).
  509
  510operation_visibility(Attribute, Name) :-
  511	operation(Attribute),
  512	element_enum_attribute(Attribute, visibility, C),
  513	dia_visibility(C, Name).
  514
  515operation_static(Attribute, Static) :-
  516	operation(Attribute),
  517	element_boolean_attribute(Attribute, class_scope, Static).
  518
  519operation_abstract(Attribute, Static) :-
  520	operation(Attribute),
  521	element_boolean_attribute(Attribute, abstract, Static).
  522
  523operation_query(Attribute, Static) :-
  524	operation(Attribute),
  525	element_boolean_attribute(Attribute, query, Static).
  526
  527operation_inheritance(Attribute, Name) :-
  528	operation(Attribute),
  529	element_enum_attribute(Attribute, inheritance_type, X),
  530	dia_inheritance(X, Name).
  531
  532operation_parameters(Operation, Parameters) :-
  533	operation(Operation),
  534	element_element(Operation, Parameters),
  535	element_type(Parameters, 'dia:attribute'),
  536	element_attribute(Parameters, name=parameters).
  537
  538operation_parameter(Operation, Parameter) :-
  539	operation_parameters(Operation, P),
  540	element_element(P, Parameter),
  541	element_type(Parameter, 'dia:composite'),
  542	element_attribute(Parameter, type=umlparameter).
  543
  544parameter(P) :- operation_parameter(_, P).
  545
  546parameter_id(P, I) :-
  547	operation_parameter(O, P),
  548	operation_id(O,OpId),
  549	term_hash(P, H),
  550	atom_number(Ha, H),
  551	atom_concat(OpId, 'P', X),
  552	atom_concat(X, Ha, I).
  553
  554parameter_name(Attribute, Name) :-
  555	parameter(Attribute),
  556	element_string_attribute(Attribute, name, Name).
  557
  558parameter_type(Attribute, Name) :-
  559	parameter(Attribute),
  560	element_string_attribute(Attribute, type, AName),
  561	(   AName = ''
  562	->  var(Name)
  563	;   Name = AName).
  564
  565
  566parameter_value(Attribute, Name) :-
  567	parameter(Attribute),
  568	element_string_attribute(Attribute, value, AName),
  569	(   AName = ''
  570	->  var(Name)
  571	;   Name = AName).
  572
  573parameter_comment(Attribute, Name) :-
  574	parameter(Attribute),
  575	element_string_attribute(Attribute, comment, Name).
  576
  577parameter_direction(Parameter, Direction) :-
  578	parameter(Parameter),
  579	element_enum_attribute(Parameter, kind, X),
  580	dia_parameter_kind(X, Direction).
  581
  582association(Model, A) :-
  583	dia_layer(Model, L),
  584	element_element(L, A),
  585	element_type(A, 'dia:object'),
  586	element_attribute(A, type=Type),
  587	(   Type='UML - Association'
  588	;   Type='UML - Generalization'
  589	;   Type='UML - Realizes'
  590	;   Type='UML - Dependency'
  591	;   Type='UML - Implements'
  592	;   Type='UML - Contains').
  593
  594association(A) :- association(_,A).
  595
  596association_id(A, ID) :-
  597	association(Model, A),
  598	element_attribute(A, id=AssocID),
  599	model_id(Model, MID),
  600	atom_concat(MID,AssocID, ID).
  601
  602association_name(A, N) :-
  603	association(A),
  604	element_string_attribute(A, name, N).
  605
  606association_stereotype(A, N) :-
  607	association(A),
  608	(   element_string_attribute(A, stereotype, N)
  609	->  true
  610	;   N = '').
  611
  612association_text(A, T) :-
  613	association(A),
  614	(   element_string_attribute(A, text, T)
  615	->  true
  616	;   T = '').
  617
  618association_direction(A, N) :-
  619	association(A),
  620	(   element_enum_attribute(A, direction, X)
  621	->  dia_direction(X, N)
  622	;   N = undefined).
  623
  624association_type(A, N) :-
  625	association(A),
  626	element_attribute(A, type=T),
  627	(   T =='UML - Generalization'
  628	->  N = generalization
  629	;   T == 'UML - Realizes'
  630	->  N = realization
  631	;   T == 'UML - Dependency'
  632	->  N = dependency
  633	;   T == 'UML - Contains'
  634	->  N = containment
  635	;   T == 'UML - Implements'
  636	->  N = implementation
  637	;   T == 'UML - Association'
  638	->  element_enum_attribute(A, assoc_type, X),
  639	    dia_assoc_type(X, N)).
  640
  641association_role_a(A, R) :-
  642	association(A),
  643	(   element_string_attribute(A, role_a, R)
  644	->  true
  645	;   R='').
  646
  647association_multiplicity_a(A, R) :-
  648	association(A),
  649	(   element_string_attribute(A, multipicity_a, R)
  650	->  true
  651	;   element_string_attribute(A, multiplicity_a, R)
  652	->  true
  653	;   R='').
  654
  655association_visibility_a(A, R) :-
  656	association(A),
  657	(   element_enum_attribute(A, visibility_a, X)
  658	->  dia_visibility(X,R)
  659	;   R=undefined).
  660
  661association_arrow_a(A, R) :-
  662	association(A),
  663	(   element_boolean_attribute(A, show_arrow_a, R)
  664	->  true
  665	;   R=undefined).
  666
  667association_role_b(A, R) :-
  668	association(A),
  669	(   element_string_attribute(A, role_b, R)
  670	->  true
  671	;   R='').
  672
  673association_multiplicity_b(A, R) :-
  674	association(A),
  675	(   element_string_attribute(A, multipicity_b, R)
  676	->  true
  677	;   element_string_attribute(A, multiplicity_b, R)
  678	->  true
  679	;   R='').
  680
  681association_visibility_b(A, R) :-
  682	association(A),
  683	(   element_enum_attribute(A, visibility_b, X)
  684	->  dia_visibility(X,R)
  685	;   R=undefined).
  686
  687association_arrow_b(A, R) :-
  688	association(A),
  689	(   element_boolean_attribute(A, show_arrow_b, R)
  690	->  true
  691	;   R=undefined).
  692
  693association_from_id(A, X) :-
  694	association_direction(A, D),
  695	(   D = b_to_a
  696	->  association_end_b(A, X)
  697	;   association_end_a(A, X)).
  698
  699association_from_role(A, X) :-
  700	association_direction(A, D),
  701	(   D = b_to_a
  702	->  association_role_b(A, X)
  703	;   association_role_a(A, X)).
  704
  705association_from_multiplicity(A, X) :-
  706	association_direction(A, D),
  707	(   D = b_to_a
  708	->  association_multiplicity_b(A, X)
  709	;   association_multiplicity_a(A, X)).
  710
  711association_from_arrow(A, X) :-
  712	association_direction(A, D),
  713	(   D = b_to_a
  714	->  association_arrow_b(A, X)
  715	;   association_arrow_a(A, X)).
  716
  717association_from_visibility(A, X) :-
  718	association_direction(A, D),
  719	(   D = b_to_a
  720	->  association_visibility_b(A, X)
  721	;   association_visibility_a(A, X)).
  722
  723association_to_id(A, X) :-
  724	association_direction(A, D),
  725	(   D = b_to_a
  726	->  association_end_a(A, X)
  727	;   association_end_b(A, X)).
  728
  729association_to_role(A, X) :-
  730	association_direction(A, D),
  731	(   D = b_to_a
  732	->  association_role_a(A, X)
  733	;   association_role_b(A, X)).
  734
  735association_to_multiplicity(A, X) :-
  736	association_direction(A, D),
  737	(   D = b_to_a
  738	->  association_multiplicity_a(A, X)
  739	;   association_multiplicity_b(A, X)).
  740
  741association_to_arrow(A, X) :-
  742	association_direction(A, D),
  743	(   D = b_to_a
  744	->  association_arrow_a(A, X)
  745	;   association_arrow_b(A, X)).
  746
  747association_to_visibility(A, X) :-
  748	association_direction(A, D),
  749	(   D = b_to_a
  750	->  association_visibility_a(A, X)
  751	;   association_visibility_b(A, X)).
  752
  753
  754association_connections(A, C) :-
  755	association(A),
  756	element_element(A, C),
  757	element_type(C, 'dia:connections').
  758
  759association_end_a(A, CA) :-
  760	association_connections(A, C),
  761	element_element(C, X),
  762	element_type(X, 'dia:connection'),
  763	element_attribute(X, handle='0'),
  764	element_attribute(X, to=Id),
  765	association(Model, A),
  766	model_id(Model, ModelId),
  767	atom_concat(ModelId, Id, CA).
  768
  769association_end_b(A, CA) :-
  770	association_connections(A, C),
  771	element_element(C, X),
  772	element_type(X, 'dia:connection'),
  773	element_attribute(X, handle='1'),
  774	element_attribute(X, to=Id),
  775	association(Model, A),
  776	model_id(Model, ModelId),
  777	atom_concat(ModelId, Id, CA).
  778
  779large_package(M, X) :-
  780	dia_layer(M, L),
  781	element_element(L, X),
  782	element_type(X, 'dia:object'),
  783	element_attribute(X, type='UML - LargePackage').
  784
  785large_package(X) :- large_package(_,X).
  786large_package_id(X, Id) :-
  787	large_package(M, X),
  788	element_attribute(X, id=PackageId),
  789	model_id(M, ModelId),
  790	atom_concat(ModelId, PackageId, Id).
  791large_package_name(X, N) :-
  792	large_package(X),
  793	element_string_attribute(X, name, N).
  794large_package_stereotype(X, N) :-
  795	large_package(X),
  796	element_string_attribute(X, stereotype, N).
  797
  798small_package(M, X) :-
  799	dia_layer(M, L),
  800	element_element(L, X),
  801	element_type(X, 'dia:object'),
  802	element_attribute(X, type='UML - SmallPackage').
  803
  804small_package(X) :- small_package(_,X).
  805small_package_id(X, Id) :-
  806	small_package(M, X),
  807	element_attribute(X, id=PackageId),
  808	model_id(M, ModelId),
  809	atom_concat(ModelId, PackageId, Id).
  810small_package_text(X, N) :-
  811	small_package(X),
  812	element_element(X, Xn),
  813	element_attribute(Xn, name=text),
  814	element_type(Xn, 'dia:attribute'),
  815	element_element(Xn, Xnn),
  816	element_type(Xnn, 'dia:composite'),
  817	element_attribute(Xnn, type=text),
  818	element_string_attribute(Xnn, string, N).
  819
  820small_package_stereotype(X, N) :-
  821	small_package(X),
  822	element_string_attribute(X, stereotype, N).
  823
  824branch(M, B) :-
  825	dia_layer(M, L),
  826	element_element(L, B),
  827	element_type(B, 'dia:object'),
  828	element_attribute(B, type='UML - Branch').
  829
  830branch(B) :- branch(_, B).
  831
  832branch_id(B, I) :-
  833	branch(M, B),
  834	element_attribute(B, id=BranchId),
  835	model_id(M, ModelId),
  836	atom_concat(ModelId, BranchId, I).
  837
  838branch_name(B, N) :-
  839	branch(B),
  840	(   element_string_attribute(B, name, N)
  841	->  true
  842	;   N='').
  843
  844branch_stereotype(B, N) :-
  845	branch(B),
  846	(   element_string_attribute(B, stereotype, N)
  847	->  true
  848	;   N='').
  849
  850
  851package(P) :- small_package(P) ; large_package(P).
  852package_id(P, Id) :- small_package_id(P, Id) ; large_package_id(P, Id).
  853package_name(P, Id) :- large_package_name(P, Id); small_package_text(P, Id).
  854package_stereotype(P, S) :-
  855	large_package_stereotype(P, S) ; small_package_stereotype(P, S).
  856
  857constraint(Model, C) :-
  858	dia_layer(Model, L),
  859	element_element(L, C),
  860	element_type(C, 'dia:object'),
  861	element_attribute(C, type='UML - Constraint').
  862constraint(C) :- constraint(_, C).
  863constraint_id(C, Id) :-
  864	constraint(M, C),
  865	model_id(M, Mid),
  866	element_attribute(C, id=Cid),
  867	atom_concat(Mid, Cid, Id).
  868constraint_what(C, Id) :-
  869	constraint(M, C),
  870	model_id(M, Mid),
  871	element_element(C, Cs),
  872	element_type(Cs, 'dia:connections'),
  873	element_element(Cs, Con),
  874	element_type(Con, 'dia:connection'),
  875	element_attribute(Con, handle='1'),
  876	element_attribute(Con, to=Wid),
  877	atom_concat( Mid, Wid, Id ).
  878
  879constraint_expression(C, Expr) :-
  880	constraint(C),
  881	element_string_attribute(C, constraint, Expr).
  882
  883element_id(Element, Id) :-
  884	(   class_id(Element, Id)
  885	;   operation_id(Element, Id)
  886	;   attribute_id(Element, Id)
  887	;   parameter_id(Element, Id)
  888	;   association_id(Element, Id)
  889	;   template_parameter_id(Element, Id)
  890	;   branch_id(Element, Id)
  891	;   large_package_id(Element, Id)
  892	;   small_package_id(Element, Id)
  893	;   constraint_id(Element, Id)).
  894
  895clause(C) :-
  896	predicates_list(Predicates),
  897	member(Predicate/Arity, Predicates),
  898	functor(Pred, Predicate, Arity),
  899	(   Arity =:= 1,
  900	    Pred =.. [ Predicate, Argument ],
  901	    call(Pred),
  902	    atom_concat(Predicate, '_id', IdPredicate),
  903	    Query =.. [ IdPredicate, Argument, Id ],
  904	    call(Query),
  905	    C =.. [ Predicate, Id ]
  906	;   Arity =:= 2,
  907	    Pred =.. [ Predicate, Object, Value ],
  908	    call(Pred),
  909	    element_id(Object, ObjectId),
  910	    (	(   Predicate == class_attributes
  911		;   Predicate == class_operations
  912		;   Predicate == operation_parameters
  913		;   Predicate == class_template_parameters)
  914	    ->	findall(Id, ( element_element(Value, E), element_id(E,Id)), Ids),
  915		C =.. [ Predicate, ObjectId, Ids ]
  916	    ;	(   Predicate == class_attribute
  917		;   Predicate == class_operation
  918		;   Predicate == class_template_parameter
  919		;   Predicate == operation_parameter)
  920	    ->	element_id(Value, Id),
  921		C =.. [ Predicate, ObjectId, Id ]
  922	    ;	C =.. [ Predicate, ObjectId, Value])
  923	;   C = (Pred :- fail)).
  924
  925clauses(Clauses, Specs) :-
  926	findall( C, clause(C), Clauses ),
  927	clauses_specs(Clauses, Specs).
  928
  929clauses_specs(Clauses, Specs) :-
  930	findall(Pn/Pa,
  931		(   member(C, Clauses),
  932		    functor(C, Pn, Pa)),
  933		List),
  934	list_to_set(List, Specs).
 clauses(-List)
Unifies List with a list of all goals in predicates_list/1 that succeed in the dia-module. The list then contains all relevant diagram data in the form of prolog-clauses and can be written to files or asserted into appropriate modules (see write_facts/2 and assert_facts/2).
  943clauses(Clauses) :- clauses(Clauses, _).
 write_facts(+FileSpec, +Options)
Calls clauses/1 and writes the clauses representing the diagram-data into the file specified by FileSpec. Options is a list of options:
module
Generates a module/2 directive.
dynamic
Declares the clauses written as dynamic (see dynamic/1).
export
Marks the clauses written as exports (see export/1).
multifile
Declares the clauses written as multifile (see multifile/1).
  958write_facts(Dest, Opts) :-
  959	telling(X),
  960	filespec(Dest, '.pl', Name, File),
  961	tell(File),
  962	(   memberchk(module, Opts)
  963	->  writeq( :- module(Name, []) ), write('.'), nl
  964	;   true),
  965	(   memberchk(dynamic, Opts)
  966	->  predicates_list(Predicates),
  967	    foreach(member(Predicate, Predicates),
  968		    (	writeq( :- dynamic(Predicate) ), writeln('.') ))
  969	;   true),
  970	(   memberchk(multifile, Opts)
  971	->  predicates_list(Predicates),
  972	    foreach(member(Predicate, Predicates),
  973		    (	writeq( :- multifile(Predicate) ), writeln('.') ))
  974	;   true),
  975	(   memberchk(export, Opts)
  976	->  predicates_list(Predicates),
  977	    foreach(member(Predicate, Predicates),
  978		    (	writeq( :- export(Predicate) ), writeln('.') ))
  979	;   true),
  980	write_facts,
  981	told,
  982	tell(X).
 write_facts(+FileSpec)
Shorthand for write_facts( FileSpec, [] ).
  987write_facts(File) :- write_facts(File, []).
 write_facts
Calls clauses/1 and prints the resulting list to the current output stream using writeq/1.
  993write_facts :-
  994	clauses(Clauses),
  995	foreach(member(Clause, Clauses), (writeq(Clause), writeln('.'))).
 erase_facts(+ModuleIdentifier)
Erases all clauses matching one of the predicates in predicates_list/1 from the module identified by ModuleIdentifier.
 1003erase_facts(Mod) :-
 1004	predicates_list(L),
 1005	foreach( (   member(Pn/Pa, L),
 1006		     functor(P, Pn, Pa)),
 1007		 foreach(clause(Mod:P, _, R), erase(R))).
 assert_facts(+ModuleIdentifier, Options)
Calls clauses/1 and asserts the clauses into the module specified by ModuleIdentifier. Options is a list of options:
export
Mark the clauses asserted as exports (see export/1).
 1016assert_facts(Mod, Opts) :-
 1017	clauses(X),
 1018	foreach(member(C, X), assert(Mod:C)),
 1019	(   memberchk(export, Opts)
 1020	->  predicates_list(Predicates),
 1021	    foreach(member(Predicate, Predicates),
 1022		    export(Mod:Predicate))
 1023	;   true).
 assert_facts(Module)
Shorthand for assert_facts(Module, []).
 1028assert_facts(Mod) :- assert_facts(Mod, []).
 assert_facts
Shorthand for assert_facts(user, []).
 1033assert_facts :- assert_facts(user).
 import_facts(Module)
Asserts rules into the user module that delegate queries for diagram-data to Module.
 1039import_facts(FromModule) :-
 1040	predicates_list(Predicates),
 1041	foreach( (   member(Pn/Pa, Predicates),
 1042		     functor(P, Pn, Pa)),
 1043		 (   user:assert( P :- FromModule:P ) )).
 import_facts
Equivalent to import_facts(dia).
 1048import_facts :- import_facts(dia).
 1049
 1050
 1051erase_import_rules :-
 1052	predicates_list(Predicates),
 1053	foreach( (   member(Pn/Pa, Predicates),
 1054		     functor(P, Pn, Pa)),
 1055		 user:retractall(P)).
 1056
 1057copy_facts_(Src, Dest) :-
 1058	predicates_list(Pl),
 1059	findall( P,
 1060		 (   member(Pn/Pa, Pl),
 1061		     functor(P, Pn, Pa),
 1062		     call(Src:P)),
 1063		 Facts),
 1064	foreach(member(F, Facts), assert(Dest:F)).
 copy_facts(+ListOfModules, +DestinationModule)
Asserts all goals in predicates_list/1 that succeed in any of the modules in ListOfModules into DestinationModule.
 1070copy_facts(X, Dest) :-
 1071	atom(X),
 1072	(   X == []
 1073	->  true
 1074	;   copy_facts_(X, Dest)).
 1075copy_facts([M|Modules], Dest) :-
 1076	copy_facts(M, Dest),
 1077	copy_facts(Modules, Dest).
 import_diagram(+FileSpec)
Loads the diagram specified by FileSpec and asserts the facts representing the diagram-data into a module with the same name.
 1084import_diagram(FileSpec) :-
 1085	load_diagram(FileSpec),
 1086	filespec(FileSpec,'.dia', Name, _),
 1087	erase_facts(Name),
 1088	assert_facts(Name),
 1089	close_diagram(Name)