Block operator `[]` for matrix notation

I’m trying to build a module to support matrix arithmetic using the [] block operator (SWI-Prolog -- Manual). So to start:

module(matrices,
	[
	op(100, yf, []),
	new_array/2
	]).
	
new_array(Array, Contents) :-
	Array =.. ['$arr'|Contents].

arithmetic:evaluable(_[_],user).

[]([Ix], Array, X) :-
	functor(Array,'$arr',_),
	arg(Ix,Array,X).

The first issue I ran into was the operator didn’t appear to be exported:


ERROR: /Users/rworkman/Documents/PrologDev/swiCLPBNR/matrices_proto.pl:10:22: Syntax error: Operator expected

?- current_op(P,A,[]).
false.

?- op(100, yf, []).
true.

?- current_op(P,A,[]).
P = 100,
A = yf.

% /Users/rworkman/Documents/PrologDev/swiCLPBNR/matrices_proto compiled 0.00 sec, 1 clauses
Thread 1 (main): foreign predicate system:ground/1 did not clear exception: 
	error(type_error(atom,[]),context(system:sub_atom/5,_911962))
?- A[I]=..L.
L = [[], [I], A].

By using the top level to define the operator, the module now loads and A[I] is parsed as documented, although an (inconsequential?) error message is output.

Now when I create a new matrix and try to evaluate and matrix expression:

?- new_array(M,[1,2,3]), X is M[2].
ERROR: Type error: `callable' expected, found `new_array(_920036,[1,2,3]),[]([2],_920036,_920064)' (a compound)
ERROR: In:
ERROR:    [9] toplevel_call(user:user: ...)

?- new_array(M,[1,2,3]),call([]([2],M,X)).
M = '$arr'(1, 2, 3),
X = 2.

It appears that some check isn’t recognizing [] as a callable functor, yet using call explicitly works fine.

Bugs? (or operator error).

1 Like

Syntax -wise I cannot reproduce a problem:

:- module(matrices,
       [ op(100, yf, []),
         new_array/2
       ]).

new_array(Array, Contents) :-
	Array =.. ['$arr'|Contents].
?- new_array(A, [1,2,3]).
A = '$arr'(1, 2, 3).

?- X = A[1].
X = A[1].

You cannot make this work under is/2. All values under is/2 must be numbers. There is the functional expansion used for dicts. This could be used, but at the moment not using the public APIs. See boot/expand.pl, function/2. I think we could decide to make function/2 hookable.

Note that e.g., ECLiPSe uses (AFAIK) [] as functor for arrays. Arrays are around in a couple of Prolog systems, so you may want to stay as close as possible to one of these. I’ve started arrays a couple of times, but never carried it through. Still would be great to have!

This was my operator error; forget to make module declaration a directive.

Not strictly true, I think. Through arithmetic goal expansion, I can add “functions” that take things other than numbers:

?- use_module(library(clpBNR)).
% *** clpBNR v0.9.5alpha ***.
true.

?- X::real(1,10), M is midpoint(X).
M = 11r2,
X::real(1, 10).

midpoint is not a “current_arithmetic_function” and X is not a number. I just want to do something similar to index into a matrix. My suspicion is that may work except for some over-zealous checker (compiler?).

Specifically, the “checker” thinks a term with [] functor isn’t callable, but call has no problem with it:

?- new_array(A,[1,2,3]), []([2],A,X).
ERROR: Type error: `callable' expected, found `new_array(_7022,[1,2,3]),[]([2],_7022,_7050)' (a compound)
ERROR: In:
ERROR:    [9] toplevel_call(user:user:(...))
?- new_array(A,[1,2,3]), call([]([2],A,X)).
A = $arr(1, 2, 3),
X = 2.

There seem to be number of issues with [] not being an atom for doing this. I fixed some of them to make at least the basics working. That makes this work:

:- module(matrices,
	  [ op(100, yf, []),
	    []/3,
	    new_array/2
	  ]).
:- use_module(library(arithmetic)).

new_array(Array, Contents) :-
    Array =.. ['$arr'|Contents].

:- arithmetic_function(user:([]/2)).

[]([Ix], Array, X) :-
    functor(Array,'$arr',_),
    arg(Ix,Array,X).

Somewhat more interesting, this now works as well:

:- module(matrices,
          [ op(100, yf, []),
            []/3,
            new_array/2
          ]).

new_array(Array, Contents) :-
    compound_name_arguments(Array, [], Contents).

% Undocumented way to register a new function.  Requires
% 8.3.17-22 or later.

'$expand':function([](_,_), _).

[]([IxT], Array, X) :-
    compound(Array),
    compound_name_arity(Array, [], _),
    Ix is IxT,
    arg(Ix,Array,X).

Now we can do e.g.

?- new_array(A, [1,2,3]), X is A[1]+A[1+2].
A = [](1, 2, 3),
X = 4.

Or simply

?- new_array(A, [1,2,3]), writeln(A[2]).
2
A = [](1, 2, 3).

I’m not yet sure whether I want a way to define new functions and if so what a good way to define them is and how to make them module aware. Should we go down this route?

No surprise; I’m definitely in favour of supporting user defined functions for arithmetic expressions. It looks like you have a fix to permit this for my immediate purpose.

Outside of that, I’m not so sure; what exactly is a Prolog function? Does it permit evaluation of any argument in a call, as in your writeln example? Would this permit something like:

list_length([],0).
list_length([_|Tail],N+1) :-
	list_length(Tail,N).

How would the eval case be distinguished from the non-eval case, i.e., I really wanted the term N+1 (symbolic sum)? Also scope, as you mentioned; you wouldn’t want function definitions to affect the semantics of existing modules. So lots of issues to think about.

I see you’ve used an arithmetic_function directive rather than an arithmetic:evaluable rule to define a user arithmetic function. Are these equivalent? If so, are there times to prefer one over the other?

Once upon a time SWI-Prolog had these. For several Prolog systems functions are just predicates with arity N+1 that are evaluated by is/2, >/2, etc. Currently SWI-Prolog arithmetic is purely numeric. The arithmetic_function/1 API is a work-around that rewrites is/2, etc. at compile time. Pure numeric arithmetic has a lot of advantages, notably as it allows to compile them into a stack engine for the VM and it avoids the need to change intermediate results from C native to Prolog representation. In the back of my head I always have the plan to provide a C API for adding more evaluable functions.

The only one that currently exists is ./2 (predicate ./3) to access dicts. They are handled by the compiler which examines the goal arguments and inserts evaluation of functions appearing there as goals before the call. So, writeln(Dict.x) becomes .(Dict, x, X), writeln(X).

Only if you define +/2 as a function. That is a very bad idea, in particular as there is no quoting mechanism. This is fine as ./2 is not a normal term (anymore). It would also be fine for arrays as /2 is also a rather uncommon term. In the rare case you need to create a term of that shape you have X =.. [[],A,B].

arithmetic_function/1 is the public API. That indeed maintains a multifile predicate arithmetic:evaluable. As that is not documented it is better not to rely on that :slight_smile:

IBM Prolog had some syntax for functions … IIRC, something like this:

foo(X) :- bar(?X+1).

being equivalent to

foo(X) :- +(X,1,X2), bar(X2).

assuming that this was already defined:

'+('X,Y,Z) :- Z is X + Y.

It seems to me that this kind of expansion could be done at the same time as . expansion is done

Now that I’m familiar with it, I’m happy with the current mechanism for user defined arithmetic functions in module arithmetic. I have been using arithmetic:evaluable but I should switch to the arithmetic_function directive. And I’m also happy with compiled arithmetic when it’s purely numeric.

I think that the general function mechanism should be limited until such time a compelling use case is made. In the meantime, the undocumented support is fine for people (hackers) who want to prototype DSL’s. (I am a bit irritated that . has been usurped as an possible operator for use with dicts, but I can live with that.)

Bottom line: The “basics” that allow the first example to work are sufficient for my immediate needs.

Yip. The not-officially-supported ‘$expand’:function/2 hook can be used to define ?/1 as a function, after which you can define ?/2 as predicate. It might be worthwhile to turn this into something public that respects modules, i.e., a function declaration is only visible locally unless the associated predicate is exported. Functional notation can be quite handy for lightweight implementation of simple DSLs.

1 Like

After some hackery, I’m now able to do things like M1[1][2] is 10*M2[1+1][1].

One of the issues is the checking on function arguments done by arithmetic:expand_predicate_arguments/3. User defined arithmetic “types” like arrays or matrices aren’t currently eligible. I got around this by defining an identity function for such types:

% matrix value
:- arithmetic_function(user:'$Mx'/1).

'$Mx'(X,'$Mx'(X)).  % identity - matrix data evaluates to itself

But this forces a fixed arity on the data. I really would like to represent an array or matrix row to be a variadic term, i.e., '$Mx'/n (where n is any positive integer), and be able to use arg/3 on it.

One possibility is to have module arithmetic support an arithmetic type directive which just defines a functor name used to wrap user defined data:

:- artithmetic_type('$Mx').

Any instance of such a type would pass the expand_predicate_arguments test, just like a numeric value.

Complex number arithmetic is another use case I can think of for this kind of facility.

If there’s any consensus, I’m happy to contribute to the development effort if it amounts to much.

1 Like

I think I can live with an extension such that expand_predicate_arguments/3 does not expand certain arguments. Possibly this should be related to the function though. I.e., [](Index, Term) must evaluate
Index the usual way, but should leave a []/N term for Term unaffected. In general a []/N term should result in an exception.

OK. I’m going to dig into this further because I’m sure I haven’t thought it all through. I’ll post a strawman proposal if I make some progress.

I’ll think about how user defined arithmetic types relate to user defined functions. Perhaps modules provide a context for this, i.e., the argument expansion is only skipped when the argument type is defined in the same module as the function. On the other hand, it would be nice to overload operators so matrix (or complex number) multiplication could use the standard operators. But I’m still not yet really grasping the big picture regarding how extended, e.g., matrix or complex, arithmetic interacts with standard numeric arithmetic.

It should if it (the argument) represents function evaluation. But if it’s “data” it’s not so clear why it should be an exception; it’s analogous to a number, i.e., it evaluates to itself, so a variadic type instance shouldn’t be a problem.

That’s the ambiguity since functions and complex data syntactically look the same - they’re compound terms - and you may need some “meta-data” to tell them apart.

My first intuition would be that user-defined arithmetic functions have an input type for each of the arguments. Whether we also need an output type is a bit unclear. The rewrite must be aware that built-in arithmetic always takes numbers as input and always produces numbers.

A simpler option might be to define that the argument of user-defined functions is always passed raw, i.e., it must evaluate its arguments itself. We could have

:- arithmetic_function f(number, array).

where f/2 is the same as f(number,number). This is similar to tabling where we have n/a for general tabling or n(a1,a2,…) for specifying how the various arguments must be handled.

The types could be ignored, where number or one of the other built-in numeric types means “evaluate first” and anything else means “pass without evaluation”. The annotation is that merely documentation and the function itself may or may not do type validation.

I always thought the cons opeator for Prolog lists (also ./2 until Swi 7) was also a function. For example, datalog doesn’t have lists and I always thought that’s because it doesn’t have functions, so it can’t use cons. Am I deeply confused about this? And how deeply?

There are function symbols in the logical sense, which Prolog calls compound terms. Then there are functions as we know them from math and functional languages: things that evaluate their arguments to some new value. Prolog doesn’t have this. is/2 is a relation that evaluates a term to a number. The terms handled by is/2 are the subject of this topic.

1 Like

A bit of a downward detour:

The function expansion for the block notation in module arithmetic is pretty agnostic about what is allowed in the index:

?- arithmetic:expand_function(M[1+1],N,G).
G = []([1+1], M, N).

?- arithmetic:expand_function(M[1,1],N,G).
G = []([1, 1], M, N).

?- arithmetic:expand_function(M[1],N,G).
G = []([1], M, N).

?- arithmetic:expand_function(M[abcd],N,G).
G = []([abcd], M, N).

?- arithmetic:expand_function(M[1+1],N,G).
G = []([1+1], M, N).

?- arithmetic:expand_function(M[V],N,G).
G = []([V], M, N).

?- arithmetic:expand_function(M[(1,1)],N,G).
G = []([(1, 1)], M, N).

So what is legal is pretty much up to the eval process. This is largely the (unforseen?) consequence of arithmetic evaluation supporting character to code conversion, e.g., ?- CC is [a], but it’s nice this much works.

What isn’t permitted is a “list”:

?- arithmetic:expand_function(M[1,1],N,G).
ERROR: Arithmetic: `[1,1]' is not a function
ERROR: In:
ERROR:   [15] throw(error(type_error(evaluable,...),_26780))
ERROR:   [13] arithmetic:do_expand_function([1,1],_26818,_26820) at /Applications/SWI-Prolog8.3.15.app/Contents/swipl/library/arithmetic.pl:231
ERROR:   [12] arithmetic:expand_predicate_arguments([[1|...],_26882],[_26888|_26890],(_26894,_26896)) at /Applications/SWI-Prolog8.3.15.app/Contents/swipl/library/arithmetic.pl:241
ERROR:   [11] arithmetic:do_expand_function(_26936[1|...],_26928,((_26952,_26954),_26948)) at /Applications/SWI-Prolog8.3.15.app/Contents/swipl/library/arithmetic.pl:227
ERROR:   [10] arithmetic:expand_function(_26994[1|...],_26986,_26988) at /Applications/SWI-Prolog8.3.15.app/Contents/swipl/library/arithmetic.pl:204
ERROR:    [9] toplevel_call(user:arithmetic: ...) at /Applications/SWI-Prolog8.3.15.app/Contents/swipl/boot/toplevel.pl:1113
ERROR: 
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.

Should lists be permitted (syntactically) at this level which facilitates the fairly natural A[2,1] as a equivalent to A[2][1] or should that require another level of goal expansion? Note that it’s still up to the evaluation to determine what’s legal semantically.

This all seems relying on edge cases, which is typically asking for trouble in the future. My first intuition is that using the general functional notation approach makes more sense for arrays. If you prefer the arithmetic only route I think my suggestion to introduce types for the function declaration is the most compatible and promising approach.

Would this disallow, e.g. X is length("abc")+1?
Also, it could be nice to allow things like S2 is S1[:-1] - equivalent to sub_string(S1, _, _, 1, S2).
These would be really nice with an expanded function operator (I’m not sure that ?/1 is a great choice; but we don’t have an APL keyboard, e.g. ), to reduce the need for intermediate variables. e.g.

list_length(List, Length) :- list_length(List, 0, Length).
list_length([], Length, Length).
list_length([_|Xs], Length0, Length) :-
    list_length(Xs, ? Length0+1, Length).

Currently it does, but it’s a bit convoluted. Because string_length/2 meets the requirements, it’s possible to use it directly as a user defined arithmetic function:

:- arithmetic_function(user:string_length/1).

So this now works:

?- S="abc", X is string_length(S)+1.
S = "abc",
X = 4.

Unfortunately the following does not:

?- X is string_length("abc")+1.
ERROR: Type error: `callable' expected, found `"abc"' (a string)
ERROR: In:
ERROR:   [23] current_arithmetic_function("abc")
ERROR:   [22] arithmetic:do_expand_function("abc",_8324,_8326) at /Applications/SWI-Prolog8.3.9.app/Contents/swipl/library/arithmetic.pl:194

This because the user function expansion for arithmetic goals has a restrictive view of what’s allowed as an argument; in this case strings aren’t allowed.

I think it would be better in general if these decisions were postponed until evaluation, but I’m still in investigative mode.