5

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.

Wouter Beek
  • 3,307
  • 16
  • 29
  • 2
    See [this answer](http://stackoverflow.com/a/28442760/772868) for the clpfd way to solve a related problem. – false Jun 07 '15 at 10:07
  • 1
    What do you expect to gain compared to `when((ground(Codes);nonvar(N)), number_codes(N,Codes))`? Both are weak and not relations - for that matter. – false Jun 07 '15 at 11:04
  • @false That comes quite close! However it does not deal with padding zeros, e.g., `phrase(day(2), "02")`. – Wouter Beek Jun 07 '15 at 11:29
  • I cannot see any problem with that goal, provided `set_prolog_flag(double_quotes, codes)`. – false Jun 08 '15 at 07:26
  • @false I meant `phrase(day(2), Codes)`, where `Codes` should comply to an ABNF rules that requires exactly two digits. – Wouter Beek Jun 09 '15 at 14:49
  • What I still miss is your statement what you actually expect. Do you expect this to work for dates only - then it would be trivial. But in the general case, infinity has to be considered... And will you refuse a date like 1.1.2015? It's all this undefinedness around which makes it difficult to answer. – false Jun 09 '15 at 17:22
  • Why not `day(N) --> digit(D1), digit(D2), {N #= 10*D1+D2, N in 0..31}.` – false Jun 09 '15 at 17:41
  • @false The parser should only succeed for days that consist of exactly two digits, e.g., `"02" -> 2`. The generator should only generate days that consist of exactly two digits, e.g., `2 -> "02"`. Here `"02"` stands for (a part of) the parsed/generated string and `2` stands for the value that is parsed / based on which a string is generated. In the overall grammar the values are compound terms `date/9` as per http://www.swi-prolog.org/pldoc/man?section=dattimedata – Wouter Beek Jun 09 '15 at 17:41
  • 1
    The bug lies in code_type: It fails for: `code_type(C,digit(N)),N=0.` but succeeds for `N=0, code_type(C,digit(N)).` – false Jun 09 '15 at 17:46
  • ... whereas same works for `N = 1`. So it's a SWI bug. – false Jun 09 '15 at 17:47
  • You do the reporting? – false Jun 09 '15 at 17:48
  • @false I agree to your use of `N #= 10*D1+D2 ...` for this particular case but that would only work for sequences of two digits. I would prefer it to be more generic, e.g., for use in anther rule which parses the number of days in the year, the year itself, and possibly other domains (e.g., social security numbers, telephone numbers) as well. For some uses it would be cumbersome to write `10000*D1+1000*D2+...` – Wouter Beek Jun 09 '15 at 17:50
  • @false Thanks for spotting the SWI bug! I will indeed report it. – Wouter Beek Jun 09 '15 at 17:51
  • This is what I suspected in the first place!You have not clearly stated how you want to handle infinity! – false Jun 09 '15 at 17:51
  • @false Ah, only now do I understand your remark about infinity properly :-) – Wouter Beek Jun 09 '15 at 17:56

1 Answers1

4

+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.

mat
  • 40,498
  • 3
  • 51
  • 78
  • Did any one of the three upvotes actually **test** the resulting code? There are still many further errors in it. Like the two cuts. – false Jun 07 '15 at 11:00
  • I certainly didn't: After answering the actual question (*triggering* the propagator), I did not even attempt to correct the first mistake I found after that (`digits_to_nonneg/2` failing unexpectedly), much less even further beyond. Writing correct propagators is certainly worth several questions in its own right. – mat Jun 07 '15 at 11:44