Patterns for functional composition, expressions, conciseness?

I’m constantly fighting with Prolog. Often I’d like to express functional ideas, together with relational ones:

... :-
   g(Y,f(X), Result) 

or

... :-
  Result := g(Y,f(X)) 

but I typically need to refactor as as this:

... :-
   f(X, Tmp),
   g(Y, Tmp, Result),

which I think:

  • is detrimental to clarity (because understanding the functional dependence of g on f requires more mental effort),
  • leaves me wasting time inventing names for unwanted variables, and
  • invites new programmer errors that are eliminated in languages without assignment (we may, for example, use Tmp elsewhere by mistake).

It seems to me that the difference is largely just syntax and the lack of ease in forming non-boolean expressions doesn’t benefit prolog. More general expressions are standard idiom in 100% of languages outside of logic programming, so we can say their worth has been proven.

Are there patterns to employ in prolog to achieve more functional-style readability?
For example, are there macros that can automatically rewrite:

g(Y, λ(f,X), Result) 

or

Result <- g(Y, λ(f,X)) 

as:

... :- 
   f(X, Tmp0),
   g(Y, Tmp0, Result) 

Have you looked into some of the Packs?

Perhaps library(yall): Lambda expressions would help.

1 Like

I already use {...}\[X,Y]>>(f(...)) with maplist and similar. AFAICT, its main benefit of yall/lambda, it to be be able to have inline anonymous predicates. What I’d like is non-boolean expressions and to be able to evaluate expression values in-place without temporary variables.

Perhaps this might work: https://www.swi-prolog.org/pack/list?p=func

g(Y, f(X, ~), Result).

The tilde is transformed to:

X_ =  f(X, ~),
g(Y, X_, Result).

I have experimented term rewrite with lifter, but - bugs apart - I find it not worth the effort. The lifted code makes gtrace difficult to use…
The code looks like

fac(N, F) :-
	N > 1 -> F is fac(° is N-1, °) * N ; F is 1.

delta_fields(FA, FB, FD) :-
	sort(FA, SA),
	sort(FB, SB),
	append(maplist([X,Y]>>(Y = +X), ord_subtract(SA, SB, °), °)
	      ,maplist([X,Y]>>(Y = -X), ord_subtract(SB, SA, °), °)
	      ,FD).

delta_fields_named(FA, FB, FD) :-
    append(maplist([X,Y]>>(Y = +X),
		   ord_subtract(sort(FA, °A),
				sort(FB, °B), °), °)
          ,maplist([X,Y]>>(Y = -X),
		   ord_subtract(B, A, °), °)
          ,FD).

Anyway, Michael Hendricks has contributed function_expansion, you should try it, or maybe func.
Check the behaviour in meta arguments (like Goal in findall/3), I tried function_expansion time ago, it had the same problem of lifter, that doesn’t recognize the nesting scope. Maybe esad - that seems to be the current mantainer of func, has corrected the bug.

1 Like

@CapelliC is the output more difficult to debug than what you’d equivalently have to write by hand?

yes, because the current on-debug clause has to be decompiled into a service code window, and variables are renamed.

OT

fac/2 I’ve posted above shows the unrecognized scope bug WRT (;)/2,
instead this definition is fine

factorial(0,1).
factorial(N,Fac) :- Fac is factorial(° is (°N > 0) - 1, °) * N .

Now that is strange, because both definitions come from lifter.plt, that should be the same (wrt lifting) as posted in 2013

Hmmm… it seems like goal_expansion shouldn’t have to rename existing variables, right?
Can the implementation be replaced with one that preserves existing variable names, or should we expect problems?

Does this do what you want?

call_compose(P1, P2) :-
    call(P1, Result1),
    P2 =.. [P2pred | P2args],
    P2call =.. [P2pred, Result1 | P2args],
    call(P2call).

p1(a, 1).
p1(b, 2).

p2(1, 1-a).
p2(2, 2-b).

test(X, Y) :-
    call_compose(p1(X), p2(Y)). % p1(X,R1), p2(R1, Y).
?- test(X, Y).
X = a,
Y = 1-a ;
X = b,
Y = 2-b.

Be careful with inline expansions that introduce “intermediate” variables (like Result1 above) … they don’t play nicely with existensional quantification in aggregators such as setof/3.

1 Like

To some extend this reminds me of my first encounter with Prolog where I tried to emulate imperative programming in Prolog. Many of us probably had the same experience. It doesn’t work. Prolog is a lousy imperative language and an equally lousy functional language. Yes, you can add functional notation to Prolog. There are several preprocessors (using goal_expansion/2 or something similar) that add some sort of functional notation to Prolog. I fear all suffer from ambiguities and hard to explain corner cases. This includes SWI-Prolog’s Dict.key or Dict.function(arg …) notation as we have seen in recent posts.

There are several reasons that makes this hard. I’ll not go into the details right now.

Bottom line is that Prolog has its own strengths that you get in return. Like any language, you should make these strengths work for you instead of trying to make the strengths of the language you were used to work on Prolog.

P.s. Picat is (B-)Prolog with more conventional language constructs. To get there, they had to give up Prolog’s prolog-is-data feature. This was to me the reason not to join the Picat initiative. Giving up that feature severely harms one of the key benefits of Prolog: separate the domain model from the implementation and tie the two together using a domain specific language (DSL).

10 Likes

This might be of interest: Quick map of LP landscape

1 Like

@peter.ludemann I don’t get it. Is there a more detailed example with setof?

Doesn’t this assume P1 and P2 are both arity 2?

Despite its problems, the lifter and func libraries at least provide clarity to the reader… I’d argue that call_compose(p1(X), p2(Y)) is less clear (and less general) than p2(p1(X, ~), Y)).

Would these problems be avoided if new predicates were introduced instead of temporary variables?

@stuz5000
If you do something like this:

all_compose(P1, P2, X, Ys) :-
    setof(Y, ( call(P1, X, H), call(P2, H, Y) ), Ys)

then it’ll backtrack over the intermediate (H) results.

There’s no problem if you you put it in a separate predicate like the one here: Patterns for functional composition, expressions, conciseness?

But if you use inline expansion, you’ll need to do:

all_compose(P1, P2, X, Ys) :-
    setof(Y, H^( call(P1, X, H), call(P2, H, Y) ), Ys)

[Warning: untested code]

1 Like

Which Prolog are you using for this? I was able to do the following with SWI-Prolog:

compose(P, Q, X, Y) :-
   call(P, X, H),
   call(Q, H, Y).

which I could use like this:

?- call(compose(between(1), between(1)), 3, Z).
Z = 1 ;
Z = 1 ;
Z = 2 ;
Z = 1 ;
Z = 2 ;
Z = 3.