unittyped-0.1: An extendable library for type-safe computations including units.

Safe HaskellNone

UnitTyped

Description

Module defining values with dimensions and units, and mathematical operations on those.

Synopsis

Documentation

class Convertable a b | b -> a whereSource

Convertable is a class that models the fact that the unit b has dimension a (of kind UnitMap).

Methods

factor :: Fractional f => Value f a b -> fSource

The multiplication factor to convert this unit between other units in the same dimension. Only the ratio matters, which one is '1' is not important, as long as all are consistent.

showunit :: Fractional f => Bool -> Value f a b -> StringSource

String representation of a unit. The boolean determines wether to use brackets (only important for the denomiator). The value should not be important for the output, its only here because it needs to be a class method.

Instances

Convertable NoDimension Count 
Convertable NoDimension Mole 
Convertable NoDimension Degree 
Convertable NoDimension Radian 
Convertable NoDimension Ppt 
Convertable NoDimension Ppb 
Convertable NoDimension Ppm 
Convertable NoDimension Permil 
Convertable NoDimension Percentage 
Convertable LuminousDimension Candela 
Convertable CurrentDimension Ampere 
Convertable TemperatureDimension Kelvin 
Convertable MassDimension Gram 
Convertable MassDimension Pound 
Convertable TimeDimension Second 
Convertable TimeDimension JulianYear 
Convertable TimeDimension Month 
Convertable TimeDimension Year 
Convertable TimeDimension Day 
Convertable TimeDimension Minute 
Convertable TimeDimension Hour 
Convertable LengthDimension Meter 
Convertable LengthDimension NauticalMile 
Convertable LengthDimension Ångström 
Convertable LengthDimension Foot 
Convertable LengthDimension Yard 
Convertable LengthDimension Inch 
Convertable LengthDimension Mile 
Convertable CurrencyUnit Gulden 
Convertable CurrencyUnit Pound 
Convertable CurrencyUnit Yen 
Convertable CurrencyUnit Dollar 
Convertable CurrencyUnit Euro 
Convertable Inductance Henry 
Convertable FluxDensity Tesla 
Convertable Flux Weber 
Convertable Conductance Siemens 
Convertable Resistance Ohm 
Convertable Capacitance Farad 
Convertable Potential Volt 
Convertable Charge Coulomb 
Convertable Pressure MmHg 
Convertable Pressure Bar 
Convertable Pressure Pascal 
Convertable Power Watt 
Convertable Energy Ev 
Convertable Energy Joule 
Convertable Force Newton 
Convertable Speed Knot 
Convertable DataUnit Bit 
Convertable DataUnit Byte 
Convertable VolumeUnit FluidOunce 
Convertable VolumeUnit Gallon 
Convertable VolumeUnit Liter 
Convertable AreaUnit Barn 
(MetaUnit m a b, Convertable a b) => Convertable a (m b) 
(Convertable a b, Convertable c d, UnitMerge a c' u, UnitNeg c c') => Convertable u (Div b d) 
(Convertable a b, Convertable c d, UnitMerge a c u) => Convertable u (Mul b d) 
Convertable (UnitCons * Time (Neg One) UnitNil) Hertz 

data Value a b c Source

A value tagged with its dimension b and unit c.

Constructors

Value a 

Instances

(Num ((Value f a b -> Value f a (m b)) -> c), Fractional f, Convertable a (m b), ~ * c (Value f a b -> Value f a (m b))) => Fractional ((Value f a b -> Value f a (m b)) -> c) 
(Num (Value f a b -> t), Fractional f, Convertable a b, ~ * t (Value f a b)) => Fractional (Value f a b -> t) 
(Fractional f, Convertable a (m b), ~ * c (Value f a b -> Value f a (m b))) => Num ((Value f a b -> Value f a (m b)) -> c) 
(Fractional f, Convertable a b, ~ * t (Value f a b)) => Num (Value f a b -> t) 
(Fractional f, Show f, Convertable a b, Show b) => Show (Value f a b) 

data Mul b d Source

A unit representing the multplication of the units b and d.

Instances

(Convertable a b, Convertable c d, UnitMerge a c u) => Convertable u (Mul b d) 

data Div b d Source

A unit representing the division of the units b by d.

Instances

(Convertable a b, Convertable c d, UnitMerge a c' u, UnitNeg c c') => Convertable u (Div b d) 

type NoDimension = UnitNilSource

This is for dimensionless values.

data Count Source

One thing.

data UnitMap whereSource

This is meant to be use as a datatype promoted to a kind. It represents a map of dimensions to type level integers. If two maps are equal, then the dimension they represent is the same.

Constructors

UnitNil :: UnitMap 
UnitCons :: a -> Number -> UnitMap -> UnitMap 

data Nat Source

Type level natural numbers (excluding zero, though).

Constructors

One 
Suc Nat 

data Number Source

Type level integers.

Constructors

Zero 
Neg Nat 
Pos Nat 

class UnitMerge map1 map2 rest | map1 map2 -> restSource

States that merging the first map with the second map produces the third argument. Merging happens by summing the two values for the same key. Typically, dimensions are merged when multiplicing two values.

Instances

UnitMerge UnitNil map2 map2 
(UnitMerge rest map2 rest2, UnitAppend unit value rest2 rec) => UnitMerge (UnitCons * unit value rest) map2 rec 

class UnitEq map1 map2 b | map1 map2 -> bSource

b is equal to True if and only if map1 and map2 represent the same dimension.

Instances

(UnitNeg map2 map2', UnitMerge map1 map2' sum, UnitNull sum b) => UnitEq map1 map2 b 

class UnitNeg map1 rest | map1 -> restSource

States that rest is the same dimension as map1, but all integers inverted. Used for division.

Instances

UnitNeg UnitNil UnitNil 
(Negate value value', UnitNeg rest rest') => UnitNeg (UnitCons * unit value rest) (UnitCons * unit value' rest') 

type POne = Pos OneSource

Type level +1

type PTwo = Pos (Suc One)Source

Type level +2

type PThree = Pos (Suc (Suc One))Source

Type level +3

type PFour = Pos (Suc (Suc (Suc One)))Source

Type level +4

type PFive = Pos (Suc (Suc (Suc (Suc One))))Source

Type level +5

type PSix = Pos (Suc (Suc (Suc (Suc (Suc One)))))Source

Type level +6

type NOne = Neg OneSource

Type level -1

type NTwo = Neg (Suc One)Source

Type level -2

type NThree = Neg (Suc (Suc One))Source

Type level -3

type NFour = Neg (Suc (Suc (Suc One)))Source

Type level -4

class (Convertable a b, Convertable c d) => Pow a b i c d | a b -> c, a b -> dSource

^ is not definable on Values in general, as the result depends on the exponent. However, we can use this class to raise a unit to a type level Number.

Instances

(Convertable a b, Convertable c d, Pow' () a b i c d) => Pow a b i c d 

coerce :: (Convertable a b, Convertable c d, Fractional f, UnitEq a c True) => Value f a b -> Value f c d -> Value f c dSource

coerce something of a specific dimension into any other unit in the same dimension. The second argument is only used for its type, but it allows nice syntax like:

>>> coerce (120 meter / second) (kilo meter / hour)
432.0 km/h

as :: (Convertable a b, Convertable c d, Fractional f, UnitEq a c True) => Value f a b -> Value f c d -> Value f c dSource

Shorthand for coerce.

one :: (Fractional f, Convertable a b) => Value f a bSource

A wrapped value with scalar value 1.

mkVal :: Fractional f => f -> Value f a bSource

Create a new value with given scalar as value.

val :: Fractional f => Value f a b -> fSource

Obtain the value of a value wrapped in a type.

(.*.) :: (Fractional f, Convertable a b, Convertable c d, UnitMerge a c u) => Value f a b -> Value f c d -> Value f u (Mul b d)Source

Multiply two values, constructing a value with as dimension the product of the dimensions, and as unit the multplication of the units.

(./.) :: (Fractional f, Convertable a b, Convertable c d, UnitMerge a c' u, UnitNeg c c') => Value f a b -> Value f c d -> Value f u (Div b d)Source

Divide two values, constructing a value with as dimension the division of the dimension of the lhs by the dimension of the rhs, and the same for the units.

(.+.) :: (Fractional f, Convertable a b, Convertable c d, UnitEq c a True) => Value f a b -> Value f c d -> Value f a bSource

Add two values with matching dimensions. Units are automatically resolved. The result will have the same unit as the lhs.

(.-.) :: (Fractional f, Convertable a b, Convertable c d, UnitEq c a True) => Value f a b -> Value f c d -> Value f a bSource

Subtract two values with matching dimensions. Units are automatically resolved. The result will have the same unit as the lhs.

(.$.) :: (Convertable a b, Fractional f) => f -> Value f a b -> Value f a bSource

Multiply a unit by a scalar.

(~.) :: (Convertable a b, Convertable c d, Fractional f, UnitEq a c True) => Value f a b -> Value f c d -> Value f c dSource

Shorthand for coerce.

(.==.) :: (Convertable a b, Convertable c d, UnitEq c a True) => Value Rational a b -> Value Rational c d -> BoolSource

== for values. Only defined for values with rational contents. Can be used on any two values with the same dimension.

(.<=.) :: (Convertable a b, Convertable c d, UnitEq c a True) => Value Rational a b -> Value Rational c d -> BoolSource

<= on values. Only defined for values with rational contents. Can be used on any two values with the same dimension.

(.<.) :: (Convertable a b, Convertable c d, UnitEq c a True) => Value Rational a b -> Value Rational c d -> BoolSource

< on values. Only defined for values with rational contents. Can be used on any two values with the same dimension.

(.>=.) :: (Convertable a b, Convertable c d, UnitEq c a True) => Value Rational a b -> Value Rational c d -> BoolSource

>= on values. Only defined for values with rational contents. Can be used on any two values with the same dimension.

(.>.) :: (Convertable a b, Convertable c d, UnitEq c a True) => Value Rational a b -> Value Rational c d -> BoolSource

> on values. Only defined for values with rational contents. Can be used on any two values with the same dimension.

square :: (Fractional f, Convertable a b, Pow a b PTwo c d) => Value f a b -> Value f c dSource

Calculate the square of a value. Identical to pow2, reads better on units:

>>> 100 . square meter `as` square yard
119.59900463010803 yd⋅yd⋅#

cubic :: (Fractional f, Convertable a b, Pow a b PThree c d) => Value f a b -> Value f c dSource

Calculate the third power of a value. Identical to pow3, reads better on units:

>>> 1 . cubic inch `as` mili liter
16.387063999999995 mL

pown3 :: (Fractional f, Convertable a b, Pow a b NThree c d) => Value f a b -> Value f c dSource

Calculate x^(-3).

pown2 :: (Fractional f, Convertable a b, Pow a b NTwo c d) => Value f a b -> Value f c dSource

Calculate x^(-2).

pown1 :: (Fractional f, Convertable a b, Pow a b NOne c d) => Value f a b -> Value f c dSource

Calculate x^(-1).

pow0 :: (Fractional f, Convertable a b, Pow a b Zero c d) => Value f a b -> Value f c dSource

Calculate x^0. Yes, this is always one :: Value f NoDimension Count.

pow1 :: (Fractional f, Convertable a b, Pow a b POne c d) => Value f a b -> Value f c dSource

Calculate x^1.

pow2 :: (Fractional f, Convertable a b, Pow a b PTwo c d) => Value f a b -> Value f c dSource

Calculate x^2.

pow3 :: (Fractional f, Convertable a b, Pow a b PThree c d) => Value f a b -> Value f c dSource

Calculate x^3.

pow4 :: (Fractional f, Convertable a b, Pow a b PFour c d) => Value f a b -> Value f c dSource

Calculate x^4.

pow5 :: (Fractional f, Convertable a b, Pow a b PFive c d) => Value f a b -> Value f c dSource

Calculate x^5.

pow6 :: (Fractional f, Convertable a b, Pow a b PSix c d) => Value f a b -> Value f c dSource

Calculate x^6.