Copyright | Copyright (C) 2006-2015 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Stable |
Portability | GHC only |
Safe Haskell | Safe |
Language | Haskell2010 |
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.
- data UnitName m
- data NameAtom m
- type PrefixName = NameAtom PrefixAtom
- data Metricality
- atom :: String -> String -> String -> UnitName NonMetric
- applyPrefix :: PrefixName -> UnitName Metric -> UnitName NonMetric
- (*) :: UnitName m1 -> UnitName m2 -> UnitName NonMetric
- (/) :: UnitName m1 -> UnitName m2 -> UnitName NonMetric
- (^) :: UnitName m -> Int -> UnitName NonMetric
- product :: Foldable f => f (UnitName NonMetric) -> UnitName NonMetric
- reduce :: UnitName m -> UnitName m
- grouped :: UnitName m -> UnitName NonMetric
- baseUnitName :: Dimension' -> UnitName NonMetric
- nOne :: UnitName NonMetric
- nMeter :: UnitName Metric
- nGram :: UnitName Metric
- nKilogram :: UnitName NonMetric
- nSecond :: UnitName Metric
- nAmpere :: UnitName Metric
- nKelvin :: UnitName Metric
- nMole :: UnitName Metric
- nCandela :: UnitName Metric
- deka :: PrefixName
- hecto :: PrefixName
- kilo :: PrefixName
- mega :: PrefixName
- giga :: PrefixName
- tera :: PrefixName
- peta :: PrefixName
- exa :: PrefixName
- zetta :: PrefixName
- yotta :: PrefixName
- deci :: PrefixName
- centi :: PrefixName
- milli :: PrefixName
- micro :: PrefixName
- nano :: PrefixName
- pico :: PrefixName
- femto :: PrefixName
- atto :: PrefixName
- zepto :: PrefixName
- yocto :: PrefixName
- type UnitNameTransformer = forall m. UnitName m -> UnitName NonMetric
- type UnitNameTransformer2 = forall m1 m2. UnitName m1 -> UnitName m2 -> UnitName NonMetric
- weaken :: UnitName m -> UnitName NonMetric
- strengthen :: UnitName m -> Maybe (UnitName Metric)
- relax :: forall m1 m2. (Typeable m1, Typeable m2) => UnitName m1 -> Maybe (UnitName m2)
Data Types
The name of a unit.
Represents the name of an atomic unit or prefix.
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.
Construction of Unit Names
:: 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 :: PrefixName -> UnitName Metric -> UnitName NonMetric Source
(*) :: 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.
Standard Names
baseUnitName :: Dimension' -> UnitName NonMetric Source
The name of the base unit associated with a specified dimension.
Names for the Base Units
Names for the SI Metric Prefixes
deka :: PrefixName Source
kilo :: PrefixName Source
mega :: PrefixName Source
giga :: PrefixName Source
tera :: PrefixName Source
peta :: PrefixName Source
exa :: PrefixName Source
deci :: PrefixName Source
nano :: PrefixName Source
pico :: PrefixName Source
atto :: PrefixName Source
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
relax :: forall m1 m2. (Typeable m1, Typeable m2) => UnitName m1 -> Maybe (UnitName m2) Source
Convert a UnitName
of one Metricality
into a name of the other metricality by
strengthening or weakening if neccessary. Because it may not be possible to strengthen,
the result is returned in a Maybe
wrapper.