Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Constraint not propagated upon instantiation of list members

I am building a parser and generator for dates and times. In an ordinary programming language these would be written separately. In Prolog+CLP(FD) I can write 1 predicate that does both :-)

In my use case it often makes sense to parse a number of digits and convert the to an integer, or to generate a number of digits based on a given integer.

My problem is that clpfd:run_propagator/2 is not called when individual digits are instantiated, despite my declarations using clpfd:init_propagator/2. Is there a way to do this or am I making a mistake in my definition of clpfd_digits/2?

Code implemented in SWI-Prolog:

:- use_module(library(apply)).
:- use_module(library(clpfd)).

:- multifile(clpfd:run_propagator/2).

day(D) --> {clpfd_digits(D, [D1,D2])}, digit(D1), digit(D2).

digit(D) --> [C], {code_type(C, digit(D))}.

clpfd_digits(N, Ds):-
  clpfd:make_propagator(clpfd_digits(N, Ds), Prop),
  clpfd:init_propagator(N, Prop),
  clpfd:init_propagator(Ds, Prop),
  forall(
    member(D, Ds),
    clpfd:init_propagator(D, Prop)
  ),
  clpfd:trigger_once(Prop).

clpfd:run_propagator(clpfd_digits(N, Ds), MState):-
  (   maplist(is_digit0, Ds)
  ->  clpfd:kill(MState),
      digits_to_nonneg(Ds, N)
  ;   integer(N)
  ->  clpfd:kill(MState),
      nonneg_to_digits(N, Ds)
  ;   true
  ).

digits_to_nonneg([], 0):- !.
digits_to_nonneg(Ds, N):-
  maplist(char_weight, Chars, Ds),
  number_chars(N, Chars).

char_weight(Char, D):-
  char_type(Char, digit(D)).

nonneg_to_digits(0, []):- !.
nonneg_to_digits(N, Ds):-
  atom_chars(N, Chars),
  maplist(char_weight, Chars, Ds).

is_digit0(D):- integer(D), between(0, 9, D).

Example of use:

?- string_codes("12", Cs), phrase(day(D), Cs).
Cs = [49, 50],
clpfd_digits(D, [1, 2]).

As you can see the constraint is not calculated to derive at the value of D.

like image 519
Wouter Beek Avatar asked Sep 28 '22 17:09

Wouter Beek


1 Answers

+1 for using CLP(FD) constraints for this task!

forall/2 and constraints do not mix very well, since backtracking revokes posted constraints.

Your example works as expected with:

flip_init(Prop, D) :- clpfd:init_propagator(D, Prop).

and using maplist(flip_init(Prop), Ds) instead of forall/2.

The next problem is then that digits_to_nonneg([1,2], N) simply fails, but this is unrelated to the actual constraint triggering, which happens as expected. (By the way: Using constraints, you may be able to simplify the code so that you can use a single predicate in both directions.)

Also, you can use in/2 instead of between/3: D in 0..9. This is often useful if you want to use it as a constraint instead of just a test.

like image 193
mat Avatar answered Nov 15 '22 10:11

mat