Mentions légales du service

Skip to content
Snippets Groups Projects
lemon.pl 4.62 KiB
/** <module> Influence graph export in Lemon graph format

Lemon is a [C++ graph library](http://lemon.cs.elte.hu/trac/lemon), lgf is its
input format

@author Sylvain Soliman
@license GPL
@copyright Inria EPI Lifeware 2018-2019
*/
:- module(
  lemon,
  [
    % Public API
    export_lemon_graph/1
  ]
).

% :- use_module(doc).
:- use_module(counters).
:- use_module(invariants).


%! export_lemon_graph(+OutputFile) is det.
%
% exports the current influence graph to OutputFile (adding '.lgf' extension
% if needed)
export_lemon_graph(OutputFile) :-
  biocham_command,
  doc('exports the current influence or multistability graph to \\argument{OutputFile} in Lemon
    graph format (\\url{http://lemon.cs.elte.hu/trac/lemon}) (adding \\texttt{.lgf}
    extension if needed). Computes the conservation laws of the model (by \\command{search_conservations/0}) in order
    to do so.'),
  type(OutputFile, output_file),
  automatic_suffix(OutputFile, '.lgf', write, FilenameLgf),
  setup_call_cleanup(
    open(FilenameLgf, write, Stream),
    export_lemon_stream(Stream),
    close(Stream)
  ).


%! export_lemon_stream(+Stream) is det.
%
% exports the current influence graph to the given Stream
export_lemon_stream(Stream) :-
  with_output_to(atom(_), invariants:find_pinvar),
  setup_call_cleanup(
    new_graph(GraphId),
    (
      influence_graph(GraphId),
      export_lemon_stream(GraphId, Stream)
    ),
    delete_item(GraphId)
  ).


%! species(-Species, -Uid) is nondet.
%
% stores a unique identifier Uid for each Species
:- dynamic(species/2).


%! export_lemon_stream(+Id, +Stream) is det.
%
% exports the graph associated to Id to the stream Stream
export_lemon_stream(Id, Stream) :-
  write(Stream, '@nodes\nlabel\tspecies\n'),
  set_counter(species, 0),
  retractall(species(_, _)),
  forall(
    item([parent: Id, kind: vertex, item: VertexName]),
    (
      count(species, Count),
      assertz(species(VertexName, Count)),
      format(Stream, '~w\t~w\n', [Count, VertexName])
    )
  ),
  write(Stream, '@arcs\n\t\tlabel\treaction\tsign\n'),
  number_reactions,
  set_counter(influences, 0),
  forall(
    item([parent: Id, kind: edge, item: Edge, id: EdgeId]),
    (
      Edge = (VertexA -> VertexB),
      species(VertexA, IdA),
      species(VertexB, IdB),
      get_attribute(EdgeId, origin = Origin),
      forall(
        member((Sign, Reaction), Origin),
        (
          count(influences, Count),
          normalize_reaction(Reaction, Normalized, _Negated),
          reactions(Normalized, RId),
          sign(Sign, SignNumber),
          format(
            Stream,
            '~w\t~w\t~w\t~w\t~w\n',
            [IdA, IdB, Count, RId, SignNumber]
          )
        )
      )
    )
  ),
  % TODO conservation laws
  write(Stream, '@attributes\nconserv '),
  findall(
    Conserv,
    (
      invariants:base_mol(List),
      maplist(no_coeff, List, LList),
      atomic_list_concat(LList, ',', Conserv)
    ),
    ConservList
  ),
  atomic_list_concat(ConservList,';', ConservAtom),
  write(Stream, ConservAtom),
  write(Stream, ';\n').


%! reactions(-Reaction, -Uid) is nondet.
%
% stores a unique identifier Uid for each Reaction
:- dynamic(reactions/2).


%! number_reactions is det.
%
% associates a unique number to each reaction
% such that reaction that are stoichiometrically inverse get opposite numbers
% and stoichiometrically equivalent get same number
number_reactions :-
  retractall(reactions(_, _)),
  set_counter(reactions, 1),
  forall(
    item([kind: reaction, item: Item]),
    (
      normalize_reaction(Item, Normalized, Negated),
      (
        reactions(Normalized, _Count)
      ->
        true
      ;
        reactions(Negated, Index)
      ->
        Count is -Index,
        assertz(reactions(Normalized, Count))
      ;
        count(reactions, Count),
        assertz(reactions(Normalized, Count))
      )
    )
  ).


%! sign(+Atom, -Number) is det.
%
% associates number Number to a sign Atom
sign('+', 1).
sign('-', -1).


%! no_coeff(+Coeff, -NoCoeff) is det.
%
% from a species with or without stoichiometry Coeff, remove the optional
% coefficient to get the species without stoichiometry NoCoeff
no_coeff(_*V, V) :-
  !.
no_coeff(X, X).


%! normalize_reaction(+Item, -NormalizedStoichiometry, -Negated) is det.
%
% compute a sorted stoichiometry list for the reaction Item as
% NormalizedStoichiometry and a sorted list for the inverse reaction as
% Negated
normalize_reaction(Item, NormalizedStoichiometry, Negated) :-
  reaction_editor:get_stoichiometry_and_kinetics(Item, Stoichiometry, _),
  sort(Stoichiometry, NormalizedStoichiometry),
  maplist(reaction_editor:negate_coefficient, Stoichiometry, NegatedStoich),
  sort(NegatedStoich, Negated).