Functional notation in swi-prolog

Hello all,
One critique of prolog I see often is the lack of functional notation.
Therefore, to chain calls to predicates, we need to introduce additional variables (and find names for them).
However, this critique is too simple, because there are what I call functional islands in prolog (and swi-prolog).
Here is my own-compiled list of functional notation used in swi-prolog:

  • prolog standard arithmetic:
    • iso prolog
    • scope: is, =:=, =\=, < and all arithmetic comparison operators
    • only works with numbers (let’s ignore edge cases for now ^^) for speed reason ?
    • calling convention: input as args, single implicit output
  • ā€˜.’ functional notation for dicts
    • swi-prolog specific
    • works anywhere
    • polymorphic through the use of different dict tags (here dict tags and module are squashed)
    • bugs: expansion inside lambdas doesn’t work correctly
    • calling convention:
      • R = Dict.func(Args), which is compile time expanded to '.'(Dict, func(Arg), R)
      • is defined as Dict.func(Arg) := R :- ..., which is compile time expanded to func(Dict, Arg, R)
    • expansion time: system
  • library(arithmetic)
    • builtin pack for swi-prolog
    • same scope as prolog arithmetic
    • user extensible
    • expansion time: system
  • library(arithmetic_types)
    • extra pack for swi-prolog, so kind of swi-prolog specific
    • same scope as prolog arithmetic, but prefix standard arithmetic operator by . like .+, .* etc
    • user extensible
    • polymorphic depending on args
    • calling convention: same as prolog arithmetic, is defined by putting output as last argument
    • expansion time: user
  • library(func)
    • extra pack for swi-prolog, so kind of swi-prolog specific
    • works anywhere
    • user extensible
    • works with the module system, polymorphic
    • calling convention can be very complex and use extra operators like $, of, ~
    • expansion time: user
    • has some support for dicts
  • library(macros)
    • default pack for swi-prolog
    • works anywhere
    • user extensible
    • only expand values, does not call predicates. Functional in the sense that the return value is implicit
  • dcg for chaining calls
    • more of a hack than anything else
  • wrapping predicate: clpfd:#=, clpqr:{}, clpBNR:{}, units:qeval
    • reimplements DSLs
    • fully runtime
    • not user extensible, clpBNR provides supports for custom op
    • very difficult to mix with each other
    • incompatible with compile time expansion of functional notation

As you can see, most of these functional islands works through compile time expansion.
This approach has pros and cons:

  • pros, apart from the functional notation
    • can be as efficient as normal code, if expanded to concrete predicates, but the need for polymorphism often kills this
    • polymorphic predicates (sometimes)
    • user extensible
  • cons
    • needs unambiguous operator at compile time. ā€˜.’ for dicts is quite natural, but .+ of arithmetic_types and the use of $ and of in func is quite ugly
    • breaks prolog standard evaluation order unless explicitly taken care of
      • dict expansion takes care of correctly expanding when used with meta-predicate but breaks when used in a lambda
      • arithmetic_types takes care of correctly expanding prolog arithmetic expression but not dict functional notation
1 Like

And here is my conundrum:

Let’s say, I am implementing an array library based on swi-prolog dicts.
Dicts allows me to have:

  • A really nice structure to implement my library with
  • ā€˜.’ functional notation, meaning I can mimic most of numpy api verbatim

The problem is when it is time to implement arithmetic operators and mix with dict functional notation.
Let’s say, you want to evaluate an expression like this (A + B).reshape([3]).
If I implement a wrapper predicate @=, this will break because the dict functional predicate will expand like this:

add_reshape(A, B, C) :-
  C @= (A+B).reshape(3).

% will expand to
add_reshape(A, B, C) :-
  '.'(A+B, reshape(3), Tmp), % fails since A+B is not a dict
  C @= Tmp.

Basically, once you stard using compile time expansion, you can’t mix it with other approach like wrapping predicates.

I’m generally interested in this topic so here are a few comments:

  1. You should include library(arithmetic) in your list. It is part of the SWIP installed library (not an add-on) and supports user defined functions on numbers using the Prolog standard functional arithmetic predicates.
  2. The add-on arithmetic_types is a layer built on library(arithmetic) supporting user defined types like booleans, lists, arrays etc. It does not permit the overloading of the existing arithmetic operators, i.e., no polymorphism on those functions, but does support polymorphism on user defined types. The operators are defined by the the type, so the example of prefixing the standard arithmetic operators by ā€˜.’ is a convention adapted by one of the example types (type_ndarray), not one imposed by the library in general.
  3. I’m not convinced that the CLP instances you mentioned are all that ā€œdifficult to mix with each otherā€; have you tried? And I’m also not convinced there’s much need since the semantics have considerable overlap. clpqr and clpBNR obviously share the same wrapping predicate so that has to be qualified. clpfd uses a totally different syntax with different operators so not sure what the issue is there. And if external load time expansions are selective enough, it’s not clear to me how they impact the CLP DSL’s. (Note: I believe clpfd does considerable work through load time expansions but that may be one reason they have a distinct set of operators.)
  4. A minor point but clpBNR is user extensible (see https://ridgeworks.github.io/clpBNR/CLP_BNR_Guide/CLP_BNR_Guide.html#toc4User_Defined_Narrowing_Functions).

No, I think the issue is you want to specifically use the ā€˜.’ operator for something other than dictionaries, but the dictionary load time term expansion is overriding that. This has nothing to do with wrapping predicates.

If you (for now) use a different syntax, e.g.,ā€˜$’, then you should be able to write C is (A+B)$reshape(3) which wouldn’t affected by dictionary term expansion. Of course then you would have to define what the function ā€˜$’ is before any runtime evaluation would succeed. If that all works, then we can debate the case for supporting other uses of an infix ā€˜.’ operator other than dictionaries.

Thank you for replying :slight_smile:

Thank you for the tip. I never realized it was there because it is not referenced in the official documentation. But there is a documentation page.
I’ll add that to my list.

I wasn’t aware of this feature. I’ll update my first post.

One experience I’ve had was to integrate clpBNR:{} into units:qeval.
I have qualified this as hard because it required explicit support from qeval to handle clpBNR.
Maybe hard is the wrong term, maybe something like: ā€œneed explicit manual support for mix with each otherā€.

Well, I guess I understand what you mean. But in code like this:

X is (A+B).reshape(3) 

is A+B just a term +(A, B) or the results of A+B which is a dict ?
I could argue that since A+B is used inside of is, and is implements functional notation, the common interpretation would be the second one.

But I prefer to frame this problem another way:

  • wrapping predicates supports functional notation lazily
  • compile time expansion supports functional notation eagerly

Therefore, you can’t mix both approaches since the evaluation order will be wrong.


I also have a few questions about arithmetic_types:

  • Would you consider extending the compile time expansion of operators like .+ outside of is so that it could be used anywhere ?
    Are there any blockers except the fact that you want to keep compatibility with library arithmetic ?
  • I have noticed that compile time expansion inside of is, is is replaced with unification =. What about comparison predicates like =:= ? For example, let’s say you want to compare two ndarrays and produce a third boolean ndarray ?

I’m not sure what your expectations were. clpBNR has no dependancies on units:qeval but units:qeval wants to use constraints when standard arithmetic would generate errors. So units:qeval has to (explicitly) a) determine when constraints are required, and b) add the necessary constraints using clpBNR:{}. I don’t see any undue complexity here.

Now maybe you were expecting some sort of integration of constraints into standard arithmetic resulting in a more logical arithmetic system. Nice aspirational goal, but that has never been the way CLP libraries work in a traditional Prolog context for reasons practical and historical.

Most Prolog’s that I’m aware of have no pre-defined use for the infix operator ā€˜.’. The addition of dictionaries to SWIP added it for the dictionary functional notation. It has no separate meaning in an arithmetic expression until someone defines it as such. If you choose to overload this operator, you need to distinguish between its applicable uses.

Currently the libraries which support arithmetic extension interpret . as dictionary access so you can write things like:

?- Pt = point{x:1,y:2}, NxtX is Pt.x+5.
Pt = point{x:1, y:2},
NxtX = 6.

So it has an existing meaning with is (and related predicates). Changing the semantics of ā€˜.’ within is would potentially break existing applications using the dictionary interpretation, unless there were additional context sensitive code to distinguish the two cases.

I don’t see what ā€œwrappingā€ has to do with any of this, e.g.,

?- Pt = point{x:1,y:2}, {Y == Pt.x+5}.
Pt = point{x:1, y:2},
Y = 6.

What you can’t do (easily) is overload previously defined syntax.

And ā€œcompile time expansionā€ does what it can and defers anything else to runtime. For example expressions can be represented by vars at load time (in source) and evaluated at runtime as long as the expressions are defined at that time. So there isn’t such a sharp distinction between the two cases as you imply.

As I said previously, the operators (.+, .-, etc.) are defined by the arithmetic type, in this case type_ndarray and not by module(arithmetic_types). You can use these operators anywhere their definitions are visible, but their semantics, as defined by type_ndarray, is only applicable within the arithmetic predicates is and comparisons, because they are the only goals that are subject to expansion by arithmetic_types.

In theory, yes. Whether the example types (type bool, type ndarray) are up to the job remains to be seen. As long as the evaluation of the LHS and RHS are numbers, I expect things should work.

Note that is means unification because that’s standard arithmetic semantics. The same also applies to the comparison operators.

Thank you, I think I understand the topic a little bit more clearly now.
I understand now how library arithmetic and arithmetic_types are supporting dict notation.
The support works well for getting attributes.

So, I think I am not advocating changing the semantics, but broadening the support for arithmetic extension to arguments of the ā€˜.’ notation.
I believe that such changes won’t break existing code.
For example, let’s take the expression C is (A+B).reshape(3+1):

  • for the A+B part, I don’t think there is existing code like this, since it doesn’t run as LHS of ā€˜.’ needs to be a dict
  • for reshape(3+1), this could be the only potential breakage, as existing code could interpret 3+1 differently from is. But that would be highly unlikely.
  • existing code that don’t contain arithmetic expression in arguments of ā€˜.’ notation would be left identical

Would you be interested if I made a PR adding such support to the arithmetic_types library ?

But consider C is P.X. How would you deal with a LHS and/or RHS that isn’t known until evaluation time?

Currently 3+1 would be evaluated at runtime prior to applying reshape:

?- arithmetic_types:math_goal_expansion(X is reshape(A,1+2),G).
G = (_A is 1+2, arithmetic_types:eval(reshape(A, _A), _B), X=_B).

I might be interested if you had a ā€œproof of conceptā€ implementation that nailed down the details.