dimensional-1.5: Statically checked physical dimensions
CopyrightCopyright (C) 2006-2018 Bjorn Buckwalter
LicenseBSD3
Maintainerbjorn@buckwalter.se
StabilityStable
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TypeFamilies
  • ConstraintKinds
  • DataKinds
  • DeriveDataTypeable
  • DeriveGeneric
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces

Numeric.Units.Dimensional.Variants

Description

Provides a type level representation of Variants of dimensional values, which may be quantities or units.

Synopsis

Documentation

data Variant Source #

The kind of variants of dimensional values.

Constructors

DQuantity ExactPi'

The value is a quantity, stored as an ExactPi multiple of its value in its dimension's SI coherent unit.

DUnit Metricality

The value is a unit, possibly a Metric unit.

Instances

Instances details
Generic Variant Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

Associated Types

type Rep Variant :: Type -> Type #

Methods

from :: Variant -> Rep Variant x #

to :: Rep Variant x -> Variant #

type Rep Variant Source # 
Instance details

Defined in Numeric.Units.Dimensional.Variants

type Rep Variant = D1 ('MetaData "Variant" "Numeric.Units.Dimensional.Variants" "dimensional-1.5-HMi5nnDJYaz1w5t6f148nq" 'False) (C1 ('MetaCons "DQuantity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExactPi')) :+: C1 ('MetaCons "DUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Metricality)))

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))

type family (v1 :: Variant) * (v2 :: Variant) :: Variant where ... infixl 7 Source #

Forms the product of two Variants.

The product of units is a non-metric unit.

The product of quantities is a quantity.

Equations

('DUnit m1) * ('DUnit m2) = 'DUnit 'NonMetric 
('DQuantity s1) * ('DQuantity s2) = 'DQuantity (s1 * s2) 

type family (v1 :: Variant) / (v2 :: Variant) :: Variant where ... Source #

Forms the quotient of two Variants.

The quotient of units is a non-metric unit.

The quotient of quantities is a quantity.

Equations

('DUnit m1) / ('DUnit m2) = 'DUnit 'NonMetric 
('DQuantity s1) / ('DQuantity s2) = 'DQuantity (s1 / s2) 

type family Weaken (v :: Variant) :: Variant where ... Source #

Weakens a Variant by forgetting possibly uninteresting type-level information.

Equations

Weaken ('DQuantity s) = 'DQuantity s 
Weaken ('DUnit m) = 'DUnit 'NonMetric 

type CompatibleVariants v1 v2 = 'True ~ AreCompatible v1 v2 Source #

Two Variants are compatible when dimensional values of the first may be converted into the second merely by changing the representation of their values.