units-1.1: A domain-specific type system for dimensional analysis

Copyright(C) 2013 Richard Eisenberg
License(C) 2013 Richard Eisenberg
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone

Data.Dimensions

Contents

Description

The units package is a framework for strongly-typed dimensional analysis. This haddock documentation is generally not enough to be able to use this package effectively. Please see the readme at http://www.cis.upenn.edu/~eir/packages/units/README.html.

Some of the types below refer to declarations that are not exported and not documented here. This is because Haddock does not allow finely-tuned abstraction in documentation. (In particular, right-hand sides of type synonym declarations are always included.) If a symbol is not exported, you do not need to know anything about it to use this package.

Though it doesn't appear here, Scalar is an instance of Num, and generally has all the numeric instances that Double has.

Synopsis

Term-level combinators

(.+) :: (d1 @~ d2, Num n) => Dim n d1 -> Dim n d2 -> Dim n d1Source

Add two compatible dimensioned quantities

(.-) :: (d1 @~ d2, Num n) => Dim n d1 -> Dim n d2 -> Dim n d1Source

Subtract two compatible dimensioned quantities

(.*) :: Num n => Dim n a -> Dim n b -> Dim n (Normalize (a @+ b))Source

Multiply two dimensioned quantities

(./) :: Fractional n => Dim n a -> Dim n b -> Dim n (Normalize (a @- b))Source

Divide two dimensioned quantities

(.^) :: Fractional n => Dim n a -> Sing z -> Dim n (a @* z)Source

Raise a dimensioned quantity to a power known at compile time

(*.) :: Num n => n -> Dim n a -> Dim n aSource

Multiply a dimensioned quantity by a scalar

(.<) :: (d1 @~ d2, Ord n) => Dim n d1 -> Dim n d2 -> BoolSource

Check if one dimensioned quantity is less than a compatible one

(.>) :: (d1 @~ d2, Ord n) => Dim n d1 -> Dim n d2 -> BoolSource

Check if one dimensioned quantity is greater than a compatible one

(.<=) :: (d1 @~ d2, Ord n) => Dim n d1 -> Dim n d2 -> BoolSource

Check if one dimensioned quantity is less than or equal to a compatible one

(.>=) :: (d1 @~ d2, Ord n) => Dim n d1 -> Dim n d2 -> BoolSource

Check if one dimensioned quantity is greater than or equal to a compatible one

dimEqSource

Arguments

:: (d0 @~ d1, d0 @~ d2, Num n, Ord n) 
=> Dim n d0

If the difference between the next two arguments are less than this amount, they are considered equal

-> Dim n d1 
-> Dim n d2 
-> Bool 

Compare two compatible dimensioned quantities for equality

dimNeqSource

Arguments

:: (d0 @~ d1, d0 @~ d2, Num n, Ord n) 
=> Dim n d0

If the difference between the next two arguments are less than this amount, they are considered equal

-> Dim n d1 
-> Dim n d2 
-> Bool 

Compare two compatible dimensioned quantities for inequality

nthRoot :: ((Zero < z) ~ True, Floating n) => Sing z -> Dim n a -> Dim n (a @/ z)Source

Take the n'th root of a dimensioned quantity, where n is known at compile time

dimSqrt :: Floating n => Dim n a -> Dim n (a @/ Two)Source

Take the square root of a dimensioned quantity

dimCubeRoot :: Floating n => Dim n a -> Dim n (a @/ Three)Source

Take the cube root of a dimensioned quantity

unity :: Num n => Dim n `[]`Source

The number 1, expressed as a unitless dimensioned quantity.

zero :: Num n => Dim n dimspecSource

The number 0, polymorphic in its dimension. Use of this will often require a type annotation.

dim :: d @~ e => Dim n d -> Dim n eSource

Dimension-safe cast. See the README for more info.

dimIn :: Unit unit => MkDim (CanonicalUnit unit) -> unit -> DoubleSource

Extracts a Double from a dimensioned quantity, expressed in the given unit. For example:

 inMeters :: Length -> Double
 inMeters x = dimIn x Meter

(#) :: Unit unit => MkDim (CanonicalUnit unit) -> unit -> DoubleSource

Infix synonym for dimIn

dimOf :: Unit unit => Double -> unit -> MkDim (CanonicalUnit unit)Source

Creates a dimensioned quantity in the given unit. For example:

 height :: Length
 height = dimOf 2.0 Meter

(%) :: Unit unit => Double -> unit -> MkDim (CanonicalUnit unit)Source

Infix synonym for dimOf

Type-level unit combinators

data u1 :* u2 Source

Multiply two units to get another unit. For example: type MetersSquared = Meter :* Meter

Constructors

u1 :* u2 

Instances

(Unit u1, Unit u2) => Unit (:* u1 u2) 

data u1 :/ u2 Source

Divide two units to get another unit

Constructors

u1 :/ u2 

Instances

(Unit u1, Unit u2) => Unit (:/ u1 u2) 

data unit :^ power Source

Raise a unit to a power, known at compile time

Constructors

unit :^ (Sing power) 

Instances

(Unit unit, SingI Z power) => Unit (:^ unit power) 

data prefix :@ unit Source

Multiply a conversion ratio by some constant. Used for defining prefixes.

Constructors

prefix :@ unit 

Instances

(~ Bool (CheckCanonical unit) False, Unit unit, UnitPrefix prefix) => Unit (:@ prefix unit) 

class UnitPrefix prefix whereSource

A class for user-defined prefixes

Methods

multiplier :: prefix -> DoubleSource

This should return the desired multiplier for the prefix being defined. This function must not inspect its argument.

Type-level dimensioned-quantity combinators

type family d1 (%*) d2 :: *Source

Multiply two dimension types to produce a new one. For example:

 type Velocity = Length %/ Time

type family d1 (%/) d2 :: *Source

Divide two dimension types to produce a new one

type family d (%^) z :: *Source

Exponentiate a dimension type to an integer

Creating new units

class Unit unit whereSource

Class of units. Make an instance of this class to define a new unit.

Associated Types

type BaseUnit unit :: *Source

The base unit of this unit: what this unit is defined in terms of. For units that are not defined in terms of anything else, the base unit should be Canonical.

Methods

conversionRatio :: unit -> DoubleSource

The conversion ratio from the base unit to this unit. If left out, a conversion ratio of 1 is assumed.

For example:

 instance Unit Foot where
   type BaseUnit Foot = Meter
   conversionRatio _ = 0.3048

Implementations should never examine their argument!

Instances

Unit Number 
Unit Katal 
Unit Sievert 
Unit Gray 
Unit Becquerel 
Unit Lux 
Unit Lumen 
Unit Henry 
Unit Tesla 
Unit Weber 
Unit Siemens 
Unit Ohm 
Unit Farad 
Unit Volt 
Unit Coulomb 
Unit Watt 
Unit Joule 
Unit Pascal 
Unit Newton 
Unit Hertz 
Unit Candela 
Unit Mole 
Unit Kelvin 
Unit Ampere 
Unit Second 
Unit Gram 
Unit Meter 
(~ Bool (CheckCanonical unit) False, Unit unit, UnitPrefix prefix) => Unit (:@ prefix unit) 
(Unit unit, SingI Z power) => Unit (:^ unit power) 
(Unit u1, Unit u2) => Unit (:/ u1 u2) 
(Unit u1, Unit u2) => Unit (:* u1 u2) 

type MkDim unit = Dim Double (DimSpecsOf unit)Source

Make a dimensioned quantity type capable of storing a value of a given unit. This uses a Double for storage of the value. For example:

 type Length = MkDim Meter

type MkGenDim n unit = Dim n (DimSpecsOf unit)Source

Make a dimensioned quantity with a custom numerical type.

data Canonical Source

Dummy type use just to label canonical units. It does not have a Unit instance.

Scalars, the only built-in unit

data Number Source

The unit for unitless dimensioned quantities

Constructors

Number 

Instances

type Scalar = MkDim NumberSource

The type of unitless dimensioned quantities This is an instance of Num, though Haddock doesn't show it.

scalar :: n -> Dim n `[]`Source

Convert a raw number into a unitless dimensioned quantity

Type-level integers

data Z Source

The datatype for type-level integers.

Constructors

Zero 
S Z 
P Z 

Instances

Eq Z 
SingI Z Zero 
SEq Z (KProxy Z) 
SDecide Z (KProxy Z) 
SingI Z n0 => SingI Z (P n) 
SingI Z n0 => SingI Z (S n) 
SingKind Z (KProxy Z) 

type family Succ z :: ZSource

Add one to an integer

type family Pred z :: ZSource

Subtract one from an integer

type family a (#+) b :: ZSource

Add two integers

type family a (#-) b :: ZSource

Subtract two integers

type family a (#*) b :: ZSource

Multiply two integers

type family a (#/) b :: ZSource

Divide two integers

type family NegZ z :: ZSource

Negate an integer

Synonyms for small numbers

type Two = S OneSource

Term-level singletons

pZero :: Sing Z ZeroSource

This is the singleton value representing Zero at the term level and at the type level, simultaneously. Used for raising units to powers.

pFour :: Sing Z (S (S (S (S Zero))))Source

pFive :: Sing Z (S (S (S (S (S Zero)))))Source

pMFour :: Sing Z (P (P (P (P Zero))))Source

pMFive :: Sing Z (P (P (P (P (P Zero)))))Source

pSucc :: Sing z -> Sing (Succ z)Source

Add one to a singleton Z.

pPred :: Sing z -> Sing (Pred z)Source

Subtract one from a singleton Z.