Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Stable |
Portability | GHC only |
Safe Haskell | None |
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.
Synopsis
- data UnitName (m :: Metricality)
- data NameAtom (m :: NameAtomType)
- data Prefix
- type PrefixName = NameAtom PrefixAtom
- data Metricality
- atom :: String -> String -> String -> UnitName NonMetric
- applyPrefix :: Prefix -> 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
- siPrefixes :: [Prefix]
- nOne :: UnitName NonMetric
- prefixName :: Prefix -> PrefixName
- scaleFactor :: Prefix -> Rational
- 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)
- name_en :: NameAtom m -> String
- abbreviation_en :: NameAtom m -> String
- asAtomic :: UnitName m -> Maybe (NameAtom (UnitAtom m))
Data Types
data UnitName (m :: Metricality) Source #
The name of a unit.
Instances
Eq (UnitName m) Source # | |
Show (UnitName m) Source # |
|
NFData (UnitName m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal | |
HasInterchangeName (UnitName m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal interchangeName :: UnitName m -> InterchangeName Source # |
data NameAtom (m :: NameAtomType) Source #
Represents the name of an atomic unit or prefix.
Instances
Eq (NameAtom m) Source # | |
Typeable m => Data (NameAtom m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal 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 m0 => (forall d. Data d => d -> m0 d) -> NameAtom m -> m0 (NameAtom m) # gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> NameAtom m -> m0 (NameAtom m) # gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> NameAtom m -> m0 (NameAtom m) # | |
Ord (NameAtom m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal | |
Generic (NameAtom m) Source # | |
NFData (NameAtom m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal | |
HasInterchangeName (NameAtom m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal interchangeName :: NameAtom m -> InterchangeName Source # | |
type Rep (NameAtom m) Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal type Rep (NameAtom m) = D1 (MetaData "NameAtom" "Numeric.Units.Dimensional.UnitNames.Internal" "dimensional-1.3-7Gh1mp5ZBGaGfkDr7lUYf2" False) (C1 (MetaCons "NameAtom" PrefixI True) (S1 (MetaSel (Just "_interchangeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InterchangeName) :*: (S1 (MetaSel (Just "abbreviation_en") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "name_en") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) |
Instances
Eq Prefix Source # | |
Data Prefix Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal 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 # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal | |
Generic Prefix Source # | |
NFData Prefix Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal | |
HasInterchangeName Prefix Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal | |
type Rep Prefix Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.Internal type Rep Prefix = D1 (MetaData "Prefix" "Numeric.Units.Dimensional.UnitNames.Internal" "dimensional-1.3-7Gh1mp5ZBGaGfkDr7lUYf2" False) (C1 (MetaCons "Prefix" PrefixI True) (S1 (MetaSel (Just "prefixName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrefixName) :*: S1 (MetaSel (Just "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.
Instances
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.
(*) :: 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.
siPrefixes :: [Prefix] Source #
A list of all Prefix
es defined by the SI.
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
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.
abbreviation_en :: NameAtom m -> String Source #
The abbreviated name of the unit in international English