convert-units-0: Arithmetic and type checked conversions between units.
Copyright(c) Alice Rixte 2025
LicenseBSD 3
Maintaineralice.rixte@u-bordeaux.fr
Stabilityunstable
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Units.Base.Prefix

Description

Provides a way to define prefixes for any system of units.

Synopsis

Documentation

type Prefix = Unit -> Unit Source #

A unit prefix, like Kilo, Milli, etc.

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.

Instances

Instances details
(forall (u :: Unit). IsUnit u => IsUnit (p u)) => IsPrefix p Source # 
Instance details

Defined in Data.Units.Base.Prefix

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

Instances details
Fractional a => PrefixFactor Atto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Centi a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Deca a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Deci a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Exa a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Femto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Giga a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Hecto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Kilo a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Mega a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Micro a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Milli a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Nano a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Peta a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Pico a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Quecca a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Quecto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Ronna a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Ronto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Tera a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Yocto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Yotta a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Zepto a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

Fractional a => PrefixFactor Zetta a Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

prefixFactor :: a Source #

PrefixFactor p a => PrefixFactor (MetaPrefix p) a Source # 
Instance details

Defined in Data.Units.Base.Prefix

Methods

prefixFactor :: a Source #

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

showPrefix | showsPrefixPrec

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

showsPrefixPrec should satisfy the law :

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 showsPrefixPrec but for pretty printing.

prettysPrefixPrec should satisfy the law :

prettysPrefixPrec d x r ++ s  ==  prettysPrec d x (r ++ s)

prettyPrefix :: String Source #

Same as showPrefix but for pretty printing

>>> prettyPrefix @Kilo
"k"

Instances

Instances details
ShowPrefix Atto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Atto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Centi Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Centi 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Deca Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Deca 
Instance details

Defined in Data.Units.SI.Prefixes

type ShowPrefixType Deca = 'Text "da"

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Deci Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Deci 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Exa Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Exa 
Instance details

Defined in Data.Units.SI.Prefixes

type ShowPrefixType Exa = 'Text "E"

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Femto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Femto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Giga Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Giga 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Hecto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Hecto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Kilo Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Kilo 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Mega Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Mega 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Micro Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Micro 
Instance details

Defined in Data.Units.SI.Prefixes

type ShowPrefixType Micro = 'Text "\181"

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Milli Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Milli 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Nano Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Nano 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Peta Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Peta 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Pico Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Pico 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Quecca Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Quecca 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Quecto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Quecto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Ronna Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Ronna 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Ronto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Ronto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Tera Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Tera 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Yocto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Yocto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Yotta Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Yotta 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Zepto Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Zepto 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix Zetta Source # 
Instance details

Defined in Data.Units.SI.Prefixes

Associated Types

type ShowPrefixType Zetta 
Instance details

Defined in Data.Units.SI.Prefixes

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

ShowPrefix p => ShowPrefix (MetaPrefix p) Source # 
Instance details

Defined in Data.Units.Base.Prefix

Associated Types

type ShowPrefixType (MetaPrefix p) 
Instance details

Defined in Data.Units.Base.Prefix

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

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

Instances details
ShowPrefix p => ShowPrefix (MetaPrefix p) Source # 
Instance details

Defined in Data.Units.Base.Prefix

Associated Types

type ShowPrefixType (MetaPrefix p) 
Instance details

Defined in Data.Units.Base.Prefix

Methods

showsPrefixPrec :: Int -> ShowS Source #

showPrefix :: String Source #

prettysPrefixPrec :: Int -> ShowS Source #

prettyPrefix :: String Source #

PrefixFactor p a => PrefixFactor (MetaPrefix p) a Source # 
Instance details

Defined in Data.Units.Base.Prefix

Methods

prefixFactor :: a Source #

(IsPrefix p, IsUnit u) => IsUnit (MetaPrefix p u) Source # 
Instance details

Defined in Data.Units.Base.Prefix

Associated Types

type DimOf (MetaPrefix p u) 
Instance details

Defined in Data.Units.Base.Prefix

type DimOf (MetaPrefix p u) = DimOf u
(ShowPrefix p, ShowUnit u) => ShowUnit (MetaPrefix p u) Source # 
Instance details

Defined in Data.Units.Base.Prefix

Associated Types

type ShowUnitType (MetaPrefix p u) 
Instance details

Defined in Data.Units.Base.Prefix

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String 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 # 
Instance details

Defined in Data.Units.Base.Prefix

Methods

factor :: a Source #

(PrefixFactor p a, ConvertibleUnit u a, BaseUnitOf (p u) ~ BaseUnitOf u) => ConvertibleUnit (MetaPrefix p u) a Source # 
Instance details

Defined in Data.Units.Base.Prefix

(Show a, ShowUnit (p u)) => Show (MetaPrefix p u a) Source # 
Instance details

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 # 
Instance details

Defined in Data.Units.Base.Prefix

type DimOf (MetaPrefix p u) Source # 
Instance details

Defined in Data.Units.Base.Prefix

type DimOf (MetaPrefix p u) = DimOf u
type ShowUnitType (MetaPrefix p u) Source # 
Instance details

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.