New version of Units pack

Hello everybody,
I have just released a new version of my new Units pack.
This new release brings:

  • numerable bugfixes for quantities conversions
  • improved the ease of user customization for adding new quantities and units
  • integration with the library error and the must_be/2 predicate for checking quantities
  • added a lot of examples to showcase how to use the library

Let me present a few simple examples to illustrate the improvements.

First, the speed example:

:- use_module(library(units)).

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

Using the library is very simple, just wrap your arithmetic with the qeval/1 predicate.
qeval/1 will first parse the whole expression, checking its correctness and then do the actual computation.
Here, the order of operation is the following:

  • Distance and Time can be of any quantities, let’s name them q1 and q2
  • Distance/Time will produce a new derived quantity q1/q2
  • as isq:speed will try to convert q1/q2 to the quantity isq:speed. Since the formula for the isq:speed quantity is isq:length/isq:time, this conversion will work only for quantities that can be convertible to isq:length and isq:time respectively.
  • Finally, Speed is assigned with the resulting expression with the quantity isq:speed
% isq:distance[si:kilo(metre)] is an explicit quantity `isq:distance`,
%   a specific type of `isq:length` with unit `si:kilo(metre)`
% si:hour is assigned a special quantity `kind_of(isq:time)`
%   which represent any type of `isq:time`
?- avg_speed(220 * isq:distance[si:kilo(metre)], 2 * si:hour, Speed).
Speed = 110 * isq:speed[si:kilo(si:metre)/si:hour].
% inverting distance and time by mistake results in an exception
?- avg_speed(2*si:hour, 220 * isq:distance[si:kilo(metre)], Speed).
ERROR: Domain error: `isq:time/isq:distance' expected, found `isq:speed'

Here is an example of using the integration with the library error for checking quantities.
Since the library record also use the library error for constructing records, we can combine both !
For example, in order to check if a quantity is an isq:width, you can use must_be(q:isq:width, MyQuantity). You need to prefix your quantity with q: so that I know that you really mean to check a quantity.

It also shows how to add new quantities:

  • horizontal_length which is a special type of the generic isq:length describing the length of a box (like isq:width or isq:height quantities)
  • horizontal_area which is a special kind of area computed from horizontal_length*isq:width
:- use_module(library(units)).
:- use_module(library(record)).

% user customization of quantities
% you can add a more specific quantity by extending the multifile predicate
%   `units:quantity_parent/2`
units:quantity_parent(horizontal_length, isq:length).
units:quantity_parent(horizontal_area, isq:area).

% don't forget to prefix all your quantities with `q:`
:- record box(length: q:horizontal_length, width: q:isq:width, height: q:isq:height).

And you use your box record like this:

% qeval can take a comma list of expressions
?- qeval((
      L is 2*horizontal_length[m],
      W is 3*isq:width[m],
      H is 1*isq:height[m]
   )),
   make_box([length(L), width(W), height(H)], Box).
L = 2 * horizontal_length[si:metre],
W = 3 * isq:width[si:metre],
H = 1 * isq:height[si:metre],
Box = box(2 * horizontal_length[si:metre], 3 * isq:width[si:metre],
          1 * isq:height[si:metre]).
% inverting horizontal_length and width won't work
?- make_box([length($W), width($L), height($H)], _).
ERROR: Type error: `q:horizontal_length' expected, found `3 * isq:width[si:metre]' (a dict)

Finally, a currency exchange example, to show some unit user customization:

:- use_module(library(units)).

% quantity_dimension/2 introduce a new basic dimension,
% similar to `isq:time` or `isq:length`
units:quantity_dimension(currency, cur).

% unit_symbol/2 adds new unit with their symbol.
% notice how euro and us_dollar are independent,
% so conversion from one to the other is impossible
units:unit_symbol(euro, €).
units:unit_symbol(us_dollar, $).

% these units should only work with quantities that are a kind of currency
units:unit_kind(euro, currency).
units:unit_kind(us_dollar, currency).

% `From` and `To` are units,
% `Rate` is a quantity with unit `To/From`, i.e. `us_dollar/euro`
exchange_rate(From, To, Rate) :-
   % user code to get real currency conversion value
   qeval(Rate is random_float *To/From).

% `From` is a quantity of type `currency`, let's say with a unit `us_dollar`
% `ToUnit` is a unit of currency, let's say `euro`
exchange_to(From, ToUnit, To) :-
   % `Rate` is going to be a quantity with unit `euro/us_dollar`
   exchange_rate(From.u, ToUnit, Rate),
   % multiplying `euro/us_dollar` with `us_dollar` will simplify the redundent unit,
   % and leave us with `euro`
   qeval(To is Rate * From).
?- qeval(FromUsd is 100*'$'),
   exchange_to(FromUsd, €, ToEuro).
FromUsd = 100 * kind_of(currency)[us_dollar],
ToEuro = 26.302733940163176 * kind_of(currency)[euro].
2 Likes