Did you know ... Search Documentation:
Pack units -- prolog/units.pl
PublicShow source

Units is a quantity and units library modeled after mp-units.

The key features are:

  • qeval/1 wrapper predicate for all arithmetic with units and quantities
  • Large amount of predefined units and quantities
  • safe arithmetic with units, quantities and quantity points
  • easy user customization through multi-file predicates
 alias(?AliasName, ?CanonicalName) is nondet[multifile]
Defines an alternative name (alias) for a canonical unit, quantity, or origin name. This predicate is multifile, allowing users and other modules to define new aliases.

Examples:

units:alias(my_meter, si:metre).
Arguments:
AliasName- The alternative name.
CanonicalName- The original, canonical name of the unit, quantity, or origin.
 dimension_symbol(?DimensionName, ?Symbol) is nondet[multifile]
Defines a quantity dimension with its symbolic representation. This predicate is multifile, allowing users and other modules to define new dimensions.

Examples:

units:dimension_symbol(isq:dim_length, 'L').  % Length dimension
units:dimension_symbol(isq:dim_time, 'T').    % Time dimension
units:dimension_symbol(my_dim_currency, '$'). % Custom currency dimension
Arguments:
DimensionName- The name of the quantity dimension (e.g., isq:dim_mass).
Symbol- The symbolic representation of the dimension (e.g., 'M').
 kind(?KindName) is nondet[multifile]
Declares a KindName as a distinct "kind" of quantity. This predicate is multifile, allowing users and other modules to define new kinds.

Base quantities (e.g., isq:length) are inherently kinds. kind/1 establishes other terms as distinct quantity kinds, often for specialization. For example, isq:angular_measure is declared a kind. Although its underlying dimension is 1 (dimensionless), this declaration makes it distinct from generic dimensionless quantities. Consequently, an angular measure (e.g., in radians) is not implicitly convertible to a simple unitless number, enhancing type safety by requiring explicit conversion if such a transformation is intended.

Examples:

units:kind(isq:angular_measure).       % A specialized dimensionless quantity with unit si:radian.
units:kind(isq:solid_angular_measure). % A specialized dimensionless quantity with unit si:steradian.
units:kind(my_custom_fundamental_kind).% A user-defined kind.
Arguments:
KindName- The atom or compound term representing the kind of quantity.
 quantity_formula(?QuantityName, ?Formula) is nondet[multifile]
Associate a quantity QuantityName with a specific Formula. This predicate is multifile, allowing users and other modules to define new derived quantities.

This is particularly important for child quantities that have a "constrained" definition; for example, isq:angular_measure is specifically isq:arc_length / isq:radius. Such definitions enable implicit conversions when the specific formula is matched.

Examples:

units:quantity_formula(isq:thermodynamic_efficiency,(isq:work)/(isq:heat)).
Arguments:
QuantityName- The name of the derived quantity (e.g., isq:thermodynamic_efficiency).
Formula- An expression representing how QuantityName is derived from other quantities (e.g., isq:work/isq:heat).
 quantity_parent(?ChildQuantity, ?ParentOrDimension) is nondet[multifile]
Defines a hierarchical relationship where ChildQuantity is a specialization of ParentOrDimension. This predicate is multifile, allowing users and other modules to extend the quantity hierarchy.

Examples:

units:quantity_parent(isq:length, isq:dim_length).         % isq:length is a base quantity with dimension isq:dim_length.
units:quantity_parent(isq:width, isq:length).              % isq:width is a kind of isq:length.
units:quantity_parent(isq:speed, isq:dim_length/isq:dim_time). % isq:speed's dimension is length/time.
Arguments:
ChildQuantity- The name of the child quantity (e.g., isq:width).
ParentOrDimension- The name of the parent quantity (e.g., isq:length), a dimension name (e.g., isq:dim_length), or a derived quantity (e.g., isq:length/isq:time).
 absolute_point_origin(?OriginName, ?QuantityType) is nondet[multifile]
Declares an OriginName as an absolute reference point for a given QuantityType. This predicate is multifile, allowing users and other modules to define new absolute origins.

Absolute origins serve as fundamental datums from which quantity points can be measured. Unlike relative origins, they are not defined in terms of other origins. The QuantityType specifies the kind of quantity for which this origin is a reference. For example, si:absolute_zero is an absolute origin for isq:thermodynamic_temperature. The special origin 0 is predefined as an absolute origin for any QuantityType serving as the default origin for quantities that do not have a specific named origin.

Examples:

units:absolute_point_origin(si:absolute_zero, isq:thermodynamic_temperature). % Absolute zero temperature.
units:absolute_point_origin(my_custom_epoch, isq:time).                      % A custom absolute time reference.
Arguments:
OriginName- The atom or compound term representing the name of the absolute origin.
QuantityType- The quantity type for which this origin is a reference (e.g., isq:thermodynamic_temperature).
 no_space_before_unit_symbol(?UnitName) is nondet[multifile]
Declares that the symbol associated with a specific UnitName should not be preceded by a space when a quantity is formatted (e.g., by qformat/1). This predicate is multifile, allowing users and other modules to specify formatting exceptions for unit symbols.

By default, qformat/1 inserts a space between a numeric value and its unit symbol. This predicate provides an override for units whose symbols (like the degree symbol °) should directly follow the value.

Examples:

units:no_space_before_unit_symbol(non_si:degree).
units:no_space_before_unit_symbol(non_si:arcminute).
units:no_space_before_unit_symbol(non_si:arcsecond).
Arguments:
UnitName- The unit name (an atom or compound term, e.g., non_si:degree) whose symbol should not have a preceding space.
 prefix(?PrefixName, ?Symbol, ?Factor) is nondet[multifile]
Defines a unit prefix, its symbol, and its numerical factor. This predicate is multifile, allowing users and other modules to define new prefixes.

Prefixes are used to denote multiples or submultiples of units. PrefixName is the full name of the prefix (e.g., si:kilo). Symbol is the character(s) used to represent the prefix (e.g., 'k'). Factor is the numerical multiplier associated with the prefix (e.g., 1000).

When a prefix is used with a unit (e.g., si:kilo(si:metre)), the library combines the prefix's symbol with the unit's symbol (e.g., "km") and applies the factor to the unit's value. Note that the library won't recognize the concatenated name of the prefix and unit, (e.g. si:kilometre for si:kilo(si:metre). If you want that, you can add an alias units:alias(si:kilometre, si:kilo(si:metre)). The only predefined alias in the library is si:kilogram as it is a base SI unit.

Examples:

units:prefix(si:kilo, 'k', 1000).
units:prefix(si:milli, 'm', 1/1000).
units:prefix(iec:kibi, 'Ki', 1024).
Arguments:
PrefixName- The full name of the prefix, often namespaced (e.g., si:kilo, iec:mebi).
Symbol- The symbol for the prefix (e.g., 'k', 'M').
Factor- The numerical factor the prefix represents (e.g., 1000, 1024*1024).
 relative_point_origin(?OriginName, ?Offset) is nondet[multifile]
Declares OriginName as a symbolic name for a quantity point defined by the Offset expression. The Offset expression itself evaluates to a specific point in a quantity's dimensional space. This predicate is multifile, allowing users and other modules to define new named quantity points.

This predicate establishes that OriginName is equivalent to the point denoted by Offset. The Offset expression should evaluate to a quantity point.

Examples:

units:relative_point_origin(si:ice_point, point(273.15 * si:kelvin)).
Arguments:
OriginName- The atom or compound term representing the symbolic name of the quantity point.
Offset- An expression that evaluates to a quantity point. Typically point(Quantity) or ExistingOrigin + Quantity. (e.g., point(273.15*si:kelvin) or oa + 10*m).
 unit_kind(?UnitName, ?QuantityKind) is nondet[multifile]
Associates a UnitName with a specific QuantityKind. This predicate is multifile, allowing users and other modules to define these associations.

The QuantityKind argument should be a term that represents a kind of quantity, often defined using the kind/1 predicate or being a base quantity.

Examples:

units:unit_kind(si:metre, isq:length).                 % Metre is a unit for quantities of kind length.
Arguments:
UnitName- The name of the unit (e.g., si:radian, si:metre).
QuantityKind- The specific kind of quantity this unit measures (e.g., isq:angular_measure, isq:length).
 unit_origin(?UnitName, ?OriginName) is nondet[multifile]
Associates a UnitName with a specific OriginName to be used as its default reference point when creating quantity points. This predicate is multifile, allowing users and other modules to define these associations.

Certain units, particularly for quantities like temperature, imply a specific origin that is not the absolute zero of the quantity scale. For example, si:degree_Celsius measures temperature relative to the freezing point of water (si:ice_point), whereas si:kelvin measures from absolute zero (si:absolute_zero).

When a quantity point is constructed using the point/1 functor with a unit that has an entry in unit_origin/2, the specified OriginName is used as the origin of the resulting quantity point. If a unit has no unit_origin/2 entry, its default origin is 0.

Examples:

units:unit_origin(si:kelvin, si:absolute_zero). % Kelvin measures from absolute zero.
units:unit_origin(si:degree_Celsius, si:ice_point). % Celsius measures from the ice point.
% For `point(20 * si:degree_Celsius)`, the origin will be `si:ice_point`.
% For `point(20 * si:metre)`, the origin will be `0` (as metre has no specific unit_origin).
Arguments:
UnitName- The name of the unit (e.g., si:degree_Celsius).
OriginName- The name of the origin associated with this unit (e.g., si:ice_point). This OriginName should be defined via absolute_point_origin/2 or relative_point_origin/2.
 unit_symbol(?UnitName, ?Symbol) is nondet[multifile]
Associates a base UnitName with its textual Symbol. This predicate is multifile, allowing users and other modules to define symbols for new base units.

This predicate is intended for base units not defined by a formula involving other units (which would use unit_symbol_formula/3). The Symbol is used for formatting quantities (e.g., by qformat/1) and can also be used for parsing input expressions.

The UnitName is the canonical, often namespaced, name of the unit. The Symbol is an atom representing its common textual representation.

Examples:

units:unit_symbol(si:metre, m).         % Metre symbol is 'm'.
units:unit_symbol(si:gram, g).          % Gram symbol is 'g'.
units:unit_symbol(currency:euro, '€').  % Custom Euro symbol.

Note: For derived units (e.g., si:newton) or units defined as scaled versions of others (e.g., non_si:hour), use unit_symbol_formula/3 instead.

Arguments:
UnitName- The canonical name of the base unit (e.g., si:metre, isq:ampere).
Symbol- The textual symbol for the unit (e.g., m, 'A').
 unit_symbol_formula(?UnitName, ?Symbol, ?Formula) is nondet[multifile]
Defines a derived UnitName, its textual Symbol, and its defining Formula in terms of other units. This predicate is multifile, allowing users and other modules to define new derived units.

This is the primary way to introduce units that are not base units (which use unit_symbol/2). The Formula expresses UnitName as a combination of other existing units (base, prefixed, or other derived units) and arithmetic operators (*, /, **). The Symbol is used for formatting quantities with this unit.

Examples:

units:unit_symbol_formula(si:newton, 'N', si:kilogram * si:metre / si:second**2). % Newton (force)
units:unit_symbol_formula(si:hertz, 'Hz', 1 / si:second).                       % Hertz (frequency)
units:unit_symbol_formula(non_si:hour, h, 60 * non_si:minute).                  % Hour (time)
units:unit_symbol_formula(si:degree_Celsius, '℃', si:kelvin).                   % Degree Celsius (temperature, same scale as Kelvin but different origin)

Note: For base units that are not derived from others, use unit_symbol/2.

Arguments:
UnitName- The canonical name of the derived unit (e.g., si:newton, non_si:hour).
Symbol- The textual symbol for the unit (e.g., 'N', 'h', '℃').
Formula- An expression defining the unit in terms of other units (e.g., si:kilogram*si:metre/si:second**2).
 qformat(+QuantityOrExpr) is det
This predicate is a convenience wrapper around qformat/2. It uses a default format ("~p") for the numerical value of the quantity.
 qformat(+ValueFormat, +QuantityOrExpr) is det
Formats a quantity expression or an evaluated quantity term using a specific ValueFormat for its numerical value, and prints the result to the current output stream.

The output consists of the numerical value formatted according to ValueFormat, followed by a space (unless suppressed by no_space_before_unit_symbol/1), and then the symbol of the unit. If the unit is 1 (dimensionless), no symbol or space is printed after the value.

Examples:

?- qformat("~2f", 1.23456 * si:metre).
1.23 m
true.

?- qformat("~e", 12345 * si:pascal).
1.234500e+04 Pa
true.
Arguments:
ValueFormat- A Prolog format string for the numerical value part of the quantity (e.g., "~2f", "~e", "~p").
QuantityOrExpr- An expression that qeval/1 can evaluate to a quantity, or an already evaluated quantity term.
 error:has_type(+Type, @Term) is semidet[multifile]
Hook for library(error)'s must_be/2 predicate to validate quantity-related types.

This predicate defines type checking for:

  • quantity: Succeeds if Term is a quantity (e.g., `Value*QuantityType[Unit]`).
  • quantity_point: Succeeds if Term is a quantity point (e.g., Origin+Quantity).
  • Specific quantity types (e.g., isq:length, isq:speed, kind_of(isq:energy)): Succeeds if Term can be evaluated by qeval/1 and the resulting quantity is implicitly convertible to the specified Type.

    Examples:

    ?- qeval(X is 10*si:metre), must_be(quantity, X).
    X = 10*kind_of(isq:length)[si:metre].
    
    ?- qeval(X is 10*si:metre), must_be(isq:length, X).
    X = 10*kind_of(isq:length)[si:metre].
    
    ?- qeval(P is point(20*si:degree_Celsius)), must_be(quantity_point, P).
    P = si:ice_point+20*kind_of(isq:thermodynamic_temperature)[si:degree_Celsius].
    
    ?- qeval(X is 10*si:metre), must_be(isq:time, X). % Fails
    ERROR: Type error: `isq:time' expected, found `10*kind_of(isq:length)[si:metre]'

    @param Type The expected type. Can be quantity, quantity_point, or a specific quantity type atom/compound term recognized by any_quantity/1. @param Term The term to check.

 qeval(+Expr) is det
Evaluates an arithmetic expression Expr involving quantities, units, and quantity points. This is the primary predicate for performing calculations and comparisons within the units library. It handles all supported operators, conversions, and ensures dimensional consistency.

Expr can be:

  • An assignment: Result is SubExpr.
    • If Result is a variable, it is bound to the quantity or quantity point resulting from SubExpr.
    • Example: qeval(X is 3*si:metre + 50*si:centimetre)
  • A comparison: `A Op B where Op` is one of =:=, =\=, <, =<, >, >=.
    • Both A and B are evaluated, and the comparison is performed.
    • Requires A and B to have compatible quantity types and units.
    • Example: qeval(1*si:kilometre =:= 1000*si:metre)
  • A CLP(BNR) constraint: {SubExpr}.
    • SubExpr is evaluated using CLP(BNR) arithmetic.
    • Example: qeval({X*si:metre =:= 10*si:foot})
  • A sequence of expressions: (Expr1, Expr2, ...). Supported sub-expressions within Expr:
  • Basic arithmetic: +A, -A, A+B, A-B, A*B, A/B, A**N (or A^N).
    • Operations respect quantity types and units.
    • Addition/subtraction require compatible kinds.
  • Conversions:
    • `QExpr in UnitExpr`: Converts quantity QExpr to UnitExpr. Example: `qeval(X is 1*si:foot in si:inch)`
    • QExpr as QuantityTypeExpr: Casts quantity QExpr to QuantityTypeExpr. Example: `qeval(X is 10*si:metre/si:second as isq:speed)`
  • Quantity point operations:
    • point(QExpr): Creates a quantity point from quantity QExpr. Origin is inferred from unit or defaults to 0. Example: qeval(P is point(20*si:degree_Celsius))
    • origin(OriginName): Refers to a defined origin. Example: qeval(P is si:ice_point + 5*si:kelvin)
    • quantity_from_zero(PExpr): Vector from origin 0 to point PExpr.
    • quantity_from(PExpr, OriginExpr): Vector from OriginExpr to PExpr.
    • point_for(PExpr, NewOriginExpr): Represents point PExpr relative to NewOriginExpr.
  • Disambiguation functors:
    • unit(U): Interprets U as a unit (e.g., si:metre).
    • quantity(Q): Interprets Q as a quantity (e.g., `V*Q[U]`).
    • quantity_point(QP): Interprets QP as a quantity point.
  • Numeric values (e.g., 3, pi, random_float) are treated as dimensionless quantities with unit 1.
  • Variables:
    • On the left of is, bound to the result.
    • Elsewhere, typically treated as CLP(BNR) variables of dimensionless quantity.

    Quantities are represented as `Value * QuantityType[Unit]`. Quantity points are represented as Origin + Quantity.

    Examples:

    ?- qeval(Dist is 10 * si:kilo(si:metre) + 500 * si:metre).
    Dist = 10500 * kind_of(isq:length)[si:metre].
    
    ?- qeval(TempPoint is point(25 * si:degree_Celsius)).
    TempPoint = si:zeroth_degree_Celsius+25*kind_of(isq:thermodynamic_temperature)[si:degree_Celsius].
    
    ?- qeval(({Len_m * si:metre =:= Len_ft * foot}, Len_m =:= 1)).
    Len_m = 1,
    Len_ft = 1250r381.
Arguments:
Expr- The arithmetic expression to evaluate.