dimensional-1.1: Statically checked physical dimensions, using Type Families and Data Kinds.

CopyrightCopyright (C) 2006-2018 Bjorn Buckwalter
LicenseBSD3
Maintainerbjorn@buckwalter.se
StabilityStable
PortabilityGHC only?
Safe HaskellNone
LanguageHaskell2010

Numeric.Units.Dimensional.Dynamic

Contents

Description

Defines types for manipulation of units and quantities without phantom types for their dimensions.

Synopsis

Dynamic Quantities

data AnyQuantity a Source #

A Quantity whose Dimension is only known dynamically.

Instances

Promotable AnyQuantity Source # 
Demotable AnyQuantity Source # 
Eq a => Eq (AnyQuantity a) Source # 
Data a => Data (AnyQuantity a) Source # 

Methods

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

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

toConstr :: AnyQuantity a -> Constr #

dataTypeOf :: AnyQuantity a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show a => Show (AnyQuantity a) Source # 
Generic (AnyQuantity a) Source # 

Associated Types

type Rep (AnyQuantity a) :: * -> * #

Methods

from :: AnyQuantity a -> Rep (AnyQuantity a) x #

to :: Rep (AnyQuantity a) x -> AnyQuantity a #

Num a => Semigroup (AnyQuantity a) Source #

AnyQuantitys form a Semigroup under multiplication, but not under addition because they may not be added together if their dimensions do not match.

Num a => Monoid (AnyQuantity a) Source #

AnyQuantitys form a Monoid under multiplication, but not under addition because they may not be added together if their dimensions do not match.

NFData a => NFData (AnyQuantity a) Source # 

Methods

rnf :: AnyQuantity a -> () #

HasDimension (AnyQuantity a) Source # 
HasDynamicDimension (AnyQuantity a) Source # 
Generic1 * AnyQuantity Source # 

Associated Types

type Rep1 AnyQuantity (f :: AnyQuantity -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 AnyQuantity f a #

to1 :: Rep1 AnyQuantity f a -> f a #

type Rep (AnyQuantity a) Source # 
type Rep (AnyQuantity a) = D1 * (MetaData "AnyQuantity" "Numeric.Units.Dimensional.Dynamic" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) (C1 * (MetaCons "AnyQuantity" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Dimension')) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))))
type Rep1 * AnyQuantity Source # 
type Rep1 * AnyQuantity = D1 * (MetaData "AnyQuantity" "Numeric.Units.Dimensional.Dynamic" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) (C1 * (MetaCons "AnyQuantity" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Dimension')) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))

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.

Instances

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 # 

Methods

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

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

toConstr :: DynQuantity a -> Constr #

dataTypeOf :: DynQuantity a -> DataType #

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

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

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

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

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

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

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

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

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

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

Num a => Num (DynQuantity a) Source # 
Show a => Show (DynQuantity a) Source # 
Generic (DynQuantity a) Source # 

Associated Types

type Rep (DynQuantity a) :: * -> * #

Methods

from :: DynQuantity a -> Rep (DynQuantity a) x #

to :: Rep (DynQuantity a) x -> DynQuantity a #

Num a => Semigroup (DynQuantity a) Source #

DynQuantitys form a Semigroup under multiplication, but not under addition because they may not be added together if their dimensions do not match.

Num a => Monoid (DynQuantity a) Source #

DynQuantitys form a Monoid under multiplication, but not under addition because they may not be added together if their dimensions do not match.

NFData a => NFData (DynQuantity a) Source # 

Methods

rnf :: DynQuantity a -> () #

HasDynamicDimension (DynQuantity a) Source # 
Generic1 * DynQuantity Source # 

Associated Types

type Rep1 DynQuantity (f :: DynQuantity -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 DynQuantity f a #

to1 :: Rep1 DynQuantity f a -> f a #

type Rep (DynQuantity a) Source # 
type Rep (DynQuantity a) = D1 * (MetaData "DynQuantity" "Numeric.Units.Dimensional.Dynamic" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) (C1 * (MetaCons "DynQuantity" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DynamicDimension)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))
type Rep1 * DynQuantity Source # 
type Rep1 * DynQuantity = D1 * (MetaData "DynQuantity" "Numeric.Units.Dimensional.Dynamic" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) (C1 * (MetaCons "DynQuantity" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DynamicDimension)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)))

class Demotable (q :: * -> *) Source #

The class of types that can be used to model Quantitys that are certain to have a value with some dimension.

Minimal complete definition

demotableOut

class Promotable (q :: * -> *) Source #

The class of types that can be used to model Quantitys whose Dimensions are only known dynamically.

Minimal complete definition

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.

Methods

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.

data DynamicDimension Source #

The dimension of a dynamic value, which may not have any dimension at all.

Constructors

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.

Instances

Eq DynamicDimension Source # 
Data DynamicDimension Source # 

Methods

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

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

toConstr :: DynamicDimension -> Constr #

dataTypeOf :: DynamicDimension -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DynamicDimension Source # 
Show DynamicDimension Source # 
Generic DynamicDimension Source # 
NFData DynamicDimension Source # 

Methods

rnf :: DynamicDimension -> () #

HasDynamicDimension DynamicDimension Source # 
type Rep DynamicDimension Source # 
type Rep DynamicDimension = D1 * (MetaData "DynamicDimension" "Numeric.Units.Dimensional.Dimensions.TermLevel" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) ((:+:) * (C1 * (MetaCons "NoDimension" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SomeDimension" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Dimension'))) (C1 * (MetaCons "AnyDimension" PrefixI False) (U1 *))))

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 DynQuantitys, 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 DynQuantitys of a specific dimension.

Dynamic Units

data AnyUnit Source #

A Unit whose Dimension is only known dynamically.

demoteUnit :: forall m d a. KnownDimension d => Unit m d a -> AnyUnit Source #

Converts a Unit of statically known Dimension into an AnyUnit.

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.

Arithmetic on Dynamic Units

(*) :: AnyUnit -> AnyUnit -> AnyUnit Source #

Forms the product of two dynamic units.

(/) :: AnyUnit -> AnyUnit -> AnyUnit Source #

Forms the quotient of two dynamic units.

(^) :: Integral a => AnyUnit -> a -> AnyUnit Source #

Raises a dynamic unit to an integer power.

recip :: AnyUnit -> AnyUnit Source #

Forms the reciprocal of a dynamic unit.

applyPrefix :: Prefix -> AnyUnit -> Maybe AnyUnit Source #

Applies a prefix to a dynamic unit. Returns Nothing if the Unit was NonMetric and thus could not accept a prefix.