Copyright | (c) Alice Rixte 2025 |
---|---|
License | BSD 3 |
Maintainer | alice.rixte@u-bordeaux.fr |
Stability | unstable |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Data.Units.Base.Convert
Description
Conversion between units. Use
, from
, or to
to convert
between two units of the same dimension.fromTo
Implementing conversions for custom units
Depending on how the custom unit is converted to its standard unit, there are three ways to implement its conversion summarized in the following table and described with further details afterwards:
Which instances to declare | Note | |
---|---|---|
Conversion factor | and
using
the default
implementations
for fromBaseUnit and
toBaseUnit |
|
Affine conversion | and
|
|
Non linear conversion |
| ,
and
cannot be used |
Multiplication by a conversion factor
For units that can be converted to and from their corresponding standard
units by multiplication of a converion factor, you only need to declare an
instance of
, likeConversionFactor
instance Fractional a => ConversionFactor Hour a where factor = 3600 instance Fractional a => ConvertibleUnit Hour a -- uses default implementations forfromBaseUnit
andtoBaseUnit
>>>
fromTo @Hour @Second 1
Second 3600.0>>>
fromTo' @Hour @Second 1
Second 3600.0
Affine conversion (with an offset)
Some units cannot be conversed by a simple multiplication. For instance, the
conversion between Celsius degrees and Kelvin degrees involves addition
x °C = x + 273.15 K
.
However, when considered as differences of temperatures, Celsius degrees
are converted to Kelvin degrees by a multiplication of 1
.
This can be expressed by the following instances:
instance Num a => ConversionFactor Celsius a where factor = 1 instance Fractional a => ConvertibleUnit Celsius a where toBaseUnit (Celsius x) = Kelvin (x - 273.15) fromBaseUnit (Kelvin x) = Celsius (x + 273.15)
>>>
fromTo @Celsius @Kelvin 0
Kelvin 273.15>>>
fromTo' @Celsius @Kelvin 0
Kelvin 0.0
Other conversions
Any other conversion can be implemented, like for instance logarithmic units.
In this case, you should only give an instance for
, and
no instance for ConvertibleUnit
. See for instance linear picth
ConversionFactor
.Tet
Synopsis
- type family DimEq (u :: Unit) (v :: Unit) where ...
- class (IsUnit u, IsUnit (BaseUnitOf u)) => ConvertibleUnit (u :: Unit) a where
- toBaseUnit :: u a -> BaseUnitOf u a
- fromBaseUnit :: BaseUnitOf u a -> u a
- type FromTo (u :: Unit) (v :: Unit) a = (DimEq u v, ConvertibleUnit u a, ConvertibleUnit v a)
- fromTo :: FromTo u v a => u a -> v a
- from :: FromTo u v a => u a -> v a
- to :: forall v u a. FromTo u v a => u a -> v a
- ($~) :: FromTo u v a => (v a -> b) -> u a -> b
- (~&) :: FromTo u v a => u a -> (v a -> b) -> b
- class (ConvertibleUnit u a, Fractional a) => ConversionFactor (u :: Unit) a where
- factor :: a
- toBaseUnit' :: ConversionFactor u a => u a -> BaseUnitOf u a
- fromBaseUnit' :: ConversionFactor u a => BaseUnitOf u a -> u a
- type FromTo' (u :: Unit) (v :: Unit) a = (DimEq u v, ConversionFactor u a, ConversionFactor v a)
- fromTo' :: FromTo' u v a => u a -> v a
- from' :: FromTo' u v a => u a -> v a
- to' :: forall v u a. FromTo' u v a => u a -> v a
Documentation
type family DimEq (u :: Unit) (v :: Unit) where ... Source #
A constraint to test whether two units have
Generic conversion between units
class (IsUnit u, IsUnit (BaseUnitOf u)) => ConvertibleUnit (u :: Unit) a where Source #
A unit whose quantities are convertible from that unit to its corresponding base unit.
Instances must satisfy the following law :
toBaseUnit
.fromBaseUnit
==id
Minimal complete definition
Nothing
Methods
toBaseUnit :: u a -> BaseUnitOf u a Source #
Convert a quantity to its base unit.
>>>
import Data.Units.NonStd.Time
>>>
toBaseUnit @Hour 1
Second 3600.0>>>
toBaseUnit (Hour 1)
Second 3600.0>>>
toBaseUnit @(Kilo Meter ./. Hour) 36
quantity @(Meter .*. Second .^- 1) 10.0>>>
toBaseUnit (Celsius 0)
Kelvin 273.15
default toBaseUnit :: ConversionFactor u a => u a -> BaseUnitOf u a Source #
fromBaseUnit :: BaseUnitOf u a -> u a Source #
Convert a quantity from its base unit to another unit.
>>>
fromBaseUnit @Hour 1800
Hour 0.5>>>
fromBaseUnit 1800 :: Hour Double
Hour 0.5>>>
fromBaseUnit @(Kilo Meter ./. Hour) 10
quantity @(Kilo Meter .*. Hour .^- 1) 36.0>>>
fromBaseUnit @Celsius 0
Celsius (-273.15)
default fromBaseUnit :: ConversionFactor u a => BaseUnitOf u a -> u a Source #
Instances
type FromTo (u :: Unit) (v :: Unit) a = (DimEq u v, ConvertibleUnit u a, ConvertibleUnit v a) Source #
A constraint that is satisfied when both units have the same dimension and
are such that u
can be converted to v
.
fromTo :: FromTo u v a => u a -> v a Source #
Conversion between two quantities with the same dimension.
>>>
fromTo @Celsius @Kelvin 0
Kelvin 273.15>>>
fromTo @(Milli Second) @Hour 1
Hour 2.7777777777777776e-7>>>
fromTo (Milli (Second 1)) :: Hour Double
Hour 2.7777777777777776e-7>>>
fromTo @Turn @Degree (1/4) -- angle conversion
Degree 90.0>>>
fromTo @(Kilo Meter ./. Hour) @(Milli Meter ./. Milli Second) 36
quantity @(Milli Meter .*. Milli Second .^- 1) 10.0
from :: FromTo u v a => u a -> v a Source #
A mere synonym of
where it is more intuitive to use only one
type application.fromTo
>>>
from @Celsius 0 :: Kelvin Double
Kelvin 273.15
to :: forall v u a. FromTo u v a => u a -> v a Source #
Same as
but the type applications are reversedfromTo
>>>
to @Kelvin (Celsius 0)
Kelvin 273.15
($~) :: FromTo u v a => (v a -> b) -> u a -> b infixr 0 Source #
A convenient operator for converting a unit before feeding it to a function.
>>>
import Linear
>>>
rotation (Radian th) = V2 (V2 (cos th) (- sin th)) (V2 (sin th) (cos th))
>>>
rotation $~ Degree 90
V2 (V2 6.123031769111886e-17 (-1.0)) (V2 1.0 6.123031769111886e-17)
(~&) :: FromTo u v a => u a -> (v a -> b) -> b infixl 1 Source #
Same as
but with arguments flipped.($~)
Conversion using conversion factors
class (ConvertibleUnit u a, Fractional a) => ConversionFactor (u :: Unit) a where Source #
Unit that can be converted to their corresponding standard unit by multiplication with a conversion factor.
Instances must satisfy the following laws:
u ==toBaseUnit
quantity
(unQuantity
q *factor
u)
u ==fromBaseUnit
quantity
('unQuantity
q /factor
u)
Methods
Multiplying a quantity of type u a
with
will convert it
to its corresponding base unit factor
BaseUnitOf u a
>>>
factor @Hour :: Double
3600.0>>>
factor @Celsius :: Double
1.0>>>
factor @(Kilo Meter ./. Hour) :: Double
0.2777777777777778
Instances
toBaseUnit' :: ConversionFactor u a => u a -> BaseUnitOf u a Source #
Convert a quantity to its corresponding base unit by multiplying it
by
.factor
>>>
toBaseUnit' @Hour 1
Second 3600.0>>>
toBaseUnit' (Hour 1)
Second 3600.0>>>
toBaseUnit' @(Kilo Meter ./. Hour) 36
quantity @(Meter .*. Second .^- 1) 10.0>>>
toBaseUnit' (Celsius 0)
Kelvin 0.0
fromBaseUnit' :: ConversionFactor u a => BaseUnitOf u a -> u a Source #
Convert a standard quantity to a unit u
by dividing it by
by
.factor
>>>
fromBaseUnit' @Hour 1800
Hour 0.5>>>
fromBaseUnit' 1800 :: Hour Double
Hour 0.5>>>
fromBaseUnit' @(Kilo Meter ./. Hour) 10
quantity @(Kilo Meter .*. Hour .^- 1) 36.0>>>
fromBaseUnit' @Celsius 0
Celsius 0.0
type FromTo' (u :: Unit) (v :: Unit) a = (DimEq u v, ConversionFactor u a, ConversionFactor v a) Source #
A constraint that is satisfied when both units have the same dimension and
are such that u
can be converted to v
by using a conversion factor.
fromTo' :: FromTo' u v a => u a -> v a Source #
Conversion, using conversion factors, between two quantities with the same dimension
>>>
fromTo' @Celsius @Kelvin 0
Kelvin 0.0>>>
fromTo' @(Milli Second) @Hour 1
Hour 2.7777777777777776e-7>>>
fromTo' (Milli (Second 1)) :: Hour Double
Hour 2.7777777777777776e-7>>>
fromTo' @Turn @Degree (1/4) -- angle conversion
Degree 90.0>>>
fromTo' @(Kilo Meter ./. Hour) @(Milli Meter ./. Milli Second) 36
quantity @(Milli Meter .*. Milli Second .^- 1) 10.0