convert-units-0: Arithmetic and type checked conversions between units.
Copyright(c) Alice Rixte 2025
LicenseBSD 3
Maintaineralice.rixte@u-bordeaux.fr
Stabilityunstable
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Units.Base.Arithmetic

Description

Addition, multiplication and exponentiation of quantities. Dimension analysis is done statically via the type system.

Addition and multiplication of a quantity by a scalar

To add, multiply, divide, and so on, a quantity with a scalar , use its Fractional instance :

>>> a = Milli (Second 5)
>>> 3 * a
quantity @(Milli Second) 15
Warning
These instances are provided because they are convenient, but be careful ! This means that you can write:
>>> Second 2 * Second 3
Second 6

which does not respect dimension analysis: the multiplication of two time quantities should be of dimension and here it has dimension T.

Some of the operators proposed here solve this problem:

>>> Second 2 .*~ Second 3
quantity @(Second .^+ 2) 6
Synopsis

Addition

(.+~) :: forall u v a. FromTo' v u a => u a -> v a -> u a infixr 5 Source #

Add two quantities of same dimension. The unit of the right operand is converted to the unit of the left operand

>>> Kilo (Meter 5) .+~ Meter 80
quantity @(Kilo Meter) 5.08
>>> Meter 2 .+~ Second 3
 • Cannot convert unit ‘s’ of dimension ‘T’
   to unit ‘m’ of dimension ‘L’.

(~+.) :: FromTo' u v a => u a -> v a -> v a infixr 5 Source #

Same as (.+~) but it is the left operand that is converted.

>>> Kilo (Meter 5) ~+. Meter 80
quantity @(Kilo Meter) 5080.0

(~+~) :: (DimEq u v, ConversionFactor u a, ConversionFactor v a) => u a -> v a -> BaseUnitOf u a infixr 5 Source #

Add two quantities of same dimension and convert to the standard unit.

>>> Kilo (Meter 1) ~+~ Milli (Meter 150)
Meter 1000.15

Subtraction

(.-~) :: forall u v a. FromTo' v u a => u a -> v a -> u a infixr 5 Source #

Subtract two quantities of same dimension. The unit of the right operand is converted to the unit of the left operand

>>> Kilo (Meter 5) .-~ Meter 80
quantity @(Kilo Meter) 4.92

(~-.) :: FromTo' u v a => u a -> v a -> v a infixr 5 Source #

Same as (.-~) but it is the left operand that is converted.

>>> Kilo (Meter 5) ~-. Meter 80
Meter 4920.0

(~-~) :: (DimEq u v, ConversionFactor v a, ConversionFactor u a) => u a -> v a -> BaseUnitOf u a infixr 5 Source #

Subtract two quantities of same dimension and convert to the standard unit.

>>> Kilo (Meter 1) ~-~ Milli (Meter 150)
Meter 999.85

Multiplication

(.*.) :: (IsUnit u, IsUnit v, Num a) => u a -> v a -> (u .*. v) a infixr 7 Source #

Multiply two quantities.

Usage is not recommended, as this will result non standard units.

For instance:

>>> Kilo (Meter 2) .*. Milli (Meter 4)
quantity @(Kilo Meter .*. Milli Meter) 8

(.*~) :: forall u v a uv. (uv ~ (u .*~ v), FromTo' (u .*. v) uv a, IsUnit u, IsUnit v, IsUnit uv, Num a) => u a -> v a -> uv a infixr 7 Source #

Multiply two quantities, and tries to normalize the resulting unit, without converting to base units.

>>> Meter 2 .*~ Meter 3 .*~ Meter 4
quantity @(Meter.^+3) 24

When two multiplied units have the same dimension, the right most unit is converted to left most unit:

>>> Milli (Meter 2) .*~ Micro (Meter 3)
quantity @(Milli Meter.^+2) 6.0e-3

Derived units are not unfolded:

>>> Kilo Watt 3 .*~ Hour 5
quantity @(Kilo Watt .*. Hour) 14.999999999999998

Units are ordered, so that the result unit do not depend on the order of the computations.

>>> Meter 2 .*~ Newton 2 .*~ Kilo (Meter 2) .*~ Kilo (Gram 1)
quantity @(Newton .*. Kilo Gram .*. Meter.^+2) 8000.0

(~*.) :: forall u v a uv. (uv ~ (u ~*. v), FromTo' (u .*. v) uv a, IsUnit u, IsUnit v, IsUnit uv, Num a) => u a -> v a -> uv a infixr 7 Source #

Same as (.*~) but with right priority

>>> Meter 2 ~*. Meter 3 ~*. Meter 4
quantity @(Meter.^+3) 24
>>> Milli (Meter 2) ~*. Micro (Meter 3)
quantity @(Micro Meter.^+2) 6000.000000000001

(~*~) :: (u2 ~ (BaseUnitOf u .^+ 2), IsUnit u2, DimEq u v, ConversionFactor u a, ConversionFactor v a) => u a -> v a -> u2 a infix 7 Source #

Multiply two quantities of the same dimension and convert both of them to the corresponding standard unity.

>>> Milli (Meter 2) ~*~ Kilo (Meter 3)
quantity @(Meter .^+ 2) 6.0
>>> Meter 2 ~*~ Second 5
• Cannot convert unit ‘m’ to unit ‘s’ because their dimensions do not match.
  Dimension of ‘m’ is: L
  Dimension of ‘s’ is: T

Division

(./.) :: (IsUnit u, IsUnit v, IsUnit (u ./. v), Fractional a) => u a -> v a -> (u ./. v) a infix 7 Source #

Multiply two quantities.

Usage is not recommended, as this will result non standard units.

For instance:

>>> Kilo (Meter 2) ./. Milli (Meter 4)
quantity @(Kilo Meter .*. Milli Meter.^-1) 0.5

(./~) :: forall u v a uv. (uv ~ (u ./~ v), FromTo' (u ./. v) uv a, IsUnit u, IsUnit v, IsUnit uv, Num a) => u a -> v a -> uv a infix 7 Source #

Same (.*~) but for division.

>>> Milli (Meter 3) ./~ quantity @(Meter .^+ 2) 2
quantity @(Milli Meter.^-1) 1.5e-6

(~/.) :: forall u v a uv. (uv ~ (u ~/. v), FromTo' (u ./. v) uv a, IsUnit u, IsUnit v, IsUnit uv, Num a) => u a -> v a -> uv a infix 7 Source #

Same (~/.) but with right priority

>>> Milli (Meter 3) ~/. quantity @(Meter .^+ 2) 2
quantity @(Meter.^-1) 1.5e-3

(~/~) :: (DimEq u v, ConversionFactor u a, ConversionFactor v a) => u a -> v a -> NoUnit a infix 6 Source #

Divide two quantities of same dimensions. The numerator will be converted to the denominator

Units of the same dimension are authorized only when the units are equal.

>>> Meter 4 ~/~ Kilo (Meter 1)
NoUnit 4.0e-3

Exponentiation

(.^.) :: forall (n :: ZZ) proxy u a. (IsUnit u, KnownInt n, Fractional a) => u a -> proxy n -> (u .^. n) a infix 8 Source #

Raise a quantity to a power.

This is meant to be used with Proxy

>>> Meter 2 .^. pos2
quantity @(Meter.^+2) 4.

Usage is not recommended, as this will result non standard units.

For instance:

>>> (Meter 2 .*. Centi (Meter 30)) .^. pos2
quantity @((Meter .*. Centi Meter).^+2) 3600.0

(~^.) :: forall (n :: ZZ) proxy u a un. (un ~ (u ~^. n), FromTo' (u .^. n) un a, IsUnit u, KnownInt n, Fractional a) => u a -> proxy n -> un a infix 8 Source #

Raise a quantity to a power and tries to normalize the resulting unit, without converting to base units.

>>> Meter 2 ~^. pos2
quantity @(Meter.^+2) 4.0
>>> (Meter 2 .*. Centi (Meter 30)) ~^. pos2
quantity @(Centi Meter.^+4) 3.6e7

(.^~) :: forall (n :: ZZ) proxy u a un. (un ~ (u .^~ n), FromTo' (u .^. n) un a, IsUnit u, KnownInt n, Fractional a) => u a -> proxy n -> un a infix 8 Source #

Same as (.^~) but with priority to rightmost units.

>>> Meter 2 .^~ pos2
quantity @(Meter.^+2) 4.0
>>> (Meter 2 .*. Centi (Meter 30)) ~^. pos2
quantity @(Meter.^+4) 0.36000000000000004

(~^~) :: forall (n :: ZZ) proxy u un a. (KnownInt n, ConversionFactor u a, un ~ (BaseUnitOf u .^. n)) => u a -> proxy n -> un a infix 8 Source #

Raise a quantity to a power and convert to the standard unit.

>>> Kilo (Meter 2) ~^~ neg1
quantity @(Meter .^- 1) 5.0e-4