How are Prolog and CHR supposed to interact?

I’ve had a look at this example and this tutorial, and it seems to me that when using CHR within Prolog, CHR is the primary interface. I.e. you use Prolog from within CHR rather than the other way around, even though Prolog is the host.

What I mean by that is one seems to write the CHR rules, and then query for a set of constraints and see what gets output. If the example above, in order to try and access CHR from within Prolog (rather than the other way around) it looks like Annie uses find_chr_constraint/1 – which is a debugging predicate, to enable unification within predicates of the constraint store.

Am I understanding this correctly?

Here is an example of what I find confusing:

:- use_module(library(chr)).

:- chr_constraint value/1.
:- chr_constraint blah/1.

value(I), value(J) <=> X is I*J, blah(X).

If I then query:

?- value(2),value(3),blah(X).

I thought I might get X=6. Instead I get:

blah(X),
blah(6).

So it seems that CHR “takes over” Prolog when its in use.

Meanwhile, I can get the intended behaviour by doing this:

value(2),value(3),find_chr_constraint(blah(X)).

then the output I get is:

X = 2,
blah(6).

but then I’m using a “debugging” predicate – which suggests that the main intended flow is actually the one above (i.e. CHR controls Prolog).

Not really :). CHR maintains a set of constraints that is stored in a global variable. It hooks into the Prolog REPL loop to display the content of this constraint store.

I do this all the time, and I would suggest you do the same. The other pattern would be what the tutorial refers to as the get foo pattern swiplchrtut/examples.adoc at 8f52d1170eb5fbae185ec69527cc564045f238bf · Anniepoo/swiplchrtut · GitHub.
I really don’t like that, just because you now have to deal with a lot additional constraints that are there only for extraction (you have to declare them and write down the extra rules for each predicate).
The caveat for find_chr_constraint is that if it’s used naively, like find_chr_constraint(X) it’s linear in the size of the store, so if you have a very large store you should be cautious.

But a question on this for @jan. Say I have 10^6 constraints of the form foo(X) in my store, and two constraints of the form bar(X), and then I do find_chr_constraint(bar(X)). I would be paying small price just for the bar right? Not a price proportional to the whole store. In other words, are the constraints in the chr store indexed?

1 Like

@meditans in your solution here:

I’m trying to understand how you get things into the constraint store in the first place. It seems to be related to the local_chr predicate which is defined as follows:

find_constraint(Goal, Cs) :-
    findall(Goal, find_chr_constraint(Goal), Cs).

local_chr(Facts, Result, Res) :-
    thread_create((maplist(call, Facts),
                   find_constraint(Result, Ns),
                   thread_exit(Ns)), Id),
    thread_join(Id, exited(Res)).

It is invoked here:

parse(File, Mat-Ns) :-
    once(phrase_from_file(input(Mat), File)),
    findall(n(I-J, 1, N), position(Mat, I-J, dgt(N)), Constraints),
    local_chr(Constraints, n(_, _, _), Ns).

… and that seems to be what activates the constraints and adds to them, but I don’t understand what’s going on here. It looks like local_chr calls all the facts in a new thread, is that what activates the constraints? It then uses find_constraint to extract the result back into Ns. Is that right?

Ah I see, let me shed some light on that.

No, you just enter things in the constraint store by invoking the constraints in a goal. Minimal example:

:- chr_constraint foo/2.

You can then just say at the top level:

?- foo(a,b), foo(b,c).
foo(a,b), foo(b,c).

And that means that you inserted the constraints in the chr store. If you added a rule in your source code, like

foo(X,Y), foo(Y,Z) <=> foo(X,Z)

and retry the query, you will see that they are combined.

My local_chr predicate is my answer to another problem. You can’t remove constraints from a chr store without writing apposite CHR rules, and I often find that bureaucracy tedious.
In the example you posted you want to remove them though, because you are doing a maplist in which you have a CHR question per item, and you can’t let the constraints combine.

So I hijacked the fact that CHR stores are per thread, spinning a thread just to run the CHR query, so that it is automatically destroyed in the end. I also baked in that predicate a way of getting the answers back, as usually what I want to do with CHR is inserting locally a bunch of constraints, see the consequences, and destroy the CHR store.

You shouldn’t be concerned with that predicate just to start.

So, summing up:

  • prolog → chr: just state the constraints.
  • chr → prolog: find_chr_constraints.
2 Likes

Thank you (and by the way, I think you’ve basically taught me CHR, so really, THANK YOU), I think I understand:

:- use_module(library(chr)).

:- chr_constraint v/1.

v(X) <=> writeln(["blah",X]).

then:

?- findall(X,(between(1,9,X),v(X)),Xs).
[blah,1]
[blah,2]
[blah,3]
[blah,4]
[blah,5]
[blah,6]
[blah,7]
[blah,8]
[blah,9]
Xs = [1, 2, 3, 4, 5, 6, 7, 8, 9].

If I invoke predicates subject to constraints, I have to use find_chr_constraint to get the results, but if I want to remove from the constraints I need a simplification rule which will do it: it cannot be done adhoc. Is that right?

So you made local_chr, the aim of which is to decide what the store starts with so that you can make adhoc adjustments in Prolog predicates. For simplicity, you also collect the results in the same predicate.

Did I understand correctly?

What happens here is that when a ‘constraint’ v(X) is inserted, the rule will immediately discard it and writeln the message. At this point the store is empty, so there isn’t anything to get out.
I usually refrain from putting side effects in chr rules except for debugging purposes, because the head selection is not deterministic.

Let’s see another example, you want to get the maximum of a list of numbers, using CHR. You can say:

:- use_module(library(chr)).
:- chr_constraint num/1.
num(X) \ num(Y) <=> X >= Y | true.

And then at the top level:

?- num(3), num(4).
num(4).

or;

?- maplist(num, [1,2,3,4,5,6,3,4,1,7,3,5,6]).
num(7).

So, you encapsulate this behavior in:

max(List, N) :-
    maplist(num, List),
    find_chr_constraint(num(N)).
?- max([1,2,3,5,2,1], N).
N = 5,
num(5) ;

But now, you want to find the maximum of two lists:

?- max([5,6,7], X), max([1,2,3], Y).
X = Y, Y = 7,
num(7) ;

That happens because nothing removed the num(7) constraint from the store from the first execution (the CHR store follows backtracking but there has been no backtracking here).

So, you could add rules in CHR to delete the store, and modify your max predicate:

:- use_module(library(chr)).

:- chr_constraint num/1, clear/0.

num(X) \ num(Y) <=> X >= Y | true.
clear \ num(X) <=> true.
clear <=> true.

max(List, N) :-
    maplist(num, List),
    find_chr_constraint(num(N)),
    clear.

and now:

?- max([5,6,7], X), max([1,2,3], Y).
X = 7,
Y = 3 ;

This seems fine, but if you had another constraint bar you should also add:

clear \ bar(X) <=> true

So in the end I got fed up with adding rules and just nuke the CHR store when I’m done :smile:

2 Likes

In particular, the constraints that are put in the CHR store as it’s created in the new thread. Unfortunately I don’t know if I can control which rules are known by the CHR store. (Maybe there’s a way, @jan? It would be dope!)

1 Like

This is a very insightful example, thank you again. I think I see how your day 3 solution could use CHR to:

  1. merge cells (as it does) (simpagation).
  2. remove cells which are not adjacent to a symbol (simpagation).
  3. note which cells are adjacent to a star which is adjacent to exactly two cells (propagation and simplification in separate rules).

I think it could have actually been a complete CHR solution. Will try to do it soon. If I succeed will post here :slight_smile:

1 Like

I highly encourage you to do that exercise, it is quite insightful to learn about CHR!
There are some shortcomings in the approach, but it’s instructive to see them.

While there are not many places to find examples of CHR for SWI-Prolog, searching GitHub does provide more than a short list.

https://github.com/search?q=use_module(library(chr))%20language%3Aprolog&type=code

Obviously I have not checked all of the noted code so YMMV.

These GitHub repositories are know to have quality SWI-Prolog code.

Useful Prolog references

Also check out

2 Likes

For posterity, how to extend Prolog with abduction capabilities using trivial additions via CHR.

http://akira.ruc.dk/~henning/publications/ChrDahlMultiCPL04.pdf

2 Likes

I hope you are proud of your pupil @meditans. Behold. Full DCG+CHR solution to both parts in 27 LOC:

:- use_module(library(chr)).
:- use_module(library(dcg/basics)).

:- set_prolog_flag(chr_toplevel_show_store, false).

ns(N,V) :- number_string(N,V).

% Parse input, designate X,Y coordinates to each character.
t(Xs) --> t(1,1,Xs).
t(_,_,[]) --> [].
t(X0,_,Xs) --> "\n",{X is X0+1},!,t(X,1,Xs).
t(X0,Y0,[p(X0,Y0,Y0,[V])|Xs]) --> [V0],{char_code(V,V0)},{Y is Y0+1},!,t(X0,Y,Xs).

% Predicates for the constraint store.
:- chr_constraint p/4.
:- chr_constraint q/4.
:- chr_constraint k/3.
:- chr_constraint stage/1.

% Remove dot coordinates.
p(_,_,_,['.']) <=> true.

% Merge digits.
p(X,Y0,Y,V),p(X,Y01,Y1,V1) <=>
    Y01-Y=:=1,
    ns(_,V),ns(_,V1) | append(V,V1,V_),p(X,Y0,Y1,V_).

% Check if X1,Y1 (a symbol coordinate) is adjacent to a digit span.
adj(X1,Y1,X,Y0,Y) :- X1>=X-1,X+1>=X1,Y1>=Y0-1,Y+1>=Y1.

% iff stage(2), filter for digit spans adjacent to symbols.
stage(2),p(X1,Y1,Y1,_) \ p(X,Y0,Y,V) <=>
         ns(_,V),adj(X1,Y1,X,Y0,Y) | ns(N,V),q(X,Y0,Y,N).

% iff stage(3), group digit spans around star symbols.
stage(3),p(X1,Y1,Y1,['*']) \ q(X,Y0,Y,V) <=>
	 adj(X1,Y1,X,Y0,Y) | k(X1,Y1,[V]).
% iff stage(3), aggregate star groups.
stage(3) \ k(X,Y,V),k(X,Y,V1) <=> V\=V1 | append(V,V1,Vs),k(X,Y,Vs).

solve(File,Part1,Part2) :-
    phrase_from_file(t(Xs),File), % read file and parse with t DCG.
    maplist(call,Xs), % call all predicates to put into CHR store.
    %invoke stage(2) and sum qs.
    stage(2),aggregate_all(sum(N),find_chr_constraint(q(_,_,_,N)),Part1),
    % invoke stage(3) and sum ks with just 2 values.
    stage(3),aggregate_all(sum(N),(find_chr_constraint(k(_,_,[A,B])),N is A*B),Part2). 

It works, but there is a lot of deprecated code there. find_chr_constraint/1 has been superseded by current_chr_constraint/1. thread_exit/1 is deprecated because it bypasses possibly needed cleanup. An engine would be more appropriate. But, notably if you want only one of the constraints, you can use the fact that the CHR store is sensitive to backtracking. So,

    findall(X, ( setup_constraints, current_chr_constraint(g(X))), Xs).

This backtracks over setting up the constraints and thus empties the constraint store.

P.s. It appears that current_chr_constraint/1 is not exported from library(chr). Fixed.
P.s. Finding all instances of a constraint using current_chr_constraint(p(X)) only processes the constraints for p/1. Otherwise it is a simple member/2 call, so finding a particular p(X), e.g., p(42) is not indexed.

1 Like

This was a great read! It inspired me to do some tests about CHR on my own (I’ll add details in one of the other questions I have opened).

Thank you @jan, noted and I’ll start using current_chr_constraint/1 when I install a new prolog version!

1 Like

Maybe a bit late reply. While reading Thom Frühwirth’s book ‘Constraint Handling Rules’, I compiled some notes and code that might be helpful to you. GitHub - chansey97/chr_book: Valuable code and exercises about the book "Constraint Handling Rules (2009)" .

4 Likes

It appears that calling CHR predicates from within meta-predicates does not trigger the constraint store.

Say we have:

:- chr_constraint x/1

E.g. normally call(x(1)). inserts x(1) into the CHR store.

You can also do:

findall(x(X), between(1,10,X), Xs), maplist(call, Xs)

in order to insert x(1)…x(10) into the CHR store.

However, this will fail:

findall(_, between(1,10,X), call(x(X)), _).

It will not insert anything into the store.

Because findall/3 backtracks over all solutions of the goal. x/1 adds the constraint to a (backtrackable) global constraint store, but as we backtrack, each x/1 that gets in there is immediately removed on backtracking.

I guess its a consequence of the constraint store being backtrackable, so it makes sense.