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.
- 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.
- load_diagrams(+ListOfFiles:list)
- Calls load_diagram/1 for each file in ListOfFiles.
- 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.
- close_diagram(+FileSpec)
- Retracts the diagram data loaded from FileSpec from the
dia-module.
- close_diagrams(+ListOfFiles)
- Calls close_diagram/1 for each member of ListOfFiles.
- close_all_diagrams
- Retracts all diagram-data from the dia-module.
- 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).
- 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).
- write_facts(+FileSpec)
- Shorthand for
write_facts( FileSpec, [] )
.
- write_facts
- Calls clauses/1 and prints the resulting list to the
current output stream using writeq/1.
- erase_facts(+ModuleIdentifier)
- Erases all clauses matching one of the predicates
in predicates_list/1 from the module identified
by ModuleIdentifier.
- 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).
- assert_facts(Module)
- Shorthand for
assert_facts(Module, [])
.
- assert_facts
- Shorthand for
assert_facts(user, [])
.
- import_facts(Module)
- Asserts rules into the user module that delegate queries
for diagram-data to Module.
- import_facts
- Equivalent to
import_facts(dia)
.
- copy_facts(+ListOfModules, +DestinationModule)
- Asserts all goals in predicates_list/1 that succeed in
any of the modules in ListOfModules into DestinationModule.
- import_diagram(+FileSpec)
- Loads the diagram specified by FileSpec and asserts the
facts representing the diagram-data into a module with
the same name.