New version of the units package v0.16

So let me ask the question a different way. mp-units is a C++, compile time library. So it has to do compile time checking of all quantity expressions to ensure type safety and quantity types are necessary to express compatibility (units of the same kind). And It’s an essential concept for runtime checking as implemented in library(units), but that doesn’t necessarily mean it’s useful concept in a quantities DSL which is about expressing relationships between quantities. By extension, I haven’t seen any examples where the qeval DSL offers any more “safety” or “expressivity” than the qty DSL.

I think you underestimate the qty DSL - see above. I think it’s just as expressive and safety is ensured through runtime checks whenever a quantity is used in an expression. Using as might enable earlier error detection but I’m not convinced that offers much value given runtime checking whenever a quantity is used. That’s not to say I couldn’t be convinced to add it given a compelling use case.

What I’m trying to do is define a simple, minimalist DSL for evaluating quantity expressions, not just for me but for most potential users. What I’m not seeing at the moment is where the qeval DSL offers any advantages (safety or expressivity), and simpler is almost always better IMO. Clearly a wrapper approach incurs overhead, but whether the qty DSL continues to exist, and where, is of secondary importance at the moment.

BTW, this no longer works for me; I’m sure it did once:

?- qeval(S is D / T as isq:speed).
ERROR: Domain error: `1' expected, found `isq:speed'
ERROR: In:
ERROR:   [17] throw(error(domain_error(1,...),_4962))
ERROR:   [16] error:domain_error(1,isq:speed) at /Applications/SWI-Prolog9.3.25.app/Contents/Resources/swipl/library/error.pl:106
ERROR:   [15] units:eval_(user,_5050/_5052 as isq:speed,_5040) at /Users/rworkman/.local/share/swi-prolog/pack/units/prolog/units.pl:735
E

Sorry, this still seems wrong to me. So if you think this works as intended (notwithstanding the confusing units in a dimensionless quantity):

?- qeval(X is m/yd).
X = 1*kind_of(1)[si:metre/imperial:yard].

what about:

?- qeval(X is (1*m)/(1*yd)).
X = 1*kind_of(1)[si:metre/imperial:yard].

Here I’m clearly dividing the quantity 1*m by 1*yd; the resulting quantity should not have magnitude 1.

Also:

?- qeval(X =:= m/yd).
X = 1250r1143.

?- qeval(X =:= (1*m)/(1*yd)).
X = 1250r1143.

leading to more confusion.

IMO, it looks like they’re not so useless after all. And floating point errors may be a concern at some point but I don’t think we’re there yet.

Why not ? I don’t understand your skepticism here.
I find it very useful to express relationships between quantities without having to hard code specific units.
In my case, I found the speed example eye opening.
You simply cannot express the same as qeval(S is D / T as isq:speed) in your qty DSL.

Well, here is my experience.
I have used other unit aware library before (like the pint library in python) and I always found it lacking, because unit expression are hard to understand.
They grow unwieldy very quickly.
What I found really nice in the mp-units library is specifically the fact that I can use quantity types like speed, length, area, and others.
I find quantity types much more understandable than whatever unit aggregate you get thrown at.
like what the heck is a furlong ?

?- qeval(X is furlong).
X = 1*kind_of(isq:length)[usc:furlong].

Ho, nice it is a length :slight_smile:

As usual, you need to wrap variables in quantity(X) except on the left of is:

?- qeval(X is quantity D / quantity T as isq:speed).
X = _A*isq:speed[_B/_C],
D = _D*isq:length[_E],
T = _F*isq:time[_G],
...

Yes, and you are clearly given back a ratio of two units.
This is not wrong, it is just another representation of the same thing.
This feature is also very important in a lot of physics expression where lots of constants should be symbolically simplified.
Since the mp-units library (and this library) models constants as units, we can do the simplification at the symbolic level: Faster-than-lightspeed Constants - mp-units

Well, because of the different semantic of is and =:=, those expressions are not equivalent.
the correct translation would be:

?- qeval(quantity X =:= (si:metre) / (usc:yard)).
X = 1*kind_of(1)[si:metre/usc:yard].

Well, this is a core feature of the library and lazy conversions is the only way to provide it, so I don’t see what the problem is ?

I don’t believe I expressed any skepticism about defining quantities without having to hard code units. What I am skeptical about is the value of using as to constrain undefined units when type safety is ensured by runtime checking. I hope you can see the difference.

My motivation in removing as from the qty DSL is to provide the simplest DSL without sacrificing functionality.

I believe I can:

?- qty(S is D / T).
S = _B[_A],
D = _D[_C],
T = _F[_E],
when(ground(_G), (quantity):any_quantity_(_G)),
% many more constraints

?- qty(S is D / T), D=1[m], T=2[s].
S = 1r2[m/s],
D = 1[m],
T = 2[s].

What this doesn’t do is constrain S to be of kind isq:speed. But my argument (see above) is that isn’t necessary because runtime checking will catch any attempts to use S as something other than a speed in expressions that require it. Note that this is something that mp_units cannot do because there is no runtime check.

So please explain why that is useful when evaluating quantity expressions.

But I don’t need to evaluate to find that out:

?- all_unit_kind(S:furlong,K).
S = imperial,
K = kind_of(isq:length).

% non-deterministic version
?- unit(S:furlong,_),all_unit_kind(S:furlong,K).
S = imperial,
K = kind_of(isq:length) ;
S = usc,
K = kind_of(isq:length).

Not “as usual” because avg_speed/3 is defined as

avg_speed(Distance, Time, Speed) :-
   qeval(Speed is Distance / Time as isq:speed).

in at least 3 places in your github repo - test code in units.pl, examples/speed.pl and README.md. So which version is intended?

I think you’re missing the main point. What is the ratio of a length of 1 metre and a length of 1 yard. I believe that’s expressed by:

?- qeval(R is (1*m)/(1*yd)).
R = 1*kind_of(1)[si:metre/imperial:yard].

but 1 is the wrong answer, and you’ll have a hard time convincing me otherwise. And the difference between is and =:= just furthers my argument that the qeval DSL is overly complex for the job it’s doing (as is the need for the quantity operation).

But how would such runtime check works ?
Your only solution is to hard code a unit that will represent a speed like m/s.
But now, your code is not generic with respect to units. you will always have to convert from and to m/s. Which we don’t want because every superfluous conversion introduces errors and slowdowns.
I also find it quite annoying that I can write an avg_speed predicate which does not complain if it doesn’t actually compute a speed ? Let’s say I want to compute an acceleration with that speed, that code won’t complain either because it is also a division.
This is one of the core innovation and feature of mp-units and this specific topic explored in length by the mp-units author

Moreover, unit compatibility is not the same as quantity types compatibility.
And this is the big reason why mp-units introduced quantity types.
Unit compatibility is based on dimensional analysis. as long as two units are of the same dimensions, you can use them together.
Quantities on the other hand forms a complex graph (which often is a tree) that dictate which quantity can be converted to each other.
For example, isq:length is the root of all lengths. isq:height is a special type of lengths. all heights can be converted to lengths, but lengths cannot be implicitly used as heights.
See the box example for a more complete example: units/examples/box.pl at 9570d39b2151cd997bcdd91b9fe78fb29e706967 · kwon-young/units · GitHub
No amount of runtime checking with units is going to give you this functionality.

Well, my design for this library was for users to only use qeval/1. the other predicates like all_unit_kind are internal to the library and not exported.
The other exported predicate purpose is for user customization.

Basically, the problem here is that your expectation is clashing with one of the library core feature (lazy conversions).
I understand your expectation and I was similarly surprised the first time I encountered it.
However, I believe the usefulness of this feature largely outweigh a first time surprise and you will have a hard time convincing me otherwise.
The code which answer your expectation is just slightly different qeval(R is m/yd in 1).

Well, as you suggest, one way to enforce that a quantity is of type speed is to try to covert it to a known quantity of that type. But why would I do that unnecessarily? I just use the quantity in in expression that expects a speed (length/time) and if it isn’t of the right kind you get an error (due to the runtime check).

Well avg_speed actually doesn’t complain until the units are sufficiently defined, which may be at the point of call or sometime later. The difference is between failure when the units are defined and failure when the quantity is used in an incompatible way. In either the case the code will complain if a quantity is used inappropriately, e.g., if I tried to use a quantity whose units mean acceleration in an expression that expects speed.

Well as I tried to explain several times, mp-units is a compile time library used to strictly enforce the types of all variables. It has no option of a runtime check. It may be an innovation in the imperative language world but I don’t see it as one that necessarily transfers to a Prolog environment where pretty much everything is done at runtime. Again, quantity types are needed to implement proper runtime checking, but I don’t see them as necessarily being a concept that needs to be incorporated into the DSL (as demonstrated by qty).

But my question is what has this got anything to do with the DSL?

But this is obviously an issue about which you have strong opinions. So to get past the sticking point, I’ll add as to the qty DSL. So I can now write:

avg_speed(Distance, Time, Speed) :-
   qty(Speed is Distance / Time as isq:speed).

and

?- quantities:avg_speed(D,T,S),D=2[m], T=5[s].
D = 2[m],
T = 5[s],
S = 2r5[m/s].

?- quantities:avg_speed(D,T,S),D=2[g], T=5[s].
ERROR: symbol `g` type incompatible with unit `_347092{when = ..., freeze(_347092, quantities:map_units(_347092,g))}` type
false.

The error message obviously needs some work, but would this address your concerns regarding the simplified DSL? Or are there others.

Incompatible subtypes of the same type is definitely a new wrinkle that I haven’t previously considered. What I can’t decide is whether this is a contrived problem to fit a solution, or whether it’s a real world issue. For example, why is isq:height a quantity type at all. (I suppose the answer will be that that’s what mp_units does.)

Instead suppose the “box” library implements a box with properties length, width, and height, all of type isq:length and the box library enforces any restrictions on the use of those properties. Seems like a more reasonable way of organizing the software, but maybe there are more compelling examples.

Well that’s your call, but I think I argued from the beginning for a reasonable way to “query” the units database independent of the evaluation of quantities expressions. And qeval can’t do everything, e.g., what units are of quantity type “K” as in:

?- unit(U,_), all_unit_kind(U,kind_of(isq:time)).
U = iau:'Julian_year' ;
U = iau:day ;
U = iec:zebi(non_si:hour) ;
U = iec:zebi(non_si:day) .

Well I would hope that the general expectation is that the answers would be “correct” as that term is generally defined, and that correctness would not be sacrificed to some nebulous core feature like lazy conversion. Personally, I would have difficulty using any library that violated my notion of correctness.

or

?- qeval(R*1 is m/yd).
R = 1250r1143.

similarly:

?- qeval(R is (1*m)/(1*yd)).
R = 1*kind_of(1)[si:metre/imperial:yard].

?- qeval(R*1 is (1*m)/(1*yd)).
R = 1250r1143.

How are you going to explain all that to a naive user. “Simple things should be simple.”

Do these units packages define rounding? Is this correct:

https://www.shutterstock.com/de/image-photo/road-sign-longest-straight-australia-548866177

I think one way its correct:

145.6 km ÷ 1.609344 km/mile = 90.47 miles

The other way its incorrect:

90 miles × 1.609344 km/mile = 144.84 km

I suppose they must have done the rounding in miles:

?- qeval((145.6*km =:= 90*usc:mile+quantity Eps, SIEps is Eps in km)).
Eps = 0.4716455897558234*kind_of(isq:length)[usc:mile],
SIEps = 0.7590399999999958*kind_of(isq:length)[si:kilo(si:metre)].

The library units will use normal prolog arithmetic if values are sufficiently instantiated.
Else, it will use clpBNR, which will always include the true value inside an interval if needed.

Well, I would have to see an example of how such runtime check would work.

That doesn’t change the fact that a quantityless version of avg_speed won’t complain if used with wrong units.

Why not ? Integrating quantity types in qeval means that you only need to learn 2 concepts:

  • the term to represent a quantity: Value*Quantity[Unit]
  • the as operator to convert between quantity types

How much simpler can it be ?

You would have to be more precise so that I can understand your proposition.
For now, I don’t think what you propose provides the same safety guaranties as the original example.
For example, one of the core improvement of the example is that using quantities with specialized quantity types, you cannot mistakenly switch arguments like width and height.
I can tell you by experience when working with geometric package, you never know if a 2d bounding box is xyxy, yxyx, xywh, etc

This is clearly outside the original scope of the library.
If there is a clear use case for this, maybe I will make some predicate publics.

How does checks being compile time or runtime changes anything about the nature of the checks ?
Moreover, I have often heard the analogy between type systems being a kind of logic programming. If we stretch things a bit further, we could see an equivalent between c++ compile time working with types and the prolog runtime.
So, I don’t think that your dismissal of some features of the mp-units library because of it being a compile time library makes any sense.
For example, generic units and quantities handling through variable constraints (which is very prology) is fully supported by mp-units through templates.

Could you explain what you were doing here, and how you read it?

Do you have intervals associated with units, so you can write “in km”?

Sure, how about:

?- qeval((D is 5*g, T is 2*s, S is D/T)), qeval(S1 is S+2*m/s).
ERROR: Domain error: `kind_of(isq:mass/isq:time)' expected, found `kind_of(isq:length/isq:time)'

The first qeval does not use as to constrain the units of S. But when I try to use S in the second qeval expecting I can add 2*m/s to it, the runtime check generates an error. I expected that would be obvious, but perhaps not.

Disagree, see previous example. But it definitely won’t complain until a) the units are defined, and b) the quantity is used in an expression that requires checking of those units (which will not be at at the point of call to quantity typeless version of avg_speed).

How about Value[Unit] which is bidirectional, i.e., literal quantities are the same form as generated quantities? How about no quantity, unit, or in operator, (as being under discussion)? How about is being semantically the same as =:=? How about no need for qformat because is 1.23 m really better than 1.23[m] (the former not being a Prolog term)?

And does as really “convert between quantity types”? Or does it just check that the target quantity is (or will be) “compatible” with the stated quantity type?

So my question is why are width and height quantity types and not properties of “box”? Similarly shouldn’t circumference and radius be properties of “circle” rather than quantity types? And the list goes on. Trying to do everything with quantity types is folly IMO.

I suspect within any given geometric package, this is well defined. But it may well be different between such packages. But I don’t see how adding quantity types to the mix is going to change that.

And if I’m starting from scratch, why not just label the arguments, because we are talking about Prolog, e.g., box(x0(_),y0(_),x1(_),y1(_)), box(pt(_,_), pt(_,_)), box(x(),y(),w(),h())`, etc. Or use dictionary property names?

Well the use case is that I shouldn’t have to perform an evaluation when this is just a query of the units “database”; no “values” required. FWIW, the entire interface of the “quantities” wrapper module is currently:

:- module(quantities, [
	qty/1,
	symbol_unit/3
	]).

:- use_module(library(units)).
:- reexport(library(units),[op(_P,_A,[]),op(_,_,as)]).

where symbol_unit/3 is just such a query predicate:

?- symbol_unit(m,U,K).
U = si:metre,
K = isq:length ;
false.

?- symbol_unit(S,U,isq:time).
S = 'PiD',
U = iec:pebi(iau:day) ;
S = 'Pia',
U = iec:pebi(iau:'Julian_year') ;
S = 'Pis',
U = iec:pebi(cgs:second) .  % query terminated

As an aside, it should be on your list to move the test code out of units.pl into a separate test module. Firstly, it comprises about 25% of the code bulk which isn’t used by any application, and, secondly, it pre-loads all the systems it uses, which is contrary to the whole point of making the user responsible for loading the systems they need.

Didn’t say it did, or it should in the grand scheme of things. Misuse of quantities needs to be caught. For mp-units, this, by definition, is at compile time; for units it’s runtime. (I suppose one could envision using term/goal expansion to do something equivalent to mp-units at load time.)

But runtime checks are dynamic and so can make use of, for example, the current data about currency exchange rates. That’s something that mp-units cannot do without recompiling, but it could be done using pack units.

Perhaps, but off-topic since it doesn’t seem to be the job that units is currently trying to do. In any case, I much prefer the dynamic typing pf Prolog vs. the static typing of compiled languages; it’s one of the main reasons I like Prolog, and why I have zero interest in an equivalent to any C++ static library.

Don’t pretend to understand C++, but so what? What I’m seeking is a simple, correct, and easy to use Prolog library supporting quantities. Unfortunately, that’s not what pack units seems to be, so maybe I’m wasting my time here.

So the sign is incorrect:

?- qeval(90*mi =:= 145.6*km).
false.

If it’s 90 miles, the equivalent distance in km is:

?- qeval(K*km is 90*mi).
K = 144.84096.

If it’s 145.6 km, the equivalent distance in miles is:

?- qeval(M*mi is 145.6*km).
M = 90.47164558975582.

The conversion factor in the units database is:

?- qeval(X*1 is mi/km).
X = 1.609344.

which is the same value you used. In the current version it is assumed to be a precise value (not an interval). Like standard Prolog arithmetic, there is (currently) no support for rounding.

Yes, and I consider both of these very problematic and resolved by using explicit quantity types.

Well, we will just have to agree to disagree about the lisibility of symbols.
I believe the normal form of quantities should use the expanded non ambiguous name of units and quantities.
Using symbols in generated quantities means that those quantities are sensitive to the current context of how you loaded your symbol in the module.
Using those generated quantities in another context just won’t work.

quantity and in does not have anything to do with the use of explicit quantity types.
They are just syntactical sugar:

qeval(quantity X =:= metre).
% is the same as
X = V*Q[U], % or X = V[U] in your DSL
qeval(X =:= metre).
qeval(X is metre in feet).
% is the same as
X = V*Q[usc:feet],
qeval(X is metre).

Yes, I believe it is better, but only in specific context, like if you write a recipe application and you want to show quantities with units for non programming users.

The conversion rules for quantity types are quite complicated (because the reality about physical quantities is complicated) and is formalized by the isq standard. But basically:

  1. you can convert upward in the quantity tree: isq:height to isq:length
  2. you can convert downward in the quantity tree if the formula is correct: isq:length/isq:time to isq:speed
  3. kind_of(X) can also be converted downward as they represent the whole tree with root X

Because the concept of width and height is more general than the concept of a box ?

I know this is all very experimental, but I think quantity types are very useful and will try to use them more in the future.
We will see how it will turn out.
mp-units on their end seems to show that it is useful and is a candidate for standardization.

Well, as long as both uses the same quantity types like isq:height and isq:width, mistakingly using one for the other will generate an error.

Well, you could, but for one, that means you will have to unwrap the quantities when doing arithmetic, leading to a lot of boilerplates and errors.

Shouldn’t that be called symbol_unit_kind/3 ?
Again, I am not against this, but I would just like a more compelling use case of why you would do this ?

Hum, very good point. I’ll do that soon.

Well, of course mp-units can do it. they can just get the exchange rate value at runtime while using quantity types, see the example: mp-units/example/currency.cpp at d9dce46c21f6d915424112fd8b5e2163addc051b · mpusz/mp-units · GitHub

Well, I’m sorry for wasting your time. Maybe we should stop here ^^
I am very grateful for your testing of the library and all the common sense remarks that definitly improved the library.
I also think that we have different visions about this type of libraries.
I’m going to continue to experiment and follow the vision of mp-units.
If you want to integrate your qty wrapper to library units, you are very welcome to make a PR as an alternative to qeval.

It is becoming obvious that we have different views as to what is “very problematical”. And that extends to other things like correctness and simplicity/ease of use. It’s difficult to debate technical merits when there isn’t agreement on the value set.

No doubt, there’s also some miscommunication which is inherent in hashing things out on a mailing list.

In any case I agree there doesn’t seem to be much point in continuing the discussion so I’ll be looking for other ways to “scratch this itch”.

I had first used 1.60934, but then used 1.609344. But I think
this here is not a symmetric answer, and a symmetric answer
using constraint logic programming maybe impossible:

I computes 145.6*km - 90*mile in terms of km, so it computes:

/* Calculator Accessory, Windows 11, decimal-based arithmetic */
145.6 - 90*1.609344 = 0.75904

/* SWI-Prolog Evaluator, Windows 11, binary-based arithmetic */
?- X is 145.6 - 90*1.609344.
X = 0.7590399999999988

So to be correctly rounded to one digit after the period, the eps would
need to be smaller. But for the other direction, whether the conversion
from km to mile was correct, I guess a 2nd query would be needed.

But still I would be interested whether constraint logic programming
can answer such questions in one query, like whether CLAM (the idea
of Constraint Logic Abstract Machines) has a rounding bidirectionality?

Giving new momentum to the dream that CLAM is a silver bullet.

Edit 14.07.2025:
Interestingly qeval and/or clpBNR shows 0.7590399999999958, and
not the other value 0.7590399999999988, maybe from another Maschine,
not the same Windows 11 Operating System Binary-Based Arithmetic ?

Or a dependency in which order arithmetic operations were applied.

So not quite sure what the question is but the first issue is the decimal to binary conversion error for floats. Using clpBNR interval arithmetic:

?- {X is 145.6, Y is 1.609344}.
X:: 145.6000000000000...,
Y:: 1.609344000000000... .

The answers indicate there is no precise binary representation for the floating point constants. Now when calculating X, there is an accumulated error:

% X is error in km.
?- {X is 145.6 - 90*1.609344}, range(X,R). 
R = [0.7590399999999136, 0.7590400000000557],
X:: 0.759040000000... .

Maybe you can expand on what you mean by the “other direction”. It probably isn’t this:

% X is error in mi.
?- {X is 145.6/1.609344 - 90}, range(X,R).
R = [0.47164558975578075, 0.4716455897558518],
X:: 0.471645589755... .

In my original post I had two formulations, with two
outcomes, one was “Yes” Ok, the other was “No” Not Ok:

Why is it correct? Its correct since the road sign shows
miles to zero digits after the period, i.e. it shows 90 miles
and not 90.0 miles. And 90.47 rounded to zero digits is indeed 90.

Why is it incorrect? Its incorrect since the road sign
showed 145.6, so it showed one digit after the period.
And 144.84 rounded to one digit after the period gives 144.8,

and not 145.6. But I even don’t know how a units package
would or could express such roundings?

My recent thinking is such rounding could have a place in CLAM (Constraint
Logic Abstract Machine), as part of some interval arithmetic. Particularly
pointed intervals, like 145.6 is basically the interval [145.55 .. 145.65),

including the lower bound excluding the upper bound. The value 145.6 is
associated with the interval, and not some midpoint, has to do that the
rounded value is the associated point. So all values in the interval round to

the associated rounded value. But I didn’t do a thorough research yet.
It would basically give a different rationalize and associated interval computation
from input, a more business like rationalize that requires that the number

scanner tokenizer also records the number of fractional digits in the input. So
that for example 90 and 90.0 are not the same when it comes to
rationalize and associated interval computation from some given input.

Most fixnum rounding have midpoint = rounded value:

145.6 ~~> [145.55 .. 145.65) ~~> (145.55 + 145.65)/2 = 145.6
90    ~~> [89.5 ..90.5)      ~~> (89.5 + 90.5)/2 = 90

But some rounding, like for example automatically choosing a scale,
i.e. going from bytes to kilo bytes, mega bytes, giga bytes etc..,
many directory listings can do that when they show a file size,

I guess the associated intervals and rounded values are more exotic.

You can express rounding with clpBNR by using an integer + a small epsilon.

round(X, Round) :-
    Round::integer(-inf, inf), Eps::real(-0.5, 0.5),
    {Round+Eps =:= X}.
% round to N digit
round(N, X, Round) :-
    Y::integer(-inf, inf), Eps::real(-0.5, 0.5),
    {Y+Eps =:= X * 10^N, Round is Y / 10^N}.

The only problem with this code is for limit values, where it is difficult to implement the rule that 0.5 should round to 1 and not to zero.
This code will keep both possibilities.
The reason is that clpBNR does not support open interval for reals like ]-0.5, 0.5].
So you can express the original problem as follows:

?- qeval(V*mile =:= 145.6*km in mile), round(V, Round).
Round = 90,
V:: 90.471645589755... .
?- qeval(V*km =:= 90*mile in km), round(1, V, _Round), Round is float(_Round).
V = 452628r3125,
Round = 144.8. % which is wrong
1 Like

Maybe you’re looking for something equivalent to the following in clpBNR:

?- Mi::real(89.5,90.5), Km::real(145.55,145.65), {Mi*1.609344 =:= Km}.
Mi::real(90.44057703014393, 90.5),
Km::real(145.54999999999998, 145.64563200000003).

Things to note:

  • while you do want “rounded” versions of Mi and Km, you don’t want the same for the conversion factor (1.609344).
  • the bounds of Mi and Km are not precisely converted to binary, so there may be additional outward rounding to ensure completeness.
  • the final interval values of Mi and Km are further narrowed as a result of applying the constraint.

It might be worth considering introducing the concept of a numeric string literal, representing a rounded real value, into the clpBNR sub-language, so you could write:

?- {Mi is "90", Km is "145.6", Mi*1.609344 =:= Km}.

On a general note, the distinction between an open and closed interval gets lost when considering floating point errors introduced when converting to a binary double value.

?- {X is 145.5}, range(X,R).
X = 145.5,
R = [145.5, 145.5].
% but 
?- {X is 145.55}, range(X,R).
R = [145.54999999999998, 145.55000000000004],
X:: 145.5500000000000... .
1 Like