dimensional-1.5: Statically checked physical dimensions
CopyrightCopyright (C) 2006-2018 Bjorn Buckwalter
LicenseBSD3
Maintainerbjorn@buckwalter.se
StabilityStable
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • ScopedTypeVariables
  • TypeFamilies
  • ConstraintKinds
  • DataKinds
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveGeneric
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • KindSignatures
  • RoleAnnotations
  • GeneralizedNewtypeDeriving
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll

Numeric.Units.Dimensional

Description

Summary

In this module we provide data types for performing arithmetic with physical quantities and units. Information about the physical dimensions of the quantities/units is embedded in their types and the validity of operations is verified by the type checker at compile time. The wrapping and unwrapping of numerical values as quantities is done by multiplication and division of units, of which an incomplete set is provided.

We limit ourselves to "Newtonian" physics. We do not attempt to accommodate relativistic physics in which e.g. addition of length and time would be valid.

As far as possible and/or practical the conventions and guidelines of NIST's "Guide for the Use of the International System of Units (SI)" [1] are followed. Occasionally we will reference specific sections from the guide and deviations will be explained.

Disclaimer

Merely an engineer, the author doubtlessly uses a language and notation that makes mathematicians and physicists cringe. He does not mind constructive criticism (or pull requests).

The sets of functions and units defined herein are incomplete and reflect only the author's needs to date. Again, patches are welcome.

Usage

Preliminaries

This module requires GHC 8 or later. We utilize Data Kinds, TypeNats, Closed Type Families, etc. Clients of the module are generally not required to use these extensions.

Clients probably will want to use the NegativeLiterals extension though.

Examples

We have defined operators and units that allow us to define and work with physical quantities. A physical quantity is defined by multiplying a number with a unit (the type signature is optional).

v :: Velocity Double
v = 90 *~ (kilo meter / hour)

It follows naturally that the numerical value of a quantity is obtained by division by a unit.

numval :: Double
numval = v /~ (meter / second)

The notion of a quantity as the product of a numerical value and a unit is supported by 7.1 "Value and numerical value of a quantity" of [1]. While the above syntax is fairly natural, it is unfortunate that it must violate a number of the guidelines in [1], in particular 9.3 "Spelling unit names with prefixes", 9.4 "Spelling unit names obtained by multiplication", 9.5 "Spelling unit names obtained by division".

As a more elaborate example of how to use the module, we define a function for calculating the escape velocity of a celestial body [2].

escapeVelocity :: (Floating a) => Mass a -> Length a -> Velocity a
escapeVelocity m r = sqrt (two * g * m / r)
  where
      two = 2 *~ one
      g = 6.6720e-11 *~ (newton * meter ^ pos2 / kilo gram ^ pos2)

For completeness, we should also show an example of the error messages we will get from GHC when performing invalid arithmetic. In the best case, GHC will be able to use the type synonyms we have defined in its error messages.

let x = 1 *~ meter + 1 *~ second

Couldn't match type 'Numeric.NumType.DK.Integers.Zero
               with 'Numeric.NumType.DK.Integers.Pos1
Expected type: Unit 'Metric DLength a
  Actual type: Unit 'Metric DTime a
In the second argument of `(*~)', namely `second'
In the second argument of `(+)', namely `1 *~ second'

In other cases, the error messages aren't very friendly.

let x = 1 *~ meter / (1 *~ second) + 1 *~ kilo gram

Couldn't match type 'Numeric.NumType.DK.Integers.Zero
               with 'Numeric.NumType.DK.Integers.Neg1
Expected type: Quantity DMass a
  Actual type: Dimensional
                 ('DQuantity V.* 'DQuantity) (DLength / DTime) a
In the first argument of `(+)', namely `1 *~ meter / (1 *~ second)'
In the expression: 1 *~ meter / (1 *~ second) + 1 *~ kilo gram
In an equation for `x':
      x = 1 *~ meter / (1 *~ second) + 1 *~ kilo gram

It is the author's experience that the usefulness of the compiler error messages is more often than not limited to pinpointing the location of errors.

Notes

Future work

While there is an insane amount of units in use around the world it is reasonable to provide those in relatively widespread use. Units outside of SI will most likely be added on an as-needed basis.

Additional physics models could be implemented. See [3] for ideas.

Related work

Henning Thielemann's numeric prelude has a physical units library, however, checking of dimensions is dynamic rather than static. Aaron Denney has created a toy example of statically checked physical dimensions covering only length and time. HaskellWiki has pointers [4] to these.

Also see Samuel Hoffstaetter's blog post [5] which uses techniques similar to this library.

Libraries with similar functionality exist for other programming languages and may serve as inspiration. The author has found the Java library JScience [6] and the Fortress programming language [7] particularly noteworthy.

References

  1. https://www.nist.gov/pml/special-publication-811
  2. https://en.wikipedia.org/wiki/Escape_velocity
  3. https://web.archive.org/web/20080905151927/http://jscience.org/api/org/jscience/physics/models/package-summary.html
  4. https://wiki.haskell.org/Physical_units
  5. https://liftm.wordpress.com/2007/06/03/scientificdimension-type-arithmetic-and-physical-units-in-haskell/
  6. http://jscience.org/
  7. https://github.com/stokito/fortress-lang
Synopsis

Types

Our primary objective is to define a data type that can be used to represent (while still differentiating between) units and quantities. There are two reasons for consolidating units and quantities in one data type. The first being to allow code reuse as they are largely subject to the same operations. The second being that it allows reuse of operators (and functions) between the two without resorting to occasionally cumbersome type classes.

The relationship between (the value of) a Quantity, its numerical value and its Unit is described in 7.1 "Value and numerical value of a quantity" of [1]. In short a Quantity is the product of a number and a Unit. We define the *~ operator as a convenient way to declare quantities as such a product.

data family Dimensional v :: Dimension -> Type -> Type Source #

A dimensional value, either a Quantity or a Unit, parameterized by its Dimension and representation.

Instances

Instances details
Vector Vector a => Vector Vector (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

basicUnsafeFreeze :: Mutable Vector s0 (SQuantity s d a) -> ST s0 (Vector (SQuantity s d a)) #

basicUnsafeThaw :: Vector (SQuantity s d a) -> ST s0 (Mutable Vector s0 (SQuantity s d a)) #

basicLength :: Vector (SQuantity s d a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (SQuantity s d a) -> Vector (SQuantity s d a) #

basicUnsafeIndexM :: Vector (SQuantity s d a) -> Int -> Box (SQuantity s d a) #

basicUnsafeCopy :: Mutable Vector s0 (SQuantity s d a) -> Vector (SQuantity s d a) -> ST s0 () #

elemseq :: Vector (SQuantity s d a) -> SQuantity s d a -> b -> b #

MVector MVector a => MVector MVector (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

basicLength :: MVector s0 (SQuantity s d a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s0 (SQuantity s d a) -> MVector s0 (SQuantity s d a) #

basicOverlaps :: MVector s0 (SQuantity s d a) -> MVector s0 (SQuantity s d a) -> Bool #

basicUnsafeNew :: Int -> ST s0 (MVector s0 (SQuantity s d a)) #

basicInitialize :: MVector s0 (SQuantity s d a) -> ST s0 () #

basicUnsafeReplicate :: Int -> SQuantity s d a -> ST s0 (MVector s0 (SQuantity s d a)) #

basicUnsafeRead :: MVector s0 (SQuantity s d a) -> Int -> ST s0 (SQuantity s d a) #

basicUnsafeWrite :: MVector s0 (SQuantity s d a) -> Int -> SQuantity s d a -> ST s0 () #

basicClear :: MVector s0 (SQuantity s d a) -> ST s0 () #

basicSet :: MVector s0 (SQuantity s d a) -> SQuantity s d a -> ST s0 () #

basicUnsafeCopy :: MVector s0 (SQuantity s d a) -> MVector s0 (SQuantity s d a) -> ST s0 () #

basicUnsafeMove :: MVector s0 (SQuantity s d a) -> MVector s0 (SQuantity s d a) -> ST s0 () #

basicUnsafeGrow :: MVector s0 (SQuantity s d a) -> Int -> ST s0 (MVector s0 (SQuantity s d a)) #

KnownDimension d => Demotable (Quantity d) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dynamic

Methods

demotableOut :: Quantity d a -> AnyQuantity a

Generic1 (Dimensional ('DQuantity s) d :: Type -> Type) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Associated Types

type Rep1 (Dimensional ('DQuantity s) d) :: k -> Type #

Methods

from1 :: forall (a :: k). Dimensional ('DQuantity s) d a -> Rep1 (Dimensional ('DQuantity s) d) a #

to1 :: forall (a :: k). Rep1 (Dimensional ('DQuantity s) d) a -> Dimensional ('DQuantity s) d a #

Generic1 (Dimensional ('DUnit m) d :: Type -> Type) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Associated Types

type Rep1 (Dimensional ('DUnit m) d) :: k -> Type #

Methods

from1 :: forall (a :: k). Dimensional ('DUnit m) d a -> Rep1 (Dimensional ('DUnit m) d) a #

to1 :: forall (a :: k). Rep1 (Dimensional ('DUnit m) d) a -> Dimensional ('DUnit m) d a #

KnownVariant v => Functor (Dimensional v d) Source #

A Functor instance for Dimensional.

Note that this instance is dubious, because it allows you to break the dimensional abstraction. See dmap for more information.

Note that, while this instance overlaps with that given for Dimensionless, it is confluent with that instance.

Note that this is an orphan instance.

Instance details

Defined in Numeric.Units.Dimensional.Functor

Methods

fmap :: (a -> b) -> Dimensional v d a -> Dimensional v d b #

(<$) :: a -> Dimensional v d b -> Dimensional v d a #

Functor (SQuantity s DOne) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

fmap :: (a -> b) -> SQuantity s DOne a -> SQuantity s DOne b #

(<$) :: a -> SQuantity s DOne b -> SQuantity s DOne a #

Eq1 (SQuantity s d) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

liftEq :: (a -> b -> Bool) -> SQuantity s d a -> SQuantity s d b -> Bool #

Ord1 (SQuantity s d) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> SQuantity s d a -> SQuantity s d b -> Ordering #

NFData a => NFData (Quantity d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

rnf :: Quantity d a -> () #

Bounded a => Bounded (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

minBound :: SQuantity s d a #

maxBound :: SQuantity s d a #

Eq a => Eq (Dimensional ('DQuantity s) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

(==) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

(/=) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

(Typeable s, Typeable d, Data a) => Data (Dimensional ('DQuantity s) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

gfoldl :: (forall d0 b. Data d0 => c (d0 -> b) -> d0 -> c b) -> (forall g. g -> c g) -> Dimensional ('DQuantity s) d a -> c (Dimensional ('DQuantity s) d a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dimensional ('DQuantity s) d a) #

toConstr :: Dimensional ('DQuantity s) d a -> Constr #

dataTypeOf :: Dimensional ('DQuantity s) d a -> DataType #

dataCast1 :: Typeable t => (forall d0. Data d0 => c (t d0)) -> Maybe (c (Dimensional ('DQuantity s) d a)) #

dataCast2 :: Typeable t => (forall d0 e. (Data d0, Data e) => c (t d0 e)) -> Maybe (c (Dimensional ('DQuantity s) d a)) #

gmapT :: (forall b. Data b => b -> b) -> Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a #

gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> Dimensional ('DQuantity s) d a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> Dimensional ('DQuantity s) d a -> r #

gmapQ :: (forall d0. Data d0 => d0 -> u) -> Dimensional ('DQuantity s) d a -> [u] #

gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> Dimensional ('DQuantity s) d a -> u #

gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> Dimensional ('DQuantity s) d a -> m (Dimensional ('DQuantity s) d a) #

gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> Dimensional ('DQuantity s) d a -> m (Dimensional ('DQuantity s) d a) #

gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> Dimensional ('DQuantity s) d a -> m (Dimensional ('DQuantity s) d a) #

Ord a => Ord (Dimensional ('DQuantity s) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

compare :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Ordering #

(<) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

(<=) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

(>) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

(>=) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

max :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a #

min :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a #

(KnownDimension d, KnownExactPi s, Show a, Real a) => Show (SQuantity s d a) Source #

Uses non-breaking spaces between the value and the unit, and within the unit name.

Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

showsPrec :: Int -> SQuantity s d a -> ShowS #

show :: SQuantity s d a -> String #

showList :: [SQuantity s d a] -> ShowS #

Show a => Show (Unit m d a) Source #

Unit names are shown with non-breaking spaces.

Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

showsPrec :: Int -> Unit m d a -> ShowS #

show :: Unit m d a -> String #

showList :: [Unit m d a] -> ShowS #

Generic (Dimensional ('DQuantity s) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Associated Types

type Rep (Dimensional ('DQuantity s) d a) :: Type -> Type #

Methods

from :: Dimensional ('DQuantity s) d a -> Rep (Dimensional ('DQuantity s) d a) x #

to :: Rep (Dimensional ('DQuantity s) d a) x -> Dimensional ('DQuantity s) d a #

Generic (Dimensional ('DUnit m) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Associated Types

type Rep (Dimensional ('DUnit m) d a) :: Type -> Type #

Methods

from :: Dimensional ('DUnit m) d a -> Rep (Dimensional ('DUnit m) d a) x #

to :: Rep (Dimensional ('DUnit m) d a) x -> Dimensional ('DUnit m) d a #

Num a => Semigroup (SQuantity s d a) Source #

Quantitys of a given Dimension form a Semigroup under addition.

Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

(<>) :: SQuantity s d a -> SQuantity s d a -> SQuantity s d a #

sconcat :: NonEmpty (SQuantity s d a) -> SQuantity s d a #

stimes :: Integral b => b -> SQuantity s d a -> SQuantity s d a #

Num a => Monoid (SQuantity s d a) Source #

Quantitys of a given Dimension form a Monoid under addition.

Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

mempty :: SQuantity s d a #

mappend :: SQuantity s d a -> SQuantity s d a -> SQuantity s d a #

mconcat :: [SQuantity s d a] -> SQuantity s d a #

Storable a => Storable (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

sizeOf :: SQuantity s d a -> Int #

alignment :: SQuantity s d a -> Int #

peekElemOff :: Ptr (SQuantity s d a) -> Int -> IO (SQuantity s d a) #

pokeElemOff :: Ptr (SQuantity s d a) -> Int -> SQuantity s d a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (SQuantity s d a) #

pokeByteOff :: Ptr b -> Int -> SQuantity s d a -> IO () #

peek :: Ptr (SQuantity s d a) -> IO (SQuantity s d a) #

poke :: Ptr (SQuantity s d a) -> SQuantity s d a -> IO () #

AEq a => AEq (Dimensional ('DQuantity s) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Methods

(===) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

(~==) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool #

Unbox a => Unbox (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

KnownDimension d => HasDimension (Dimensional v d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

KnownDimension d => HasDynamicDimension (Dimensional v d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

HasInterchangeName (Unit m d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

newtype MVector v (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

newtype MVector v (SQuantity s d a) = MV_Quantity {}
newtype Dimensional ('DQuantity s) d a Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

newtype Dimensional ('DQuantity s) d a = Quantity a
data Dimensional ('DUnit m) d a Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

data Dimensional ('DUnit m) d a = Unit !(UnitName m) !ExactPi !a
type Rep1 (Dimensional ('DQuantity s) d :: Type -> Type) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

type Rep1 (Dimensional ('DQuantity s) d :: Type -> Type) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.5-HMi5nnDJYaz1w5t6f148nq" 'True) (C1 ('MetaCons "Quantity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 (Dimensional ('DUnit m) d :: Type -> Type) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

type Rep1 (Dimensional ('DUnit m) d :: Type -> Type) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.5-HMi5nnDJYaz1w5t6f148nq" 'False) (C1 ('MetaCons "Unit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (UnitName m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ExactPi) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)))
type Rep (Dimensional ('DQuantity s) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

type Rep (Dimensional ('DQuantity s) d a) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.5-HMi5nnDJYaz1w5t6f148nq" 'True) (C1 ('MetaCons "Quantity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep (Dimensional ('DUnit m) d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

type Rep (Dimensional ('DUnit m) d a) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.5-HMi5nnDJYaz1w5t6f148nq" 'False) (C1 ('MetaCons "Unit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (UnitName m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ExactPi) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))
newtype Vector (SQuantity s d a) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

newtype Vector (SQuantity s d a) = V_Quantity {}

type Unit (m :: Metricality) = Dimensional ('DUnit m) Source #

A unit of measurement.

type Quantity = SQuantity One Source #

A dimensional quantity.

data Metricality Source #

Encodes whether a unit is a metric unit, that is, whether it can be combined with a metric prefix to form a related unit.

Constructors

Metric

Capable of receiving a metric prefix.

NonMetric

Incapable of receiving a metric prefix.

Instances

Instances details
Eq Metricality Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

Data Metricality Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Metricality -> c Metricality #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Metricality #

toConstr :: Metricality -> Constr #

dataTypeOf :: Metricality -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Metricality) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metricality) #

gmapT :: (forall b. Data b => b -> b) -> Metricality -> Metricality #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Metricality -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Metricality -> r #

gmapQ :: (forall d. Data d => d -> u) -> Metricality -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Metricality -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Metricality -> m Metricality #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Metricality -> m Metricality #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Metricality -> m Metricality #

Ord Metricality Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

Generic Metricality Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

Associated Types

type Rep Metricality :: Type -> Type #

NFData Metricality Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

Methods

rnf :: Metricality -> () #

type Rep Metricality Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

type Rep Metricality = D1 ('MetaData "Metricality" "Numeric.Units.Dimensional.Variants" "dimensional-1.5-HMi5nnDJYaz1w5t6f148nq" 'False) (C1 ('MetaCons "Metric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonMetric" 'PrefixI 'False) (U1 :: Type -> Type))

Physical Dimensions

The phantom type variable d encompasses the physical dimension of a Dimensional. As detailed in [5], there are seven base dimensions, which can be combined in integer powers to a given physical dimension. We represent physical dimensions as the powers of the seven base dimensions that make up the given dimension. The powers are represented using NumTypes. For convenience, we collect all seven base dimensions in a data kind Dimension.

We could have chosen to provide type variables for the seven base dimensions in Dimensional instead of creating a new data kind Dimension. However, that would have made any type signatures involving Dimensional very cumbersome. By encompassing the physical dimension in a single type variable we can "hide" the cumbersome type arithmetic behind convenient type classes as will be seen later.

data Dimension Source #

Represents a physical dimension in the basis of the 7 SI base dimensions, where the respective dimensions are represented by type variables using the following convention:

  • l: Length
  • m: Mass
  • t: Time
  • i: Electric current
  • th: Thermodynamic temperature
  • n: Amount of substance
  • j: Luminous intensity

For the equivalent term-level representation, see Dimension'

Instances

Instances details
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDimension (Proxy ('Dim l m t i th n j)) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TypeLevel

Methods

dimension :: Proxy ('Dim l m t i th n j) -> Dimension' Source #

(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDynamicDimension (Proxy ('Dim l m t i th n j)) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TypeLevel

Methods

dynamicDimension :: Proxy ('Dim l m t i th n j) -> DynamicDimension Source #

Dimension Arithmetic

When performing arithmetic on units and quantities, the arithmetics must be applied to both the numerical values of the Dimensionals but also to their physical dimensions. The type level arithmetic on physical dimensions is governed by closed type families expressed as type operators.

We could provide the Mul and Div classes with full functional dependencies but that would be of limited utility as there is no limited use for "backwards" type inference. Efforts are underway to develop a type-checker plugin that does enable these scenarios, e.g. for linear algebra.

type family (a :: Dimension) * (b :: Dimension) where ... infixl 7 Source #

Multiplication of dimensions corresponds to addition of the base dimensions' exponents.

Equations

DOne * d = d 
d * DOne = d 
('Dim l m t i th n j) * ('Dim l' m' t' i' th' n' j') = 'Dim (l + l') (m + m') (t + t') (i + i') (th + th') (n + n') (j + j') 

type family (a :: Dimension) / (d :: Dimension) where ... infixl 7 Source #

Division of dimensions corresponds to subtraction of the base dimensions' exponents.

Equations

d / DOne = d 
d / d = DOne 
('Dim l m t i th n j) / ('Dim l' m' t' i' th' n' j') = 'Dim (l - l') (m - m') (t - t') (i - i') (th - th') (n - n') (j - j') 

type family (d :: Dimension) ^ (x :: TypeInt) where ... infixr 8 Source #

Powers of dimensions correspond to multiplication of the base dimensions' exponents by the exponent.

We limit ourselves to integer powers of Dimensionals as fractional powers make little physical sense.

Equations

DOne ^ x = DOne 
d ^ 'Zero = DOne 
d ^ 'Pos1 = d 
('Dim l m t i th n j) ^ x = 'Dim (l * x) (m * x) (t * x) (i * x) (th * x) (n * x) (j * x) 

type family NRoot (d :: Dimension) (x :: TypeInt) where ... Source #

Roots of dimensions correspond to division of the base dimensions' exponents by the order of the root.

Equations

NRoot DOne x = DOne 
NRoot d 'Pos1 = d 
NRoot ('Dim l m t i th n j) x = 'Dim (l / x) (m / x) (t / x) (i / x) (th / x) (n / x) (j / x) 

type Sqrt d = NRoot d 'Pos2 Source #

Square root is a special case of NRoot with order 2.

type Cbrt d = NRoot d 'Pos3 Source #

Cube root is a special case of NRoot with order 3.

type Recip (d :: Dimension) = DOne / d Source #

The reciprocal of a dimension is defined as the result of dividing DOne by it, or of negating each of the base dimensions' exponents.

Term Level Representation of Dimensions

To facilitate parsing and pretty-printing functions that may wish to operate on term-level representations of dimension, we provide a means for converting from type-level dimensions to term-level dimensions.

data Dimension' Source #

A physical dimension, encoded as 7 integers, representing a factorization of the dimension into the 7 SI base dimensions. By convention they are stored in the same order as in the Dimension data kind.

Constructors

Dim' !Int !Int !Int !Int !Int !Int !Int 

Instances

Instances details
Eq Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Data Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dimension' -> c Dimension' #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dimension' #

toConstr :: Dimension' -> Constr #

dataTypeOf :: Dimension' -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dimension') #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dimension') #

gmapT :: (forall b. Data b => b -> b) -> Dimension' -> Dimension' #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dimension' -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dimension' -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dimension' -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dimension' -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dimension' -> m Dimension' #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension' -> m Dimension' #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension' -> m Dimension' #

Ord Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Show Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Generic Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Associated Types

type Rep Dimension' :: Type -> Type #

Semigroup Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Monoid Dimension' Source #

The monoid of dimensions under multiplication.

Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

NFData Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

Methods

rnf :: Dimension' -> () #

HasDimension Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

HasDynamicDimension Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

type Rep Dimension' Source # 
Instance details

Defined in Numeric.Units.Dimensional.Dimensions.TermLevel

class HasDynamicDimension a => HasDimension a where Source #

Dimensional values inhabit this class, which allows access to a term-level representation of their dimension.

Methods

dimension :: a -> Dimension' Source #

Obtains a term-level representation of a value's dimension.

type KnownDimension (d :: Dimension) = HasDimension (Proxy d) Source #

A KnownDimension is one for which we can construct a term-level representation. Each validly constructed type of kind Dimension has a KnownDimension instance.

While KnownDimension is a constraint synonym, the presence of KnownDimension d in a context allows use of dimension :: Proxy d -> Dimension'.

Dimensional Arithmetic

(*~) :: Num a => a -> Unit m d a -> Quantity d a infixl 7 Source #

Forms a Quantity by multipliying a number and a unit.

(/~) :: Fractional a => Quantity d a -> Unit m d a -> a infixl 7 Source #

Divides a Quantity by a Unit of the same physical dimension, obtaining the numerical value of the quantity expressed in that unit.

(^) :: (Fractional a, KnownTypeInt i, KnownVariant v, KnownVariant (Weaken v)) => Dimensional v d1 a -> Proxy i -> Dimensional (Weaken v) (d1 ^ i) a infixr 8 Source #

Raises a Quantity or Unit to an integer power.

Because the power chosen impacts the Dimension of the result, it is necessary to supply a type-level representation of the exponent in the form of a Proxy to some TypeInt. Convenience values pos1, pos2, neg1, ... are supplied by the Numeric.NumType.DK.Integers module. The most commonly used ones are also reexported by Numeric.Units.Dimensional.Prelude.

The intimidating type signature captures the similarity between these operations and ensures that composite Units are NonMetric.

(^/) :: (KnownTypeInt n, Floating a) => Quantity d a -> Proxy n -> Quantity (NRoot d n) a infixr 8 Source #

Computes the nth root of a Quantity using **.

The NRoot type family will prevent application of this operator where the result would have a fractional dimension or where n is zero.

Because the root chosen impacts the Dimension of the result, it is necessary to supply a type-level representation of the root in the form of a Proxy to some TypeInt. Convenience values pos1, pos2, neg1, ... are supplied by the Numeric.NumType.DK.Integers module. The most commonly used ones are also reexported by Numeric.Units.Dimensional.Prelude.

Also available in prefix form, see nroot.

(**) :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a infixr 8 Source #

Raises a dimensionless quantity to a dimensionless power.

(*) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 * v2), Num a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 * v2) (d1 * d2) a infixl 7 Source #

Multiplies two Quantitys or two Units.

The intimidating type signature captures the similarity between these operations and ensures that composite Units are NonMetric.

(/) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 / v2), Fractional a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 / v2) (d1 / d2) a infixl 7 Source #

Divides one Quantity by another or one Unit by another.

The intimidating type signature captures the similarity between these operations and ensures that composite Units are NonMetric.

(+) :: Num a => Quantity d a -> Quantity d a -> Quantity d a infixl 6 Source #

Adds two Quantitys.

(-) :: Num a => Quantity d a -> Quantity d a -> Quantity d a infixl 6 Source #

Subtracts one Quantity from another.

negate :: Num a => Quantity d a -> Quantity d a Source #

Negates the value of a Quantity.

abs :: Num a => Quantity d a -> Quantity d a Source #

Takes the absolute value of a Quantity.

signum :: Num a => Quantity d a -> Dimensionless a Source #

Takes the sign of a Quantity. The functions abs and signum satisy the law that:

abs x * signum x == x

The sign is either negate _1 (negative), _0 (zero), or _1 (positive).

recip :: Fractional a => Quantity d a -> Quantity (Recip d) a Source #

Forms the reciprocal of a Quantity, which has the reciprocal dimension.

>>> recip $ 47 *~ hertz
2.127659574468085e-2 s

nroot :: (KnownTypeInt n, Floating a) => Proxy n -> Quantity d a -> Quantity (NRoot d n) a Source #

Computes the nth root of a Quantity using **.

The NRoot type family will prevent application of this operator where the result would have a fractional dimension or where n is zero.

Because the root chosen impacts the Dimension of the result, it is necessary to supply a type-level representation of the root in the form of a Proxy to some TypeInt. Convenience values pos1, pos2, neg1, ... are supplied by the Numeric.NumType.DK.Integers module. The most commonly used ones are also reexported by Numeric.Units.Dimensional.Prelude.

n must not be zero. Negative roots are defined such that nroot (Proxy :: Proxy (Negate n)) x == nroot (Proxy :: Proxy n) (recip x).

Also available in operator form, see ^/.

sqrt :: Floating a => Quantity d a -> Quantity (Sqrt d) a Source #

Computes the square root of a Quantity using **.

The NRoot type family will prevent application where the supplied quantity does not have a square dimension.

(x :: Area Double) >= _0 ==> sqrt x == nroot pos2 x

cbrt :: Floating a => Quantity d a -> Quantity (Cbrt d) a Source #

Computes the cube root of a Quantity using **.

The NRoot type family will prevent application where the supplied quantity does not have a cubic dimension.

(x :: Volume Double) >= _0 ==> cbrt x == nroot pos3 x

Transcendental Functions

logBase :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a Source #

Takes the logarithm of the second argument in the base of the first.

>>> logBase _2 _8
3.0

atan2 :: RealFloat a => Quantity d a -> Quantity d a -> Dimensionless a Source #

The standard two argument arctangent function. Since it interprets its two arguments in comparison with one another, the input may have any dimension.

>>> atan2 _0 _1
0.0
>>> atan2 _1 _0
1.5707963267948966
>>> atan2 _0 (negate _1)
3.141592653589793
>>> atan2 (negate _1) _0
-1.5707963267948966

Operations on Collections

Here we define operators and functions to make working with homogeneous lists of dimensionals more convenient.

We define two convenience operators for applying units to all elements of a functor (e.g. a list).

(*~~) :: (Functor f, Num a) => f a -> Unit m d a -> f (Quantity d a) infixl 7 Source #

Applies *~ to all values in a functor.

(/~~) :: forall f m d a. (Functor f, Fractional a) => f (Quantity d a) -> Unit m d a -> f a infixl 7 Source #

Applies /~ to all values in a functor.

sum :: (Num a, Foldable f) => f (Quantity d a) -> Quantity d a Source #

The sum of all elements in a foldable structure.

>>> sum ([] :: [Mass Double])
0.0 kg
>>> sum [12.4 *~ meter, 1 *~ foot]
12.7048 m

mean :: (Fractional a, Foldable f) => f (Quantity d a) -> Quantity d a Source #

The arithmetic mean of all elements in a foldable structure.

>>> mean [pi, _7]
5.070796326794897

product :: (Num a, Foldable f) => f (Dimensionless a) -> Dimensionless a Source #

The product of all elements in a foldable structure.

>>> product ([] :: [Dimensionless Double])
1.0
>>> product [pi, _4, 0.36 *~ one]
4.523893421169302

dimensionlessLength :: (Num a, Foldable f) => f b -> Dimensionless a Source #

The length of the foldable data structure as a Dimensionless. This can be useful for purposes of e.g. calculating averages.

>>> dimensionlessLength ["foo", "bar"]
2

nFromTo Source #

Arguments

:: (Fractional a, Integral b) 
=> Quantity d a

The initial value.

-> Quantity d a

The final value.

-> b

The number of intermediate values. If less than one, no intermediate values will result.

-> [Quantity d a] 

Returns a list of quantities between given bounds.

n <= 0 ==> nFromTo (x :: Mass Double) (y :: Mass Double) n == [x, y]
(x :: Length Double) <= (y :: Length Double) ==> all (\z -> x <= z && z <= y) (nFromTo x y n)
>>> nFromTo _0 _3 2
[0.0,1.0,2.0,3.0]
>>> nFromTo _1 _0 7
[1.0,0.875,0.75,0.625,0.5,0.375,0.25,0.125,0.0]
>>> nFromTo _0 _1 (-5)
[0.0,1.0]

Dimension Synonyms

Using our Dimension data kind we define some type synonyms for convenience. We start with the base dimensions, others can be found in Numeric.Units.Dimensional.Quantities.

type DOne = 'Dim 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero Source #

The type-level dimension of dimensionless values.

Quantity Synonyms

Using the above type synonyms we can define type synonyms for quantities of particular physical dimensions.

Again we limit ourselves to the base dimensions, others can be found in Numeric.Units.Dimensional.Quantities.

Constants

For convenience we define some constants for small integer values that often show up in formulae. We also throw in pi and tau for good measure.

_0 :: Num a => Quantity d a Source #

The constant for zero is polymorphic, allowing it to express zero Length or Capacitance or Velocity etc, in addition to the Dimensionless value zero.

Constructing Units

siUnit :: forall d a. (KnownDimension d, Num a) => Unit 'NonMetric d a Source #

A polymorphic Unit which can be used in place of the coherent SI base unit of any dimension. This allows polymorphic quantity creation and destruction without exposing the Dimensional constructor.

one :: Num a => Unit 'NonMetric DOne a Source #

The unit one has dimension DOne and is the base unit of dimensionless values.

As detailed in 7.10 "Values of quantities expressed simply as numbers: the unit one, symbol 1" of [1], the unit one generally does not appear in expressions. However, for us it is necessary to use one as we would any other unit to perform the "wrapping" of dimensionless values.

mkUnitR :: Floating a => UnitName m -> ExactPi -> Unit m1 d a -> Unit m d a Source #

Forms a new atomic Unit by specifying its UnitName and its definition as a multiple of another Unit.

Use this variant when the scale factor of the resulting unit is irrational or Approximate. See mkUnitQ for when it is rational and mkUnitZ for when it is an integer.

Note that supplying zero as a definining quantity is invalid, as the library relies upon units forming a group under multiplication.

Supplying negative defining quantities is allowed and handled gracefully, but is discouraged on the grounds that it may be unexpected by other readers.

mkUnitQ :: Fractional a => UnitName m -> Rational -> Unit m1 d a -> Unit m d a Source #

Forms a new atomic Unit by specifying its UnitName and its definition as a multiple of another Unit.

Use this variant when the scale factor of the resulting unit is rational. See mkUnitZ for when it is an integer and mkUnitR for the general case.

For more information see mkUnitR.

mkUnitZ :: Num a => UnitName m -> Integer -> Unit m1 d a -> Unit m d a Source #

Forms a new atomic Unit by specifying its UnitName and its definition as a multiple of another Unit.

Use this variant when the scale factor of the resulting unit is an integer. See mkUnitQ for when it is rational and mkUnitR for the general case.

For more information see mkUnitR.

Unit Metadata

name :: Unit m d a -> UnitName m Source #

Extracts the UnitName of a Unit.

exactValue :: Unit m d a -> ExactPi Source #

Extracts the exact value of a Unit, expressed in terms of the SI coherent derived unit (see siUnit) of the same Dimension.

Note that the actual value may in some cases be approximate, for example if the unit is defined by experiment.

weaken :: Unit m d a -> Unit 'NonMetric d a Source #

Discards potentially unwanted type level information about a Unit.

strengthen :: Unit m d a -> Maybe (Unit 'Metric d a) Source #

Attempts to convert a Unit which may or may not be Metric to one which is certainly Metric.

exactify :: Unit m d a -> Unit m d ExactPi Source #

Forms the exact version of a Unit.

Pretty Printing

showIn :: (Show a, Fractional a) => Unit m d a -> Quantity d a -> String Source #

Shows the value of a Quantity expressed in a specified Unit of the same Dimension.

Uses non-breaking spaces between the value and the unit, and within the unit name.

>>> putStrLn $ showIn watt $ (37 *~ volt) * (4 *~ ampere)
148.0 W

On Functor, and Conversion Between Number Representations

We intentionally decline to provide a Functor instance for Dimensional because its use breaks the abstraction of physical dimensions.

If you feel your work requires this instance, it is provided as an orphan in Numeric.Units.Dimensional.Functor.

class KnownVariant (v :: Variant) where Source #

A KnownVariant is one whose term-level Dimensional values we can represent with an associated data family instance and manipulate with certain functions, not all of which are exported from the package.

Each validly constructed type of kind Variant has a KnownVariant instance.

Minimal complete definition

extractValue, extractName, injectValue, dmap

Methods

dmap :: (a1 -> a2) -> Dimensional v d a1 -> Dimensional v d a2 Source #

Maps over the underlying representation of a dimensional value. The caller is responsible for ensuring that the supplied function respects the dimensional abstraction. This means that the function must preserve numerical values, or linearly scale them while preserving the origin.

Instances

Instances details
KnownVariant ('DQuantity s) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Associated Types

data Dimensional ('DQuantity s) :: Dimension -> Type -> Type Source #

type ScaleFactor ('DQuantity s) :: ExactPi'

Methods

extractValue :: forall (d :: Dimension) a. Dimensional ('DQuantity s) d a -> (a, Maybe ExactPi)

extractName :: forall (d :: Dimension) a. Dimensional ('DQuantity s) d a -> Maybe (UnitName 'NonMetric)

injectValue :: forall a (d :: Dimension). Maybe (UnitName 'NonMetric) -> (a, Maybe ExactPi) -> Dimensional ('DQuantity s) d a

dmap :: forall a1 a2 (d :: Dimension). (a1 -> a2) -> Dimensional ('DQuantity s) d a1 -> Dimensional ('DQuantity s) d a2 Source #

Typeable m => KnownVariant ('DUnit m) Source # 
Instance details

Defined in Numeric.Units.Dimensional.Internal

Associated Types

data Dimensional ('DUnit m) :: Dimension -> Type -> Type Source #

type ScaleFactor ('DUnit m) :: ExactPi'

Methods

extractValue :: forall (d :: Dimension) a. Dimensional ('DUnit m) d a -> (a, Maybe ExactPi)

extractName :: forall (d :: Dimension) a. Dimensional ('DUnit m) d a -> Maybe (UnitName 'NonMetric)

injectValue :: forall a (d :: Dimension). Maybe (UnitName 'NonMetric) -> (a, Maybe ExactPi) -> Dimensional ('DUnit m) d a

dmap :: forall a1 a2 (d :: Dimension). (a1 -> a2) -> Dimensional ('DUnit m) d a1 -> Dimensional ('DUnit m) d a2 Source #

changeRep :: (KnownVariant v, Real a, Fractional b) => Dimensional v d a -> Dimensional v d b Source #

Convenient conversion between numerical types while retaining dimensional information.

>>> let x = (37 :: Rational) *~ poundMass
>>> changeRep x :: Mass Double
16.78291769 kg

changeRepApproximate :: (KnownVariant v, Floating b) => Dimensional v d ExactPi -> Dimensional v d b Source #

Convenient conversion from exactly represented values while retaining dimensional information.

Lenses

These functions are compatible with the lens library.

asLens :: Fractional a => Unit m d a -> forall f. Functor f => (a -> f a) -> Quantity d a -> f (Quantity d a) Source #

Converts a Unit into a lens from Quantitys to values.