Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Stable |
Portability | GHC only? |
Safe Haskell | None |
Language | Haskell2010 |
Defines types for manipulation of units and quantities without phantom types for their dimensions.
- data AnyQuantity a
- data DynQuantity a
- class Demotable (q :: * -> *)
- class Promotable (q :: * -> *)
- class HasDynamicDimension a where
- data DynamicDimension
- promoteQuantity :: forall a d q. (Promotable q, KnownDimension d) => q a -> Maybe (Quantity d a)
- demoteQuantity :: (Demotable q, Promotable d) => q a -> d a
- (*~) :: (Floating a, Promotable q) => a -> AnyUnit -> q a
- (/~) :: (Floating a, Promotable q) => q a -> AnyUnit -> Maybe a
- invalidQuantity :: DynQuantity a
- polydimensionalZero :: Num a => DynQuantity a
- data AnyUnit
- demoteUnit :: forall m d a. KnownDimension d => Unit m d a -> AnyUnit
- promoteUnit :: forall d. KnownDimension d => AnyUnit -> Maybe (Unit NonMetric d ExactPi)
- demoteUnit' :: KnownDimension d => Unit m d ExactPi -> AnyUnit
- siUnit :: Dimension' -> AnyUnit
- anyUnitName :: AnyUnit -> UnitName NonMetric
- (*) :: AnyUnit -> AnyUnit -> AnyUnit
- (/) :: AnyUnit -> AnyUnit -> AnyUnit
- (^) :: Integral a => AnyUnit -> a -> AnyUnit
- recip :: AnyUnit -> AnyUnit
- applyPrefix :: Prefix -> AnyUnit -> Maybe AnyUnit
Dynamic Quantities
data AnyQuantity a Source #
Promotable AnyQuantity Source # | |
Demotable AnyQuantity Source # | |
Eq a => Eq (AnyQuantity a) Source # | |
Data a => Data (AnyQuantity a) Source # | |
Show a => Show (AnyQuantity a) Source # | |
Generic (AnyQuantity a) Source # | |
Num a => Semigroup (AnyQuantity a) Source # |
|
Num a => Monoid (AnyQuantity a) Source # |
|
NFData a => NFData (AnyQuantity a) Source # | |
HasDimension (AnyQuantity a) Source # | |
HasDynamicDimension (AnyQuantity a) Source # | |
Generic1 * AnyQuantity Source # | |
type Rep (AnyQuantity a) Source # | |
type Rep1 * AnyQuantity Source # | |
data DynQuantity a Source #
Possibly a Quantity
whose Dimension
is only known dynamically.
By modeling the absence of a value, this type differs from AnyQuantity
in that it may
not be a Quantity
of any Dimension
whatsoever, but in exchange it gains instances
for the common numeric classes. It's therefore useful for manipulating, and not merely storing,
quantities of unknown dimension.
This type also contains a polydimensionalZero
, representing zero value of any dimension.
Note that the Eq
instance for DynQuantity
equates all representations of an invalid value,
and also does not equate polydimensional zero with zero of any specific dimension.
Promotable DynQuantity Source # | |
Eq a => Eq (DynQuantity a) Source # | |
Floating a => Floating (DynQuantity a) Source # | |
Fractional a => Fractional (DynQuantity a) Source # | |
Data a => Data (DynQuantity a) Source # | |
Num a => Num (DynQuantity a) Source # | |
Show a => Show (DynQuantity a) Source # | |
Generic (DynQuantity a) Source # | |
Num a => Semigroup (DynQuantity a) Source # |
|
Num a => Monoid (DynQuantity a) Source # |
|
NFData a => NFData (DynQuantity a) Source # | |
HasDynamicDimension (DynQuantity a) Source # | |
Generic1 * DynQuantity Source # | |
type Rep (DynQuantity a) Source # | |
type Rep1 * DynQuantity Source # | |
class Demotable (q :: * -> *) Source #
The class of types that can be used to model Quantity
s that are certain to have a value with
some dimension.
demotableOut
Demotable AnyQuantity Source # | |
KnownDimension d => Demotable (Quantity d) Source # | |
class Promotable (q :: * -> *) Source #
promotableIn, promotableOut
class HasDynamicDimension a where Source #
Dimensional values, or those that are only possibly dimensional, inhabit this class, which allows access to a term-level representation of their dimension.
dynamicDimension :: a -> DynamicDimension Source #
Gets the 'DynamicDimension of a dynamic dimensional value, which may be NoDimension
if it does not represent
a dimensional value of any Dimension
.
A default implementation is available for types that are also in the HasDimension
typeclass.
dynamicDimension :: HasDimension a => a -> DynamicDimension Source #
Gets the 'DynamicDimension of a dynamic dimensional value, which may be NoDimension
if it does not represent
a dimensional value of any Dimension
.
A default implementation is available for types that are also in the HasDimension
typeclass.
HasDynamicDimension DynamicDimension Source # | |
HasDynamicDimension Dimension' Source # | |
HasDynamicDimension AnyUnit Source # | |
HasDynamicDimension (DynQuantity a) Source # | |
HasDynamicDimension (AnyQuantity a) Source # | |
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDynamicDimension (Proxy Dimension (Dim l m t i th n j)) Source # | |
KnownDimension d => HasDynamicDimension (Dimensional v d a) Source # | |
data DynamicDimension Source #
The dimension of a dynamic value, which may not have any dimension at all.
NoDimension | The value has no valid dimension. |
SomeDimension Dimension' | The value has the given dimension. |
AnyDimension | The value may be interpreted as having any dimension. |
promoteQuantity :: forall a d q. (Promotable q, KnownDimension d) => q a -> Maybe (Quantity d a) Source #
Converts a dynamic quantity such as an AnyQuantity
or a DynQuantity
into a
Quantity
, or to Nothing
if the dynamic quantity cannot be represented in the
narrower result type.
demoteQuantity :: (Demotable q, Promotable d) => q a -> d a Source #
Forgets information about a Quantity
or AnyQuantity
, yielding an AnyQuantity
or a DynQuantity
.
(*~) :: (Floating a, Promotable q) => a -> AnyUnit -> q a Source #
Forms a dynamic quantity by multipliying a number and a dynamic unit.
(/~) :: (Floating a, Promotable q) => q a -> AnyUnit -> Maybe a Source #
Divides a dynamic quantity by a dynamic unit, obtaining the numerical value of the quantity
expressed in that unit if they are of the same physical dimension, or Nothing
otherwise.
invalidQuantity :: DynQuantity a Source #
A DynQuantity
which does not correspond to a value of any dimension.
polydimensionalZero :: Num a => DynQuantity a Source #
A DynQuantity
which corresponds to zero value of any dimension.
When combined through arithmetic with other DynQuantity
s, inference is performed. For example,
adding a length to polydimensional zero produces that length. Adding two polydimensional zeros produces another.
Taking the sine of a polydimensional zero interprets it as a dimensionless zero and produces a dimensionless result.
Note that division by polydimensionalZero
produces a polydimensional result, which may be an error or some representation
of infinity, as determined by the underlying arithmetic type. This behavior was chosen for consistency with the behavior of division
by zero DynQuantity
s of a specific dimension.
Dynamic Units
demoteUnit :: forall m d a. KnownDimension d => Unit m d a -> AnyUnit Source #
promoteUnit :: forall d. KnownDimension d => AnyUnit -> Maybe (Unit NonMetric d ExactPi) Source #
Converts an AnyUnit
into a Unit
of statically known Dimension
, or Nothing
if the dimension does not match.
The result is represented in ExactPi
, conversion to other representations is possible using changeRepApproximate
.
The result is always tagged as NonMetric
, conversion to a Metric
unit can be attempted using strengthen
.
demoteUnit' :: KnownDimension d => Unit m d ExactPi -> AnyUnit Source #
Converts a Unit
of statically known Dimension
into an AnyUnit
.
This is the same as the more general demoteUnit
but is useful in certain circumstances to avoid
needlessly introducing an ambiguous type variable.
siUnit :: Dimension' -> AnyUnit Source #
The dynamic SI coherent unit of a given dimension.