José Veliz
José Veliz

Reputation: 110

How can I dynamically assert rules with conditions conjoined in the body in Prolog?

My code:

run_insert_format([]).
run_insert_format([H|T]) :- H = [X,Y],
                            assertz(( X :- (verificar(Y)) )), run_insert_format(T).

run_query :- 
    odbc_query(
        bd,
        sqlQueryString,
        List,
        [ findall([Animal,Characteristic],row(Animal,Characteristic)) ]),
        run_insert_format(List).

The List variable is giving me something like this:

[ [chita, mamifero], [chita, carnivoro], [chita, color_rojizo] ]

I'm trying to get this as a result of the asssertz:

%Reglas (rules)
% chita :-
%     verificar(mamifero),
%     verificar(carnivoro),
%     verificar(color_rojizo).

But instead I get this:

% chita :-
%     verificar(mamifero).
% chita :-
%     verificar(carnivoro).
% chita :-
%     verificar(color_rojizo).

I know what the code is doing correctly, but What can I do to get the second result?.

Thanks in advance

Upvotes: 1

Views: 115

Answers (1)

Shon
Shon

Reputation: 4098

To restate the problem, for each head foo, you're asserting a clause for every condition f1, f2, i.e.,

foo :- f1.
foo :- f2.

but what you want is to assert a single clause for each head with all conditions conjoined into a single body:

foo :- f1, f2.

The key step you're missing is converting the collection of characteristics for each animal into a conjunction, which you can then assert as the body.

Here is one way to achieve this result using swi-prolog association lists for grouping the characteristics:

:- use_module(library(assoc)).

assert_characteristics(Characteristics) :-
    group_characteristics(Characteristics, GroupedCharacteristics),
    maplist(assert_condition, GroupedCharacteristics).

% Conditions should be a conjunction, e.g., `(a, b, c)`
assert_condition(Head-Conditions) :-
    maplist(make_check, Conditions, Checks),
    list_to_conjunction(Checks, Conjunctions),
    assertz(( Head :- Conjunctions )).

% ex. group_characteristics([foo-f1, foo-f2, bar-b1], [foo-[f1,f2], bar-[b1]]).
group_characteristics(AnimalCharacteristics, Grouped) :-
    empty_assoc(Assoc),
    group_characteristics(AnimalCharacteristics, Assoc, Grouped).

% helper for group_characteristics/2
group_characteristics([], Assoc, Grouped) :- assoc_to_list(Assoc, Grouped).
group_characteristics([Animal-Char|Rest], Assoc0, Grouped) :-
    % Updating an existing animal with the new characteristic `Char`
    ( get_assoc(Animal, Assoc0, Chars, Assoc1, [Char|Chars]), !
    % Otherwise, the key for `Animal` isn't present yet, so add it.
    ; put_assoc(Animal, Assoc0, [Char], Assoc1) ),
    group_characteristics(Rest, Assoc1, Grouped).


% Convert a list of predictes into a conjunction of predicates
% ex. list_to_conjunction([a,b,c], (a, (b, (c, true)))).
list_to_conjunction([], true).
list_to_conjunction([P|Ps], (P, Conjuncts)) :- list_to_conjunction(Ps, Conjuncts).

% just a helper used in assert_condition/1
make_check(C, verificar(C)).

Example usage:

?- assert_characteristics([foo-foo1, bar-bar1, foo-foo2]).
true.

?- listing(foo).
:- dynamic foo/0.

foo :-
    verificar(foo2),
    verificar(foo1),
    true.

There are a number of improvements and optimizations to be added to my example, such as making the grouping operation pure or collecting the characteristics into a set to prevent redundant conditions being included in the bodies.

Upvotes: 2

Related Questions