Copyright | (c) Alice Rixte 2025 |
---|---|
License | BSD 3 |
Maintainer | alice.rixte@u-bordeaux.fr |
Stability | unstable |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Data.Units.Base.Prefix
Description
Provides a way to define prefixes for any system of units.
Synopsis
- type Prefix = Unit -> Unit
- class (forall (u :: Unit). IsUnit u => IsUnit (p u)) => IsPrefix (p :: Prefix)
- class (Fractional a, IsPrefix p) => PrefixFactor (p :: Prefix) a where
- prefixFactor :: a
- class IsPrefix p => ShowPrefix (p :: Prefix) where
- type ShowPrefixType (p :: Prefix) :: ErrorMessage
- showsPrefixPrec :: Int -> ShowS
- showPrefix :: String
- prettysPrefixPrec :: Int -> ShowS
- prettyPrefix :: String
- showsPrefix :: forall (p :: Prefix). ShowPrefix p => ShowS
- prettysPrefix :: forall (p :: Prefix). ShowPrefix p => ShowS
- newtype MetaPrefix (p :: Prefix) (u :: Unit) a = MetaPrefix (p u a)
- prefixToBaseUnit :: forall p (u :: Unit) a. (PrefixFactor p a, ConvertibleUnit u a, BaseUnitOf (p u) ~ BaseUnitOf u) => p u a -> BaseUnitOf u a
- prefixFromBaseUnit :: forall p (u :: Unit) a. (PrefixFactor p a, ConvertibleUnit u a, BaseUnitOf (p u) a ~ BaseUnitOf u a) => BaseUnitOf (p u) a -> p u a
Documentation
class (forall (u :: Unit). IsUnit u => IsUnit (p u)) => IsPrefix (p :: Prefix) Source #
The application of a prefix to a unit must always be a unit.
class (Fractional a, IsPrefix p) => PrefixFactor (p :: Prefix) a where Source #
A prefix that has a conversion factor.
Methods
prefixFactor :: a Source #
Prefix conversion factor from the prefixed unit to the corresponding standard unit
>>>
prefixFactor @Kilo
1000.0
Instances
class IsPrefix p => ShowPrefix (p :: Prefix) where Source #
Prefixes that can be shown as a string, or as a type error message.
Minimal complete definition
Associated Types
type ShowPrefixType (p :: Prefix) :: ErrorMessage Source #
Allows to print units in conversion error messages
>>>
type ShowPrefix Kilo = "k"
Methods
showsPrefixPrec :: Int -> ShowS Source #
Convert a prefix to a readable string
should satisfy the law :showsPrefixPrec
showsPrefixPrec d x r ++ s == showsPrec d x (r ++ s)
showPrefix :: String Source #
Convert a prefix to a string representing its type.
>>>
showPrefix @Kilo
"Kilo"
prettysPrefixPrec :: Int -> ShowS Source #
Same as
but for pretty printing.showsPrefixPrec
should satisfy the law :prettysPrefixPrec
prettysPrefixPrec d x r ++ s == prettysPrec d x (r ++ s)
prettyPrefix :: String Source #
Same as
but for pretty printingshowPrefix
>>>
prettyPrefix @Kilo
"k"
Instances
showsPrefix :: forall (p :: Prefix). ShowPrefix p => ShowS Source #
Equivalent to showsPrefixPrec
with a precedence of 0.
prettysPrefix :: forall (p :: Prefix). ShowPrefix p => ShowS Source #
Equivalent to prettysPrefixPrec
with a precedence of 0.
newtype MetaPrefix (p :: Prefix) (u :: Unit) a Source #
A prefix that can represent any prefix.
This can be used with the `deriving via` mechanism to derive some of the prefix instances.
Constructors
MetaPrefix (p u a) |
Instances
ShowPrefix p => ShowPrefix (MetaPrefix p) Source # | |||||
Defined in Data.Units.Base.Prefix Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
PrefixFactor p a => PrefixFactor (MetaPrefix p) a Source # | |||||
Defined in Data.Units.Base.Prefix Methods prefixFactor :: a Source # | |||||
(IsPrefix p, IsUnit u) => IsUnit (MetaPrefix p u) Source # | |||||
Defined in Data.Units.Base.Prefix Associated Types
| |||||
(ShowPrefix p, ShowUnit u) => ShowUnit (MetaPrefix p u) Source # | |||||
Defined in Data.Units.Base.Prefix Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
(PrefixFactor p a, ConversionFactor u a, BaseUnitOf (p u) ~ BaseUnitOf u) => ConversionFactor (MetaPrefix p u) a Source # | |||||
Defined in Data.Units.Base.Prefix | |||||
(PrefixFactor p a, ConvertibleUnit u a, BaseUnitOf (p u) ~ BaseUnitOf u) => ConvertibleUnit (MetaPrefix p u) a Source # | |||||
Defined in Data.Units.Base.Prefix Methods toBaseUnit :: MetaPrefix p u a -> BaseUnitOf (MetaPrefix p u) a Source # fromBaseUnit :: BaseUnitOf (MetaPrefix p u) a -> MetaPrefix p u a Source # | |||||
(Show a, ShowUnit (p u)) => Show (MetaPrefix p u a) Source # | |||||
Defined in Data.Units.Base.Prefix Methods showsPrec :: Int -> MetaPrefix p u a -> ShowS show :: MetaPrefix p u a -> String showList :: [MetaPrefix p u a] -> ShowS | |||||
type ShowPrefixType (MetaPrefix p) Source # | |||||
Defined in Data.Units.Base.Prefix | |||||
type DimOf (MetaPrefix p u) Source # | |||||
Defined in Data.Units.Base.Prefix | |||||
type ShowUnitType (MetaPrefix p u) Source # | |||||
Defined in Data.Units.Base.Prefix |
prefixToBaseUnit :: forall p (u :: Unit) a. (PrefixFactor p a, ConvertibleUnit u a, BaseUnitOf (p u) ~ BaseUnitOf u) => p u a -> BaseUnitOf u a Source #
Convert a prefixed unit to the corresponding standard unit.
prefixFromBaseUnit :: forall p (u :: Unit) a. (PrefixFactor p a, ConvertibleUnit u a, BaseUnitOf (p u) a ~ BaseUnitOf u a) => BaseUnitOf (p u) a -> p u a Source #
Convert a standard unit to the corresponding prefixed unit.