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.UnitNames

Contents

Description

This module provides types and functions for manipulating unit names.

Please note that the details of the name representation may be less stable than the other APIs provided by this package, as new features using them are still being developed.

Synopsis

Data Types

data UnitName (m :: Metricality) Source #

The name of a unit.

data NameAtom (m :: NameAtomType) Source #

Represents the name of an atomic unit or prefix.

Instances

Eq (NameAtom m) Source # 

Methods

(==) :: NameAtom m -> NameAtom m -> Bool #

(/=) :: NameAtom m -> NameAtom m -> Bool #

Typeable NameAtomType m => Data (NameAtom m) Source # 

Methods

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

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

toConstr :: NameAtom m -> Constr #

dataTypeOf :: NameAtom m -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (NameAtom m) Source # 

Methods

compare :: NameAtom m -> NameAtom m -> Ordering #

(<) :: NameAtom m -> NameAtom m -> Bool #

(<=) :: NameAtom m -> NameAtom m -> Bool #

(>) :: NameAtom m -> NameAtom m -> Bool #

(>=) :: NameAtom m -> NameAtom m -> Bool #

max :: NameAtom m -> NameAtom m -> NameAtom m #

min :: NameAtom m -> NameAtom m -> NameAtom m #

Generic (NameAtom m) Source # 

Associated Types

type Rep (NameAtom m) :: * -> * #

Methods

from :: NameAtom m -> Rep (NameAtom m) x #

to :: Rep (NameAtom m) x -> NameAtom m #

NFData (NameAtom m) Source # 

Methods

rnf :: NameAtom m -> () #

HasInterchangeName (NameAtom m) Source # 
type Rep (NameAtom m) Source # 
type Rep (NameAtom m) = D1 * (MetaData "NameAtom" "Numeric.Units.Dimensional.UnitNames.Internal" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) (C1 * (MetaCons "NameAtom" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_interchangeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InterchangeName)) ((:*:) * (S1 * (MetaSel (Just Symbol "abbreviation_en") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "name_en") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))

data Prefix Source #

Instances

Eq Prefix Source # 

Methods

(==) :: Prefix -> Prefix -> Bool #

(/=) :: Prefix -> Prefix -> Bool #

Data Prefix Source # 

Methods

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

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

toConstr :: Prefix -> Constr #

dataTypeOf :: Prefix -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Prefix Source # 
Generic Prefix Source # 

Associated Types

type Rep Prefix :: * -> * #

Methods

from :: Prefix -> Rep Prefix x #

to :: Rep Prefix x -> Prefix #

NFData Prefix Source # 

Methods

rnf :: Prefix -> () #

HasInterchangeName Prefix Source # 
type Rep Prefix Source # 
type Rep Prefix = D1 * (MetaData "Prefix" "Numeric.Units.Dimensional.UnitNames.Internal" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) (C1 * (MetaCons "Prefix" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "prefixName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PrefixName)) (S1 * (MetaSel (Just Symbol "scaleFactor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Rational))))

type PrefixName = NameAtom PrefixAtom Source #

The name of a metric prefix.

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

Eq Metricality Source # 
Data Metricality Source # 

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 :: (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 # 
Generic Metricality Source # 

Associated Types

type Rep Metricality :: * -> * #

NFData Metricality Source # 

Methods

rnf :: Metricality -> () #

type Rep Metricality Source # 
type Rep Metricality = D1 * (MetaData "Metricality" "Numeric.Units.Dimensional.Variants" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) ((:+:) * (C1 * (MetaCons "Metric" PrefixI False) (U1 *)) (C1 * (MetaCons "NonMetric" PrefixI False) (U1 *)))

Construction of Unit Names

atom Source #

Arguments

:: String

Interchange name

-> String

Abbreviated name in international English

-> String

Full name in international English

-> UnitName NonMetric 

Constructs an atomic name for a custom unit.

applyPrefix :: Prefix -> UnitName Metric -> UnitName NonMetric Source #

Forms a UnitName from a Metric name by applying a metric prefix.

(*) :: UnitName m1 -> UnitName m2 -> UnitName NonMetric infixl 7 Source #

Form a UnitName by taking the product of two others.

(/) :: UnitName m1 -> UnitName m2 -> UnitName NonMetric infixl 7 Source #

Form a UnitName by dividing one by another.

(^) :: UnitName m -> Int -> UnitName NonMetric infixr 8 Source #

Form a UnitName by raising a name to an integer power.

product :: Foldable f => f (UnitName NonMetric) -> UnitName NonMetric Source #

Forms the product of a list of UnitNames.

If you wish to form a heterogenous product of Metric and NonMetric units you should apply weaken to the Metric ones.

grouped :: UnitName m -> UnitName NonMetric Source #

Constructs a UnitName by applying a grouping operation to another UnitName, which may be useful to express precedence.

Standard Names

baseUnitName :: Dimension' -> UnitName NonMetric Source #

The name of the base unit associated with a specified dimension.

siPrefixes :: [Prefix] Source #

A list of all Prefixes defined by the SI.

nOne :: UnitName NonMetric Source #

The name of the unit of dimensionless values.

Inspecting Prefixes

prefixName :: Prefix -> PrefixName Source #

The name of a metric prefix.

scaleFactor :: Prefix -> Rational Source #

The scale factor denoted by a metric prefix.

Convenience Type Synonyms for Unit Name Transformations

type UnitNameTransformer = forall m. UnitName m -> UnitName NonMetric Source #

The type of a unit name transformation that may be associated with an operation that takes a single unit as input.

type UnitNameTransformer2 = forall m1 m2. UnitName m1 -> UnitName m2 -> UnitName NonMetric Source #

The type of a unit name transformation that may be associated with an operation that takes two units as input.

Forgetting Unwanted Phantom Types

weaken :: UnitName m -> UnitName NonMetric Source #

Convert a UnitName which may or may not be Metric to one which is certainly NonMetric.

strengthen :: UnitName m -> Maybe (UnitName Metric) Source #

Attempt to convert a UnitName which may or may not be Metric to one which is certainly Metric.

relax :: forall m1 m2. (Typeable m1, Typeable m2) => UnitName m1 -> Maybe (UnitName m2) Source #

Convert a UnitName of one Metricality into a name of another metricality by strengthening or weakening if neccessary. Because it may not be possible to strengthen, the result is returned in a Maybe wrapper.

name_en :: NameAtom m -> String Source #

The full name of the unit in international English

abbreviation_en :: NameAtom m -> String Source #

The abbreviated name of the unit in international English

asAtomic :: UnitName m -> Maybe (NameAtom (UnitAtom m)) Source #