1:- module(units, [
2 op(600, yfx, as),
3 op(600, yfx, in),
4 op(300, fy, quantity),
5 op(300, fy, unit),
6 op(300, fy, quantity_point),
7 op(300, fy, origin),
8 op(300, fy, point),
9 op(300, fy, quantity_from_zero),
10 op(300, yfx, quantity_from),
11 op(300, yfx, point_for),
12 op(100, yf, []),
13 op(99, xfy, :),
14
15 qeval/1,
16 qformat/1,
17 qformat/2,
18
19 alias/2,
20 dimension_symbol/2,
21 kind/1,
22 % quantity_character/2,
23 quantity_formula/2,
24 quantity_parent/2,
25
26 absolute_point_origin/2,
27 no_space_before_unit_symbol/1,
28 prefix/3,
29 relative_point_origin/2,
30 unit_kind/2,
31 unit_origin/2,
32 unit_symbol/2,
33 unit_symbol_formula/3
34]).
49:- use_module(library(dcg/high_order)). 50:- use_module(library(clpBNR)). 51:- use_module(library(error)). 52:- use_module(library(yall)). 53:- use_module(library(apply)). 54:- use_module(library(apply_macros)). 55:- use_module(units/utils). 56:- use_module(units/search). 57:- use_module(units/quantity). 58:- use_module(units/unit_defs).
Examples:
units:alias(my_meter, si:metre).
72:- multifile alias/2.
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
88:- multifile dimension_symbol/2.
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.
112:- multifile kind/1. 113:- multifile quantity_character/2.
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)).
132:- multifile quantity_formula/2.
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.
150:- multifile quantity_parent/2.
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.
172:- multifile absolute_point_origin/2.
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).
194:- multifile no_space_before_unit_symbol/1.
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).
224:- multifile prefix/3.
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)).
244:- multifile relative_point_origin/2.
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.
261:- multifile unit_kind/2.
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).
290:- multifile unit_origin/2.
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.
317:- multifile unit_symbol/2.
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.
344:- multifile unit_symbol_formula/3. 345 346unitsabsolute_point_origin(0, _). 347unitsdimension_symbol(dim_1, ''). 348unitsquantity_parent(1, dim_1). 349unitsunit_kind(1, 1). 350unitsunit_symbol(1, 1). 351 352:- use_module(units/systems/isq).
"~p"
) for the numerical value of the quantity.
358qformat(M) :-
359 qformat("~p", M).
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.
387qformat(VFormat, M) :-
388 qeval(X is M),
389 X = V*_[U],
390 ( U == 1
391 -> Symbol = "",
392 Space = ""
393 ; mapexpr(unit, U, Symbol),
394 ( aliased(no_space_before_unit_symbol(U))
395 -> Space = ""
396 ; Space = " "
397 )
398 ),
399 string_concat(VFormat, "~s~w", Format),
400 format(Format, [V, Space, Symbol]).
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
).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.
431errorhas_type(quantity, Term) :- 432 !, 433 catch(eval_(no, Term, R), _, fail), 434 is_dict(R, q). 435errorhas_type(quantity_point, Term) :- 436 !, 437 catch(eval_(no, Term, R), _, fail), 438 is_dict(R, qp). 439errorhas_type(Quantity, Term) :- 440 ground(Quantity), 441 any_quantity(Quantity), 442 !, 443 catch(eval_(no, Term, R), _, fail), 444 ( is_dict(R, q) 445 -> Q = R.q 446 ; is_dict(R, qp), 447 Q = R.q.q 448 ), 449 implicitly_convertible(Q, Quantity). 450 451unit_origin_0(M, Module:PrefixUnit, Origin), 452 PrefixUnit =.. [Prefix, Unit], 453 prefix(Module:Prefix, _, _) => 454 unit_origin_0(M, Unit, Origin). 455unit_origin_0(M, Unit, Origin) => 456 ( aliased(unit_origin(Unit, O)) 457 -> normalize_origin(M, O, Origin) 458 ; eval_(M, 0*Unit, Q), 459 Origin = qp{o: 0, q: Q} 460 ). 461 462:- table all_origin_/1. 463 464all_origin_(Origin) :- 465 ( absolute_point_origin(Origin, _) 466 ; relative_point_origin(Origin, _) 467 ). 468 469all_origin(Origin) :- 470 lazy(aliased(all_origin_(Origin)), Origin). 471 472normalize_origin(M, Origin, qp{o: Origin, q: Q}) :- 473 when(ground(Origin), normalize_origin_(M, Origin, Q)), 474 eval_(M, 0*_[_], Q). 475normalize_origin_(M, Origin, Q), unit_origin(Unit, Origin) => 476 eval_(M, Unit, R), 477 Q = R.put([v=0]). 478normalize_origin_(M, Origin, Q), absolute_point_origin(Origin, Quantity) => 479 eval_(M, Quantity[_], R), 480 Q = R.put([v=0]). 481normalize_origin_(M, Origin, Q), relative_point_origin(Origin, Expr) => 482 eval_(M, Expr, QP), 483 Q = QP.q.put([v=0]). 484normalize_origin_(M, Alias, Q), alias(Alias, Origin) => 485 normalize_origin_(M, Origin, QP), 486 Q = QP.q. 487 488common_origin(O1, F1, O2, F2, O) :- 489 once(iterative_deepening(1, common_origin_(O1, F1, O2, F2, O))). 490 491common_origin(O, F, O, F, O, _-N) :- 492 setarg(1, N, no), 493 eval_(no, 0*_[_], F). 494common_origin(O1, F1, O2, F2, O, N) :- 495 relative_point_origin(O1, Expr), 496 eval_(no, Expr, R), 497 common_origin_(R.o, FF1, O2, F2, O, N), 498 F1 = R.q + FF1. 499common_origin(Alias, F1, O2, F2, O, N) :- 500 alias(Alias, O1), 501 common_origin_(O1, F1, O2, F2, O, N). 502common_origin_(O1, F1, O2, F2, O, Limit-N) :- 503 ( Limit > 0 504 -> Limit1 is Limit - 1 505 ; nb_setarg(1, N, depth_limit_exceeded), 506 fail 507 ), 508 ( common_origin(O1, F1, O2, F2, O, Limit1-N) 509 ; common_origin(O2, F2, O1, F1, O, Limit1-N) 510 ). 511 512comparable(M, AB, R) :- 513 AB =.. [Op, A, B], 514 eval_(M, B, B1), 515 is_dict(B1, BTag), 516 ( Op == is, var(A) 517 -> comparable_is(A, BTag:B1, R) 518 ; eval_(M, A, A1), 519 is_dict(A1, ATag), 520 comparable(M, Op, ATag:A1, BTag:B1, R) 521 ). 522comparable(M, is, qp:A, qp:B, R) => 523 ( common_origin(A.o, F1, B.o, F2, _) 524 -> comparable(M, A.q is (F2 + B.q) - F1, RQ), 525 R = A.put([q=RQ]) 526 ; domain_error(A.o, B.o) 527 ). 528comparable(M, =:=, qp:A, qp:B, R) => 529 ( common_origin(A.o, F1, B.o, F2, O) 530 -> comparable(M, A.q + F1 =:= F2 + B.q, RQ), 531 R = qp{o: O, q: RQ} 532 ; domain_error(A.o, B.o) 533 ). 534comparable(M, =\=, qp:A, qp:B, R) => 535 ( common_origin(A.o, F1, B.o, F2, O) 536 -> comparable(M, A.q + F1 =\= F2 + B.q, RQ), 537 R = qp{o: O, q: RQ} 538 ; domain_error(A.o, B.o) 539 ). 540comparable(M, -, qp:A, qp:B, R) => 541 ( common_origin(A.o, F1, B.o, F2, _) 542 -> comparable(M, (F1 + A.q) - (F2 + B.q), R) 543 ; domain_error(A.o, B.o) 544 ). 545comparable(M, -, qp:A, q:B, R) => 546 comparable(M, A.q - B, Q), 547 R = A.put([q=Q]). 548comparable(M, +, qp:A, q:B, R) => 549 comparable(M, +, q:(A.q), q:B, RQ), 550 R = A.put([q=RQ]). 551comparable(M, +, q:A, qp:B, R) => 552 comparable(M, +, qp:B, q:A, R). 553comparable(_, Op, q:A, q:B, R) => 554 ( common_quantity(A.q, B.q, Q), 555 same_kind(A.q, B.q) 556 -> ( common_unit(A.u, AV, B.u, BV, U) 557 -> ( Op == is 558 -> A.v = A2, 559 normalize(B.v*BV/AV, B2) 560 ; normalize(A.v*AV, A2), 561 normalize(B.v*BV, B2) 562 ), 563 V =.. [Op, A2, B2], 564 R = q{v: V, u: U, q: Q} 565 ; domain_error(A.u, B.u) 566 ) 567 ; domain_error(A.q, B.q) 568 ). 569 570comparable_is(A, q:B, R) => 571 R = B.put([v=(V is B.v)]), 572 A = V*B.q[B.u]. 573comparable_is(A, qp:B, R) => 574 comparable_is(AQ, q:(B.q), RQ), 575 R = B.put([q=RQ]), 576 O = B.o, 577 ( (var(O) ; O = 0) 578 -> Origin = origin(O) 579 ; Origin = O 580 ), 581 A = Origin+AQ. 582 583:- module_transparent(qeval/1).
Expr can be:
Result is SubExpr
.
qeval(X is 3*si:metre + 50*si:centimetre)
where
Op` is one of =:=
, =\=
, <
, =<
, >
, >=
.
qeval(1*si:kilometre =:= 1000*si:metre)
{SubExpr}
.
qeval({X*si:metre =:= 10*si:foot})
(Expr1, Expr2, ...)
.
Supported sub-expressions within Expr:+A
, -A
, A+B
, A-B
, A*B
, A/B
, A**N
(or A^N
).
QExpr as QuantityTypeExpr
: Casts quantity QExpr to QuantityTypeExpr.
Example: `qeval(X is 10*si:metre/si:second as isq:speed)`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.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.3
, pi
, random_float
) are treated as dimensionless quantities with unit 1
.is
, bound to the result.
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.
647qeval((A, B)) => 648 qeval(A), 649 qeval(B). 650qeval(@(Goal)) => 651 call(Goal). 652qeval(Expr) => 653 context_module(M), 654 eval_(M, Expr, Q), 655 is_dict(Q, Tag), 656 qeval_call(Tag:Q). 657 658qeval_call(q:Q) => 659 V = Q.v, 660 ( (ground(V) ; V = {_} ; (V = (R is E), var(R), ground(E))) 661 -> call(V) 662 ; call({V}) 663 ). 664qeval_call(qp:P) => 665 qeval_call(q:(P.q)). 666 667eval_(M, {ExprIn}, R) => 668 eval_(M, ExprIn, ExprOut), 669 R = ExprOut.put(v, {ExprOut.v}). 670eval_(M, Result is ExprIn, R) => 671 comparable(M, Result is ExprIn, R). 672eval_(M, +A, R) => 673 eval_(M, A, A1), 674 R = A1.put(v, +A1.v). 675eval_(M, -A, R) => 676 eval_(M, A, A1), 677 R = A1.put(v, -A1.v). 678eval_(M, A+B, R) => 679 comparable(M, A+B, R). 680eval_(M, A-B, R) => 681 comparable(M, A-B, R). 682eval_(M, A=:=B, R) => 683 comparable(M, A=:=B, R). 684eval_(M, A=\=B, R) => 685 comparable(M, A=\=B, R). 686eval_(M, A<B, R) => 687 comparable(M, A<B, R). 688eval_(M, A>B, R) => 689 comparable(M, A>B, R). 690eval_(M, A=<B, R) => 691 comparable(M, A=<B, R). 692eval_(M, A>=B, R) => 693 comparable(M, A>=B, R). 694eval_(M, A*B, R) => 695 eval_(M, A, A1), 696 eval_(M, B, B1), 697 normalize_kind(A1.q*B1.q, Q), 698 normalize(A1.u*B1.u, U), 699 normalize(A1.v*B1.v, V), 700 R = q{v: V, q: Q, u: U}. 701eval_(M, A/B, R) => 702 eval_(M, A, A1), 703 eval_(M, B, B1), 704 normalize_kind(A1.q/B1.q, Q), 705 normalize(A1.u/B1.u, U), 706 normalize(A1.v/B1.v, V), 707 R = q{v: V, q: Q, u: U}. 708eval_(M, A**N, R) => 709 eval_(M, A, A1), 710 normalize_kind(A1.q**N, Q), 711 normalize(A1.u**N, U), 712 normalize(A1.v**N, V), 713 R = q{v: V, q: Q, u: U}. 714eval_(M, A^N, R) => 715 eval_(M, A**N, R). 716eval_(M, in(Expr, Unit), R) => 717 eval_(M, Expr, R1), 718 ( is_dict(R1, qp) 719 -> eval_(M, in(R1.q, Unit), Q), 720 R = R1.put([q=Q]) 721 ; eval_(M, Unit, Q), 722 ( implicitly_convertible(R1.q, Q.q) 723 -> common_unit(R1.u, F1, Q.u, F2, _), 724 normalize(R1.v*F1/F2, V), 725 R = q{v: V, q: R1.q, u: Q.u} 726 ; domain_error(R1.q, Q.q) 727 ) 728 ). 729eval_(M, as(Expr, Quantity), R), any_quantity(Quantity) => 730 eval_(M, Expr, R1), 731 ( is_dict(R1, qp) 732 -> eval_(M, as(R1.q, Quantity), Q), 733 R = R1.put([q=Q]) 734 ; ( implicitly_convertible(R1.q, Quantity) 735 -> R = R1.put(q, Quantity) 736 ; domain_error(R1.q, Quantity) 737 ) 738 ). 739eval_(M, force_as(Expr, Quantity), R), any_quantity(Quantity) => 740 eval_(M, Expr, R1), 741 ( is_dict(R1, qp) 742 -> eval_(M, force_as(R1.q, Quantity), Q), 743 R = R1.put([q=Q]) 744 ; ( explicitly_convertible(R1.q, Quantity) 745 -> R = R1.put(q, Quantity) 746 ; domain_error(R1.q, Quantity) 747 ) 748 ). 749eval_(M, cast(Expr, Quantity), R), any_quantity(Quantity) => 750 eval_(M, Expr, R1), 751 ( is_dict(R1, qp) 752 -> eval_(M, cast(R1.q, Quantity), Q), 753 R = R1.put([q=Q]) 754 ; ( common_quantity(R1.q, Quantity, _) 755 -> R = R1.put(q, Quantity) 756 ; domain_error(R1.q, Quantity) 757 ) 758 ). 759eval_(_, pi, R) => 760 R = q{v: pi, q: 1, u: 1}. 761eval_(_, random_float, R) => 762 R = q{v: random_float, q: 1, u: 1}. 763eval_(M, unit(X), R), normalize_unit(M, X, U) => 764 when(ground(U), all_unit_kind(U, UKind)), 765 when((ground(UKind), ground(Q)), implicitly_convertible(UKind, Q)), 766 R = q{v: 1, q: Q, u: U}. 767eval_(M, quantity(Quantity), R) => 768 Quantity = _*_[_], 769 eval_(M, Quantity, R). 770eval_(M, QuantityExpr[UnitExpr], R) => 771 eval_q(QuantityExpr, Q), 772 eval_(M, unit(UnitExpr), Unit), 773 ( implicitly_convertible(Unit.q, Q) 774 -> true 775 ; domain_error(Unit.q, Q) 776 ), 777 R = Unit.put([q=Q]). 778eval_(M, point(Expr), R) => 779 eval_(M, Expr, Q), 780 unit_origin_0(M, Q.u, Origin), 781 R = Origin.put([q=Q]). 782eval_(M, quantity_point(QP), R) => 783 QP = O + Q, 784 ( var(O) 785 -> Origin = origin(O) 786 ; Origin = O 787 ), 788 ( var(Q) 789 -> Quantity = quantity(Q) 790 ; Quantity = Q 791 ), 792 eval_(M, Origin + Quantity, R). 793eval_(M, origin(Origin), R), all_origin(Origin) => 794 normalize_origin(M, Origin, R). 795eval_(M, exp(Expr), R) => 796 eval_(M, Expr in 1, R1), 797 R = R1.put([v=exp(R1.v)]). 798eval_(M, sin(Expr), R), fail_call(M:sin, Radian) => 799 eval_(M, Expr in Radian, R1), 800 R = q{v: sin(R1.v), q: 1, u: 1}. 801eval_(M, cos(Expr), R), fail_call(M:cos, Radian) => 802 eval_(M, Expr in Radian, R1), 803 R = q{v: cos(R1.v), q: 1, u: 1}. 804eval_(M, tan(Expr), R), fail_call(M:tan, Radian) => 805 eval_(M, Expr in Radian, R1), 806 R = q{v: tan(R1.v), q: 1, u: 1}. 807eval_(M, asin(Expr), R), fail_call(M:asin, Radian) => 808 eval_(M, Expr in 1, R1), 809 eval_(M, Radian, R2), 810 R = R2.put([v=asin(R1.v)]). 811eval_(M, acos(Expr), R), fail_call(M:acos, Radian) => 812 eval_(M, Expr in 1, R1), 813 eval_(M, Radian, R2), 814 R = R2.put([v=acos(R1.v)]). 815eval_(M, atan(Expr), R), fail_call(M:atan, Radian) => 816 eval_(M, Expr in 1, R1), 817 eval_(M, Radian, R2), 818 R = R2.put([v=atan(R1.v)]). 819eval_(M, atan2(A, B), R), fail_call(M:atan2, Radian) => 820 eval_(M, A, RA1), 821 eval_(M, B, RB1), 822 ( common_quantity(RA1.q, RB1.q, _) 823 -> ( common_unit(RA1.u, _, RB1.u, _, U) 824 -> eval_(M, RA1 in U, RA2), 825 eval_(M, RB1 in U, RB2) 826 ; domain_error(RA1.u, RB1.u) 827 ) 828 ; domain_error(RA1.q, RB1.q) 829 ), 830 eval_(M, Radian, R2), 831 R = R2.put([v=atan2(RA2.v, RB2.v)]). 832eval_(M, quantity_from_zero(Expr), R) => 833 eval_(M, Expr - origin(0), R). 834eval_(M, quantity_from(Expr, Origin), R) => 835 eval_(M, Expr, R1), 836 eval_(M, R1 - Origin in R1.q.u, R). 837eval_(M, point_for(Expr, Origin), R) => 838 ( (var(Origin) ; Origin = 0) 839 -> O = origin(Origin) 840 ; O = Origin 841 ), 842 eval_(M, O + quantity_from(Expr, Origin), R). 843eval_(_, X, R), var(X) => 844 R = q{v: X, q: 1, u: 1}. 845eval_(_, Q, R), is_dict(Q, q) => 846 R = Q. 847eval_(_, N, R), number(N) => 848 R = q{v: N, q: 1, u: 1}. 849eval_(M, UnitOrSymbol, R), ground(UnitOrSymbol), normalize_unit(M, UnitOrSymbol, Unit) => 850 all_unit_kind(Unit, Kind), 851 R = q{v: 1, q: Kind, u: Unit}. 852eval_(_, Point, R), is_dict(Point, qp) => 853 R = Point. 854eval_(M, Origin, R), all_origin(Origin) => 855 normalize_origin(M, Origin, R). 856 857eval_q(quantity(Q), R), any_quantity(Q) => 858 R = Q. 859eval_q(X, R), any_quantity(X) => 860 R = X
units
Units is a quantity and units library modeled after
mp-units
.The key features are:
*/