`settings:env` as arithmetic function

After the recent change to support for user defined arithmetic functions, I’ve been experimenting with library(settings); the doc suggests that env (arity 1 and 2) should evaluate to numeric values in arithmetic expressions, but I can’t make it work. A simple test module:

:- module(test_settings,[fsetting/2]).

:- use_module(library(settings)).

:- setting(version, atom,   '1.0', 'Current version').
:- setting(timeout, number,    20, 'Timeout in seconds').

After loading:

?- list_settings.
========================================================================
Name                      Value (*=modified) Comment
========================================================================
test_settings:version     '1.0'          Current version
test_settings:timeout     20             Timeout in seconds
true.

As I understand it env(timeout) or possibly env(test_settings:timeout) in an arithmetic expression should evaluate to 20, but I get nothing but errors. Looking at the code in library(settings) and library(arithmetic) probable causes are:

  1. env is not exported from library(settings). As I understand the recent change (9.1.22) to library(arithmetic) this is necessary to use env as a function outside the defining module.
  2. timeout and test_settings:timeout are not valid arguments to an arithmetic function as defined by arithmetic:math_goal_expansion.
  3. The implementation of settings:env just calls getenv which expects ‘text’ as a name. (My rudimentary understanding of settings suggests some form of module qualification is necessary.)

I don’t consider this a big issue - I can find no examples of usage in the SWIP release, but I’d like to understand how one uses the current arithmetic library for defining new arithmetic functions.

This is how it is supposed to be used:

:- setting(timeout, number,    env('TIMEOUT'), 'Timeout in seconds').
TIMEOUT=60 swipl s.pl
17 ?- list_settings.
========================================================================
Name                      Value (*=modified) Comment
========================================================================
user:timeout              60             Timeout in seconds

The expression is evaluated in the context of library(settings).

The setting name is module qualified. Values are not.

See library(arithmetic). You still have to understand that this library rewrites e.g. A is Expr into a sequence of arithmetic evaluations and calls to “user functions”, which implies that the expression must be sufficiently instantiated at compile time. The library also provides an evaluation predicate that can at runtime evaluate expressions holding user defined functions. I don’t know how useful it is. It was added first of all as a partial work-around for removing full support of user defined functions. That in turn was motivated by efficiency. Without the need to call Prolog we can optimize arithmetic a lot further and we do not need to convert intermediate results between native and Prolog representation.

I totally missed the point on this one - it’s a mechanism to incorporate the value of shell (environment) variables in a setting default value. I got sidetracked by the arithmetic expression evaluation and thought it was a general purpose function which could be used to evaluate any numeric setting value in an arithmetic expression. (The fact that env was documented as a predicate in library(settings) didn’t help.)

I think I understand (and agree with) the basics. I think it’s a bit too restrictive when it comes to allowable arguments in user defined functions, e.g, why can’t a user defined length/1 function take a string or atom as an argument, but that’s another discussion. Best practices for defining functions in one module to be used by another is also a bit fuzzy - perhaps the change in 9.1.22 was intended to clarify that.

As is, it evaluates bottom-up. I guess it is not a big issue to make user defined functions be evaluated top-down, i.e., pass the raw arguments into the function and make the user responsible for evaluating the arguments. If you have good arguments why you want that, I think I’m ok with that.

Modules and arithmetic are not well defined. If users can mess with functions we probably need some way to control this. That is what the current approach provides. I have no clue how many people use this. It was invented to port a program with a lot of arithmetic from SWI-Prolog to Quintus, which didn’t have a lot of built-in functions and no way to add new ones. Later it was moved to SWI-Prolog’s own library after dropping user defined functions. So, it is mostly history :slight_smile:

If people share their usage and expectations, we can make a better decision. So, for all readers, if you rely on user defined functions or want to use them, please share your thoughts.

User-defined arithmetic functions? So that I can define things like Prob is dbinom(X, N, P) returning a binomial probability? That would be a nice thing.

My world view may be simplistic, but I was thinking more minimalistic. Since the errors seem to be mainly goal expansion of user defined functions, perhaps the following mod to expand_predicate_arguments/3:

expand_predicate_arguments([], [], true).
expand_predicate_arguments([H0|T0], [H|T], (A,B)) :-
%%%    do_expand_function(H0, H1, A0),
    catch(do_expand_function(H0, H1, A0),error(type_error(_,_),_),
                (H1=H0, A0=true)),   % expand failed, just literal argument
    (   callable(H1),
        current_arithmetic_function(H1)
    ->  A = (A0, H is H1)
    ;   A = A0,
        H = H1
    ),
    expand_predicate_arguments(T0, T, B).

Evaluation is unchanged. For a simple user defined len function:

?- L is len(abc).
L = 3.

?- len(abc)*2 =< 10.
true.

?- L is len([a,b,cd]).
L = 3.

?- L is len(abc+1).
ERROR: Arithmetic: `abc' is not a function

Or sum/product/average/mean of a list, determinant of a matrix, factorial (N!), combinations (nCr), boolean functions, hyperbolic trig functions, various constants (Euler’s constant, speed of light, gravitational constant, …), etc. - anything that evaluates to a number. (Some of the above imply non-numeric arguments, others don’t.)

This is all just syntactic sugar, but a useful abstraction nonetheless (IMO).

Seems a bit dangerous. I think A is len(pi) is not going to result in 2, no?

Yes, but I wonder whether this should be done under arithmetic evaluation. As is input to arithmetic evaluation are arithmetic types (numbers) and the output is a number. For historical reasons we accept arithmetic expressions in addition to numbers for variables that appear in an expression. SWI-Prolog also accepts eval(Expr). I forgot where that came from.

There are many approaches for functional notation in the Prolog world. A simple one is to define your own alternative for is/2, so we can e.g. write (choose some operator)

  Var <- Expr

Alternatively one can implement that certain terms when appearing in predicate arguments act as functions. Reliable expansion thereof is pretty complicated as we have seen with the various issues (some unresolvable) with SWI-Prolog Dict.Func notation. Note that you can actually use this expansion as math{}.eval(Expr) after defining eval() on dicts of type math.

Not necessarily, it will depend on the semantics/implementation of len. Currently:

?- L is len(pi).
L = 17.

since len for this example is defined by:

len(X,L) :- is_list(X) -> length(X,L) ; string_length(X,L).

pi in an arithmetic expression is a number which if represented as a string has length 17. On the other hand len(gamma) is 5. I don’t see this as particularly dangerous.

My limited suggestion was just to extend user defined functions to permit non-numeric arguments, such as a list of numbers (or expressions), with the output still a number. I still see that as arithmetic. And I see no issue with eval either,

?- X is pi/4, S is eval(sum([sin(X)**2,cos(X)**2])).
X = 0.7853981633974483,
S = 1.0.

In this case the user defined sum will return a number which evals to itself.

So I see this as a modest extension (with a trival implementation) to the existing library(arthmetic) and I don’t yet see any additional downside. And it seems to be agreement with what could be done with user defined functions before compiled arithmetic was introduced (with the exception of runtime expressions).

Probably so, but “perfection is the enemy of good enough” for this purpose (IMO).

I’ve had the privilege of reading and writing more SQL than what is healthy. So, from this angle, implicit type conversion is never a good idea (ie I have learned to hate it :smiley: ). In the “pi” example, I don’t see a way to use both “pi” the string/atom and pi the mathematical constant without explicitly qualifying it, it seems?

If there would be a mini-language for “functions” we might as well type it properly? But of course this is a somewhat extreme point of view.

1 Like

Not quite seeing your point. The atom pi means one thing in an arithmetic expression and something different elsewhere; same as “1+2”. I see no type conversion; just evaluation. (Perhaps pi() would have been a clearer way to express the constant.)

Which is why I’d like to stay well away from this objective. This is just a proposal for extending user (i.e., app developer) defined arithmetic functions (library(arithmetic)) to accept non-numeric arguments, and a user responsibility to determine what those arguments mean.

2 Likes

JavaScript is the poster child for bad implicit conversions (although MySQL can be pretty bad). If you want some examples, skip to 1:20 in Wat

There are some conversions that are OK - e.g., int to float. But converting a float to a string is a Bad Idea … if you really want to do that, you should do something like X is len(string(pi)) and at least it’s obvious why you get 17.

Isn’t a bug that string_length(3.1415, 6) doesn’t throw an error? The definition says

Number types must first be formatted into strings before the length of their string representation can be determined.

and I read that as requiring a string, so it should instead be this:

?- Pi is pi, atom_string(Pi, PiStr), string_length(PiStr, PiStrLen).

(or is the documentation in error and should be “Number types are first formatted into strings …”?)

1 Like

I don’t have a big problem with L is len(pi) returning 17, but I do have a big problem that
S = pi, L is len(S) returns 2 (I assume). As is, Prolog arithmetic must return the same result regardless of the order of instantiation. That is already a problem with the compile time approach to user defined functions, but at least you get the expected answer or a evaluation error (undefined function). Unless you redefine functions. I don’t know whether that is allowed, but possibly it should not be.

As for string_length/2, yes, this is dubious. Should have been restricted to write_length/3. I don’t think it should cause a lot of trouble and is worth making an incompatible change. Possibly, we could at some point add a flag that causes the built-ins to reject dubious type conversions?

1 Like

Agreed. But that’s a separate issue and it’s a problem with the current
library(arithmetic)):

?- R is len(pi).
S = pi,
R = 17.

?- S=pi, R is len(S).
S = pi,
R = 2.

?- S=len(pi), R is S.
ERROR: Arithmetic: `len/1' is not a function

So ignoring my poor choice of len as an example in this discussion, there seem to be 3 (at least?) issues with user defined arithmetic functions as supported by library(arithmetic)):

  1. How to interpret a var at compile (goal expansion) time. Current assumption is that it will be bound to an expression evaluable by builtin arithmetic at runtime; anything else (including a user defined function) is a runtime error.
  2. Should any arguments of user defined functions that are arithmetic expressions be evaluated before the function is called (bottom up) or is that the responsibility of the user defined function (top down aka runtime evaluation).
  3. Should any arguments to user defined functions which are not “evaluable” be treated as compile time errors or should it be up to the user defined function to enforce any restrictions on the arguments?

One possible source of guidance: implementation of user defined arithmetic functions in other Prolog’s and (presumably) SWIP before compiled arithmetic.

I think it is an excellent example to illustrate the issues if you want to allow for non-numeric types in is/2 and friends. As for the points

It is indeed given to built-in arithmetic. I think there is no other choice given the design.

That is indeed a good question. IMO, if you want user defined functions with non-numeric types you must make the function responsible for evaluating the arguments. That can be a bit more work. Often it will be ok as the arguments will be evaluated silently by what the user function does.

Isn’t that the same as saying that arguments must be valid arithmetic expressions and (thus) user defined functions can only deal with numbers?

The ISO standard simply says that is/2 (and >/2, etc.) evaluate their arguments using a set of defined functions. This set cannot be extended and it is not even possible to figure out which functions are defined. In several Prolog systems, each predicate is considered a function where the last argument is the return value. They may even allow for non-determinism :slight_smile: Other Prolog systems are in between. I don’t know which (that do not map functions to predicates in general) allow for adding functions. In the old days, SWI-Prolog allowed users to register a predicate as function, after which it behaved as a built-in. Evaluation was bottom up. I’ve many times considered allowing to define new functions through the foreign API. The interface relies on a lot of details that I do not like to expose, notably for big integers and rational numbers. Adding a facility to add floating point functions from C would be quite simple.

There are already too many flags. :slight_smile:

Perhaps a new predicate: strict_string_length/2 (which is a terrible name) and deprecate string_length/2. Also, the documentation for string_length/2 should be clarified (should be: “Number types are first formatted into strings …” instead of “must be”).

IBM Prolog had a syntax for treating a predicate as a function, something like this (I forget the exact syntax and couldn’t find a manual online):

foo(X,Y ) :- bar($plus_one(X), Y).

this was treated in a similar way to how SWI-Prolog expands (.)/2 dict functions, so that the above code would be equivalent to (including possible backtracking):

foo(X,Y) :- plus_one(X, Xplus1), bar(Xplus1, Y).

I think IBM Prolog also allowed registering functions for use with is/2, (<)/2, etc.; and I think that there was a way of handling general arithmetic, something like

foo(X, Y) :- bar($(X+1), Y).

I agree there are too many flags. In this case a flag is quite appropriate though. There is nothing that needs to change to string_length/2’s behavior except for rejecting a dubious type conversion. People who are ok as is can leave it. If you are not ok, enable the flag, find the issues and use write_length/3. I think that is nicer than adding a predicate with a weird name. I consider this case pretty similar to compiler errors/warnings,

That may be a good idea. I think Ciao has something similar, and probably more systems do. All the logic for functional expansion is present as it is used for dicts. We also know the pitfalls :frowning:

P.s. Pushed an update for the docs.

or just wrap it in a predicate with semantics that suits you.

Interesting thought. We could write a library that wraps predicates to enforce e.g., ISO restrictions, tighter type checks, etc. Nice and with no consequences for the main code base :slight_smile:

Except it got sidetracked in a discussion about string_length :slight_smile:

For motivation, perhaps I should have stuck to the original env('TIMEOUT') example. (Not to mention the builtin roundtoward which necessitates special cases in a few places to handle the rounding mode atom.)