Copyright | (c) Alice Rixte 2025 |
---|---|
License | BSD 3 |
Maintainer | alice.rixte@u-bordeaux.fr |
Stability | stable |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Data.Units.SI.Prefixes
Description
Prefixes for the International System of Units (abbreviated SI).
Synopsis
- newtype Quecto (u :: Unit) a = Quecto (u a)
- newtype Ronto (u :: Unit) a = Ronto (u a)
- newtype Yocto (u :: Unit) a = Yocto (u a)
- newtype Zepto (u :: Unit) a = Zepto (u a)
- newtype Atto (u :: Unit) a = Atto (u a)
- newtype Femto (u :: Unit) a = Femto (u a)
- newtype Pico (u :: Unit) a = Pico (u a)
- newtype Nano (u :: Unit) a = Nano (u a)
- newtype Micro (u :: Unit) a = Micro (u a)
- newtype Milli (u :: Unit) a = Milli (u a)
- newtype Centi (u :: Unit) a = Centi (u a)
- newtype Deci (u :: Unit) a = Deci (u a)
- newtype Deca (u :: Unit) a = Deca (u a)
- newtype Hecto (u :: Unit) a = Hecto (u a)
- newtype Kilo (u :: Unit) a = Kilo (u a)
- newtype Mega (u :: Unit) a = Mega (u a)
- newtype Giga (u :: Unit) a = Giga (u a)
- newtype Tera (u :: Unit) a = Tera (u a)
- newtype Peta (u :: Unit) a = Peta (u a)
- newtype Exa (u :: Unit) a = Exa (u a)
- newtype Zetta (u :: Unit) a = Zetta (u a)
- newtype Yotta (u :: Unit) a = Yotta (u a)
- newtype Ronna (u :: Unit) a = Ronna (u a)
- newtype Quecca (u :: Unit) a = Quecca (u a)
Documentation
newtype Quecto (u :: Unit) a Source #
SI prefix for 10⁻³⁰
Constructors
Quecto (u a) |
Instances
newtype Ronto (u :: Unit) a Source #
SI prefix for 10⁻²⁷
Constructors
Ronto (u a) |
Instances
ShowPrefix Ronto Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Ronto a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Ronto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Ronto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Ronto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Ronto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Ronto u a -> BaseUnitOf (Ronto u) a Source # fromBaseUnit :: BaseUnitOf (Ronto u) a -> Ronto u a Source # | |||||
Floating (u a) => Floating (Ronto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Ronto u a -> Ronto u a (**) :: Ronto u a -> Ronto u a -> Ronto u a logBase :: Ronto u a -> Ronto u a -> Ronto u a asin :: Ronto u a -> Ronto u a acos :: Ronto u a -> Ronto u a atan :: Ronto u a -> Ronto u a sinh :: Ronto u a -> Ronto u a cosh :: Ronto u a -> Ronto u a tanh :: Ronto u a -> Ronto u a asinh :: Ronto u a -> Ronto u a acosh :: Ronto u a -> Ronto u a atanh :: Ronto u a -> Ronto u a log1p :: Ronto u a -> Ronto u a expm1 :: Ronto u a -> Ronto u a | |||||
RealFloat (u a) => RealFloat (Ronto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Ronto u a -> Integer floatDigits :: Ronto u a -> Int floatRange :: Ronto u a -> (Int, Int) decodeFloat :: Ronto u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Ronto u a significand :: Ronto u a -> Ronto u a scaleFloat :: Int -> Ronto u a -> Ronto u a isInfinite :: Ronto u a -> Bool isDenormalized :: Ronto u a -> Bool isNegativeZero :: Ronto u a -> Bool | |||||
Num (u a) => Num (Ronto u a) Source # | |||||
Fractional (u a) => Fractional (Ronto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Ronto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Ronto u a -> Rational | |||||
RealFrac (u a) => RealFrac (Ronto u a) Source # | |||||
(Show a, ShowUnit u) => Show (Ronto u a) Source # | |||||
Eq (u a) => Eq (Ronto u a) Source # | |||||
Ord (u a) => Ord (Ronto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Ronto Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Ronto u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Ronto u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Yocto (u :: Unit) a Source #
SI prefix for 10⁻²⁴
Constructors
Yocto (u a) |
Instances
ShowPrefix Yocto Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Yocto a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Yocto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Yocto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Yocto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Yocto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Yocto u a -> BaseUnitOf (Yocto u) a Source # fromBaseUnit :: BaseUnitOf (Yocto u) a -> Yocto u a Source # | |||||
Floating (u a) => Floating (Yocto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Yocto u a -> Yocto u a (**) :: Yocto u a -> Yocto u a -> Yocto u a logBase :: Yocto u a -> Yocto u a -> Yocto u a asin :: Yocto u a -> Yocto u a acos :: Yocto u a -> Yocto u a atan :: Yocto u a -> Yocto u a sinh :: Yocto u a -> Yocto u a cosh :: Yocto u a -> Yocto u a tanh :: Yocto u a -> Yocto u a asinh :: Yocto u a -> Yocto u a acosh :: Yocto u a -> Yocto u a atanh :: Yocto u a -> Yocto u a log1p :: Yocto u a -> Yocto u a expm1 :: Yocto u a -> Yocto u a | |||||
RealFloat (u a) => RealFloat (Yocto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Yocto u a -> Integer floatDigits :: Yocto u a -> Int floatRange :: Yocto u a -> (Int, Int) decodeFloat :: Yocto u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Yocto u a significand :: Yocto u a -> Yocto u a scaleFloat :: Int -> Yocto u a -> Yocto u a isInfinite :: Yocto u a -> Bool isDenormalized :: Yocto u a -> Bool isNegativeZero :: Yocto u a -> Bool | |||||
Num (u a) => Num (Yocto u a) Source # | |||||
Fractional (u a) => Fractional (Yocto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Yocto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Yocto u a -> Rational | |||||
RealFrac (u a) => RealFrac (Yocto u a) Source # | |||||
(Show a, ShowUnit u) => Show (Yocto u a) Source # | |||||
Eq (u a) => Eq (Yocto u a) Source # | |||||
Ord (u a) => Ord (Yocto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Yocto Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Yocto u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Yocto u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Zepto (u :: Unit) a Source #
SI prefix for 10⁻²¹
Constructors
Zepto (u a) |
Instances
ShowPrefix Zepto Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Zepto a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Zepto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Zepto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Zepto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Zepto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Zepto u a -> BaseUnitOf (Zepto u) a Source # fromBaseUnit :: BaseUnitOf (Zepto u) a -> Zepto u a Source # | |||||
Floating (u a) => Floating (Zepto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Zepto u a -> Zepto u a (**) :: Zepto u a -> Zepto u a -> Zepto u a logBase :: Zepto u a -> Zepto u a -> Zepto u a asin :: Zepto u a -> Zepto u a acos :: Zepto u a -> Zepto u a atan :: Zepto u a -> Zepto u a sinh :: Zepto u a -> Zepto u a cosh :: Zepto u a -> Zepto u a tanh :: Zepto u a -> Zepto u a asinh :: Zepto u a -> Zepto u a acosh :: Zepto u a -> Zepto u a atanh :: Zepto u a -> Zepto u a log1p :: Zepto u a -> Zepto u a expm1 :: Zepto u a -> Zepto u a | |||||
RealFloat (u a) => RealFloat (Zepto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Zepto u a -> Integer floatDigits :: Zepto u a -> Int floatRange :: Zepto u a -> (Int, Int) decodeFloat :: Zepto u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Zepto u a significand :: Zepto u a -> Zepto u a scaleFloat :: Int -> Zepto u a -> Zepto u a isInfinite :: Zepto u a -> Bool isDenormalized :: Zepto u a -> Bool isNegativeZero :: Zepto u a -> Bool | |||||
Num (u a) => Num (Zepto u a) Source # | |||||
Fractional (u a) => Fractional (Zepto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Zepto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Zepto u a -> Rational | |||||
RealFrac (u a) => RealFrac (Zepto u a) Source # | |||||
(Show a, ShowUnit u) => Show (Zepto u a) Source # | |||||
Eq (u a) => Eq (Zepto u a) Source # | |||||
Ord (u a) => Ord (Zepto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Zepto Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Zepto u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Zepto u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Atto (u :: Unit) a Source #
SI prefix for 10⁻¹⁸
Constructors
Atto (u a) |
Instances
ShowPrefix Atto Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Atto a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Atto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Atto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Atto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Atto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Atto u a -> BaseUnitOf (Atto u) a Source # fromBaseUnit :: BaseUnitOf (Atto u) a -> Atto u a Source # | |||||
Floating (u a) => Floating (Atto u a) Source # | |||||
RealFloat (u a) => RealFloat (Atto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Atto u a -> Integer floatDigits :: Atto u a -> Int floatRange :: Atto u a -> (Int, Int) decodeFloat :: Atto u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Atto u a significand :: Atto u a -> Atto u a scaleFloat :: Int -> Atto u a -> Atto u a isInfinite :: Atto u a -> Bool isDenormalized :: Atto u a -> Bool isNegativeZero :: Atto u a -> Bool | |||||
Num (u a) => Num (Atto u a) Source # | |||||
Fractional (u a) => Fractional (Atto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Atto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Atto u a -> Rational | |||||
RealFrac (u a) => RealFrac (Atto u a) Source # | |||||
(Show a, ShowUnit u) => Show (Atto u a) Source # | |||||
Eq (u a) => Eq (Atto u a) Source # | |||||
Ord (u a) => Ord (Atto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Atto Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Atto u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Atto u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Femto (u :: Unit) a Source #
SI prefix for 10⁻¹⁵
Constructors
Femto (u a) |
Instances
ShowPrefix Femto Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Femto a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Femto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Femto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Femto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Femto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Femto u a -> BaseUnitOf (Femto u) a Source # fromBaseUnit :: BaseUnitOf (Femto u) a -> Femto u a Source # | |||||
Floating (u a) => Floating (Femto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Femto u a -> Femto u a (**) :: Femto u a -> Femto u a -> Femto u a logBase :: Femto u a -> Femto u a -> Femto u a asin :: Femto u a -> Femto u a acos :: Femto u a -> Femto u a atan :: Femto u a -> Femto u a sinh :: Femto u a -> Femto u a cosh :: Femto u a -> Femto u a tanh :: Femto u a -> Femto u a asinh :: Femto u a -> Femto u a acosh :: Femto u a -> Femto u a atanh :: Femto u a -> Femto u a log1p :: Femto u a -> Femto u a expm1 :: Femto u a -> Femto u a | |||||
RealFloat (u a) => RealFloat (Femto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Femto u a -> Integer floatDigits :: Femto u a -> Int floatRange :: Femto u a -> (Int, Int) decodeFloat :: Femto u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Femto u a significand :: Femto u a -> Femto u a scaleFloat :: Int -> Femto u a -> Femto u a isInfinite :: Femto u a -> Bool isDenormalized :: Femto u a -> Bool isNegativeZero :: Femto u a -> Bool | |||||
Num (u a) => Num (Femto u a) Source # | |||||
Fractional (u a) => Fractional (Femto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Femto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Femto u a -> Rational | |||||
RealFrac (u a) => RealFrac (Femto u a) Source # | |||||
(Show a, ShowUnit u) => Show (Femto u a) Source # | |||||
Eq (u a) => Eq (Femto u a) Source # | |||||
Ord (u a) => Ord (Femto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Femto Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Femto u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Femto u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Pico (u :: Unit) a Source #
SI prefix for 10⁻¹²
Constructors
Pico (u a) |
Instances
ShowPrefix Pico Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Pico a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Pico u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Pico u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Pico u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Pico u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Pico u a -> BaseUnitOf (Pico u) a Source # fromBaseUnit :: BaseUnitOf (Pico u) a -> Pico u a Source # | |||||
Floating (u a) => Floating (Pico u a) Source # | |||||
RealFloat (u a) => RealFloat (Pico u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Pico u a -> Integer floatDigits :: Pico u a -> Int floatRange :: Pico u a -> (Int, Int) decodeFloat :: Pico u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Pico u a significand :: Pico u a -> Pico u a scaleFloat :: Int -> Pico u a -> Pico u a isInfinite :: Pico u a -> Bool isDenormalized :: Pico u a -> Bool isNegativeZero :: Pico u a -> Bool | |||||
Num (u a) => Num (Pico u a) Source # | |||||
Fractional (u a) => Fractional (Pico u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Pico u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Pico u a -> Rational | |||||
RealFrac (u a) => RealFrac (Pico u a) Source # | |||||
(Show a, ShowUnit u) => Show (Pico u a) Source # | |||||
Eq (u a) => Eq (Pico u a) Source # | |||||
Ord (u a) => Ord (Pico u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Pico Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Pico u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Pico u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Nano (u :: Unit) a Source #
SI prefix for 10⁻⁹
Constructors
Nano (u a) |
Instances
ShowPrefix Nano Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Nano a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Nano u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Nano u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Nano u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Nano u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Nano u a -> BaseUnitOf (Nano u) a Source # fromBaseUnit :: BaseUnitOf (Nano u) a -> Nano u a Source # | |||||
Floating (u a) => Floating (Nano u a) Source # | |||||
RealFloat (u a) => RealFloat (Nano u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Nano u a -> Integer floatDigits :: Nano u a -> Int floatRange :: Nano u a -> (Int, Int) decodeFloat :: Nano u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Nano u a significand :: Nano u a -> Nano u a scaleFloat :: Int -> Nano u a -> Nano u a isInfinite :: Nano u a -> Bool isDenormalized :: Nano u a -> Bool isNegativeZero :: Nano u a -> Bool | |||||
Num (u a) => Num (Nano u a) Source # | |||||
Fractional (u a) => Fractional (Nano u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Nano u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Nano u a -> Rational | |||||
RealFrac (u a) => RealFrac (Nano u a) Source # | |||||
(Show a, ShowUnit u) => Show (Nano u a) Source # | |||||
Eq (u a) => Eq (Nano u a) Source # | |||||
Ord (u a) => Ord (Nano u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Nano Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Nano u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Nano u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Micro (u :: Unit) a Source #
SI prefix for 10⁻⁶
Constructors
Micro (u a) |
Instances
ShowPrefix Micro Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Micro a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Micro u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Micro u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Micro u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Micro u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Micro u a -> BaseUnitOf (Micro u) a Source # fromBaseUnit :: BaseUnitOf (Micro u) a -> Micro u a Source # | |||||
Floating (u a) => Floating (Micro u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Micro u a -> Micro u a (**) :: Micro u a -> Micro u a -> Micro u a logBase :: Micro u a -> Micro u a -> Micro u a asin :: Micro u a -> Micro u a acos :: Micro u a -> Micro u a atan :: Micro u a -> Micro u a sinh :: Micro u a -> Micro u a cosh :: Micro u a -> Micro u a tanh :: Micro u a -> Micro u a asinh :: Micro u a -> Micro u a acosh :: Micro u a -> Micro u a atanh :: Micro u a -> Micro u a log1p :: Micro u a -> Micro u a expm1 :: Micro u a -> Micro u a | |||||
RealFloat (u a) => RealFloat (Micro u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Micro u a -> Integer floatDigits :: Micro u a -> Int floatRange :: Micro u a -> (Int, Int) decodeFloat :: Micro u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Micro u a significand :: Micro u a -> Micro u a scaleFloat :: Int -> Micro u a -> Micro u a isInfinite :: Micro u a -> Bool isDenormalized :: Micro u a -> Bool isNegativeZero :: Micro u a -> Bool | |||||
Num (u a) => Num (Micro u a) Source # | |||||
Fractional (u a) => Fractional (Micro u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Micro u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Micro u a -> Rational | |||||
RealFrac (u a) => RealFrac (Micro u a) Source # | |||||
(Show a, ShowUnit u) => Show (Micro u a) Source # | |||||
Eq (u a) => Eq (Micro u a) Source # | |||||
Ord (u a) => Ord (Micro u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Micro Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Micro u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Micro u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Milli (u :: Unit) a Source #
SI prefix for 10⁻³
Constructors
Milli (u a) |
Instances
ShowPrefix Milli Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Milli a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Milli u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Milli u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Milli u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Milli u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Milli u a -> BaseUnitOf (Milli u) a Source # fromBaseUnit :: BaseUnitOf (Milli u) a -> Milli u a Source # | |||||
Floating (u a) => Floating (Milli u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Milli u a -> Milli u a (**) :: Milli u a -> Milli u a -> Milli u a logBase :: Milli u a -> Milli u a -> Milli u a asin :: Milli u a -> Milli u a acos :: Milli u a -> Milli u a atan :: Milli u a -> Milli u a sinh :: Milli u a -> Milli u a cosh :: Milli u a -> Milli u a tanh :: Milli u a -> Milli u a asinh :: Milli u a -> Milli u a acosh :: Milli u a -> Milli u a atanh :: Milli u a -> Milli u a log1p :: Milli u a -> Milli u a expm1 :: Milli u a -> Milli u a | |||||
RealFloat (u a) => RealFloat (Milli u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Milli u a -> Integer floatDigits :: Milli u a -> Int floatRange :: Milli u a -> (Int, Int) decodeFloat :: Milli u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Milli u a significand :: Milli u a -> Milli u a scaleFloat :: Int -> Milli u a -> Milli u a isInfinite :: Milli u a -> Bool isDenormalized :: Milli u a -> Bool isNegativeZero :: Milli u a -> Bool | |||||
Num (u a) => Num (Milli u a) Source # | |||||
Fractional (u a) => Fractional (Milli u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Milli u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Milli u a -> Rational | |||||
RealFrac (u a) => RealFrac (Milli u a) Source # | |||||
(Show a, ShowUnit u) => Show (Milli u a) Source # | |||||
Eq (u a) => Eq (Milli u a) Source # | |||||
Ord (u a) => Ord (Milli u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Milli Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Milli u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Milli u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Centi (u :: Unit) a Source #
SI prefix for 10⁻²
Constructors
Centi (u a) |
Instances
ShowPrefix Centi Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Centi a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Centi u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Centi u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Centi u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Centi u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Centi u a -> BaseUnitOf (Centi u) a Source # fromBaseUnit :: BaseUnitOf (Centi u) a -> Centi u a Source # | |||||
Floating (u a) => Floating (Centi u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Centi u a -> Centi u a (**) :: Centi u a -> Centi u a -> Centi u a logBase :: Centi u a -> Centi u a -> Centi u a asin :: Centi u a -> Centi u a acos :: Centi u a -> Centi u a atan :: Centi u a -> Centi u a sinh :: Centi u a -> Centi u a cosh :: Centi u a -> Centi u a tanh :: Centi u a -> Centi u a asinh :: Centi u a -> Centi u a acosh :: Centi u a -> Centi u a atanh :: Centi u a -> Centi u a log1p :: Centi u a -> Centi u a expm1 :: Centi u a -> Centi u a | |||||
RealFloat (u a) => RealFloat (Centi u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Centi u a -> Integer floatDigits :: Centi u a -> Int floatRange :: Centi u a -> (Int, Int) decodeFloat :: Centi u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Centi u a significand :: Centi u a -> Centi u a scaleFloat :: Int -> Centi u a -> Centi u a isInfinite :: Centi u a -> Bool isDenormalized :: Centi u a -> Bool isNegativeZero :: Centi u a -> Bool | |||||
Num (u a) => Num (Centi u a) Source # | |||||
Fractional (u a) => Fractional (Centi u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Centi u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Centi u a -> Rational | |||||
RealFrac (u a) => RealFrac (Centi u a) Source # | |||||
(Show a, ShowUnit u) => Show (Centi u a) Source # | |||||
Eq (u a) => Eq (Centi u a) Source # | |||||
Ord (u a) => Ord (Centi u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Centi Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Centi u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Centi u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Deci (u :: Unit) a Source #
SI prefix for 10⁻¹
Constructors
Deci (u a) |
Instances
ShowPrefix Deci Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Deci a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Deci u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Deci u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Deci u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Deci u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Deci u a -> BaseUnitOf (Deci u) a Source # fromBaseUnit :: BaseUnitOf (Deci u) a -> Deci u a Source # | |||||
Floating (u a) => Floating (Deci u a) Source # | |||||
RealFloat (u a) => RealFloat (Deci u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Deci u a -> Integer floatDigits :: Deci u a -> Int floatRange :: Deci u a -> (Int, Int) decodeFloat :: Deci u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Deci u a significand :: Deci u a -> Deci u a scaleFloat :: Int -> Deci u a -> Deci u a isInfinite :: Deci u a -> Bool isDenormalized :: Deci u a -> Bool isNegativeZero :: Deci u a -> Bool | |||||
Num (u a) => Num (Deci u a) Source # | |||||
Fractional (u a) => Fractional (Deci u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Deci u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Deci u a -> Rational | |||||
RealFrac (u a) => RealFrac (Deci u a) Source # | |||||
(Show a, ShowUnit u) => Show (Deci u a) Source # | |||||
Eq (u a) => Eq (Deci u a) Source # | |||||
Ord (u a) => Ord (Deci u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Deci Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Deci u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Deci u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Deca (u :: Unit) a Source #
SI prefix for 10¹
Constructors
Deca (u a) |
Instances
ShowPrefix Deca Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Deca a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Deca u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Deca u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Deca u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Deca u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Deca u a -> BaseUnitOf (Deca u) a Source # fromBaseUnit :: BaseUnitOf (Deca u) a -> Deca u a Source # | |||||
Floating (u a) => Floating (Deca u a) Source # | |||||
RealFloat (u a) => RealFloat (Deca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Deca u a -> Integer floatDigits :: Deca u a -> Int floatRange :: Deca u a -> (Int, Int) decodeFloat :: Deca u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Deca u a significand :: Deca u a -> Deca u a scaleFloat :: Int -> Deca u a -> Deca u a isInfinite :: Deca u a -> Bool isDenormalized :: Deca u a -> Bool isNegativeZero :: Deca u a -> Bool | |||||
Num (u a) => Num (Deca u a) Source # | |||||
Fractional (u a) => Fractional (Deca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Deca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Deca u a -> Rational | |||||
RealFrac (u a) => RealFrac (Deca u a) Source # | |||||
(Show a, ShowUnit u) => Show (Deca u a) Source # | |||||
Eq (u a) => Eq (Deca u a) Source # | |||||
Ord (u a) => Ord (Deca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Deca Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Deca u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Deca u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Hecto (u :: Unit) a Source #
SI prefix for 10²
Constructors
Hecto (u a) |
Instances
ShowPrefix Hecto Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Hecto a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Hecto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Hecto u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Hecto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Hecto u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Hecto u a -> BaseUnitOf (Hecto u) a Source # fromBaseUnit :: BaseUnitOf (Hecto u) a -> Hecto u a Source # | |||||
Floating (u a) => Floating (Hecto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Hecto u a -> Hecto u a (**) :: Hecto u a -> Hecto u a -> Hecto u a logBase :: Hecto u a -> Hecto u a -> Hecto u a asin :: Hecto u a -> Hecto u a acos :: Hecto u a -> Hecto u a atan :: Hecto u a -> Hecto u a sinh :: Hecto u a -> Hecto u a cosh :: Hecto u a -> Hecto u a tanh :: Hecto u a -> Hecto u a asinh :: Hecto u a -> Hecto u a acosh :: Hecto u a -> Hecto u a atanh :: Hecto u a -> Hecto u a log1p :: Hecto u a -> Hecto u a expm1 :: Hecto u a -> Hecto u a | |||||
RealFloat (u a) => RealFloat (Hecto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Hecto u a -> Integer floatDigits :: Hecto u a -> Int floatRange :: Hecto u a -> (Int, Int) decodeFloat :: Hecto u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Hecto u a significand :: Hecto u a -> Hecto u a scaleFloat :: Int -> Hecto u a -> Hecto u a isInfinite :: Hecto u a -> Bool isDenormalized :: Hecto u a -> Bool isNegativeZero :: Hecto u a -> Bool | |||||
Num (u a) => Num (Hecto u a) Source # | |||||
Fractional (u a) => Fractional (Hecto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Hecto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Hecto u a -> Rational | |||||
RealFrac (u a) => RealFrac (Hecto u a) Source # | |||||
(Show a, ShowUnit u) => Show (Hecto u a) Source # | |||||
Eq (u a) => Eq (Hecto u a) Source # | |||||
Ord (u a) => Ord (Hecto u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Hecto Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Hecto u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Hecto u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Kilo (u :: Unit) a Source #
SI prefix for 10³
Constructors
Kilo (u a) |
Instances
ShowPrefix Kilo Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Kilo a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Kilo u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Kilo u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Kilo u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Kilo u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Kilo u a -> BaseUnitOf (Kilo u) a Source # fromBaseUnit :: BaseUnitOf (Kilo u) a -> Kilo u a Source # | |||||
Floating (u a) => Floating (Kilo u a) Source # | |||||
RealFloat (u a) => RealFloat (Kilo u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Kilo u a -> Integer floatDigits :: Kilo u a -> Int floatRange :: Kilo u a -> (Int, Int) decodeFloat :: Kilo u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Kilo u a significand :: Kilo u a -> Kilo u a scaleFloat :: Int -> Kilo u a -> Kilo u a isInfinite :: Kilo u a -> Bool isDenormalized :: Kilo u a -> Bool isNegativeZero :: Kilo u a -> Bool | |||||
Num (u a) => Num (Kilo u a) Source # | |||||
Fractional (u a) => Fractional (Kilo u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Kilo u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Kilo u a -> Rational | |||||
RealFrac (u a) => RealFrac (Kilo u a) Source # | |||||
(Show a, ShowUnit u) => Show (Kilo u a) Source # | |||||
Eq (u a) => Eq (Kilo u a) Source # | |||||
Ord (u a) => Ord (Kilo u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Kilo Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Kilo u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Kilo u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Mega (u :: Unit) a Source #
SI prefix for 10⁶
Constructors
Mega (u a) |
Instances
ShowPrefix Mega Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Mega a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Mega u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Mega u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Mega u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Mega u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Mega u a -> BaseUnitOf (Mega u) a Source # fromBaseUnit :: BaseUnitOf (Mega u) a -> Mega u a Source # | |||||
Floating (u a) => Floating (Mega u a) Source # | |||||
RealFloat (u a) => RealFloat (Mega u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Mega u a -> Integer floatDigits :: Mega u a -> Int floatRange :: Mega u a -> (Int, Int) decodeFloat :: Mega u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Mega u a significand :: Mega u a -> Mega u a scaleFloat :: Int -> Mega u a -> Mega u a isInfinite :: Mega u a -> Bool isDenormalized :: Mega u a -> Bool isNegativeZero :: Mega u a -> Bool | |||||
Num (u a) => Num (Mega u a) Source # | |||||
Fractional (u a) => Fractional (Mega u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Mega u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Mega u a -> Rational | |||||
RealFrac (u a) => RealFrac (Mega u a) Source # | |||||
(Show a, ShowUnit u) => Show (Mega u a) Source # | |||||
Eq (u a) => Eq (Mega u a) Source # | |||||
Ord (u a) => Ord (Mega u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Mega Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Mega u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Mega u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Giga (u :: Unit) a Source #
SI prefix for 10⁹
Constructors
Giga (u a) |
Instances
ShowPrefix Giga Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Giga a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Giga u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Giga u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Giga u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Giga u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Giga u a -> BaseUnitOf (Giga u) a Source # fromBaseUnit :: BaseUnitOf (Giga u) a -> Giga u a Source # | |||||
Floating (u a) => Floating (Giga u a) Source # | |||||
RealFloat (u a) => RealFloat (Giga u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Giga u a -> Integer floatDigits :: Giga u a -> Int floatRange :: Giga u a -> (Int, Int) decodeFloat :: Giga u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Giga u a significand :: Giga u a -> Giga u a scaleFloat :: Int -> Giga u a -> Giga u a isInfinite :: Giga u a -> Bool isDenormalized :: Giga u a -> Bool isNegativeZero :: Giga u a -> Bool | |||||
Num (u a) => Num (Giga u a) Source # | |||||
Fractional (u a) => Fractional (Giga u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Giga u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Giga u a -> Rational | |||||
RealFrac (u a) => RealFrac (Giga u a) Source # | |||||
(Show a, ShowUnit u) => Show (Giga u a) Source # | |||||
Eq (u a) => Eq (Giga u a) Source # | |||||
Ord (u a) => Ord (Giga u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Giga Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Giga u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Giga u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Tera (u :: Unit) a Source #
SI prefix for 10¹²
Constructors
Tera (u a) |
Instances
ShowPrefix Tera Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Tera a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Tera u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Tera u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Tera u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Tera u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Tera u a -> BaseUnitOf (Tera u) a Source # fromBaseUnit :: BaseUnitOf (Tera u) a -> Tera u a Source # | |||||
Floating (u a) => Floating (Tera u a) Source # | |||||
RealFloat (u a) => RealFloat (Tera u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Tera u a -> Integer floatDigits :: Tera u a -> Int floatRange :: Tera u a -> (Int, Int) decodeFloat :: Tera u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Tera u a significand :: Tera u a -> Tera u a scaleFloat :: Int -> Tera u a -> Tera u a isInfinite :: Tera u a -> Bool isDenormalized :: Tera u a -> Bool isNegativeZero :: Tera u a -> Bool | |||||
Num (u a) => Num (Tera u a) Source # | |||||
Fractional (u a) => Fractional (Tera u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Tera u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Tera u a -> Rational | |||||
RealFrac (u a) => RealFrac (Tera u a) Source # | |||||
(Show a, ShowUnit u) => Show (Tera u a) Source # | |||||
Eq (u a) => Eq (Tera u a) Source # | |||||
Ord (u a) => Ord (Tera u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Tera Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Tera u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Tera u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Peta (u :: Unit) a Source #
SI prefix for 10¹⁵
Constructors
Peta (u a) |
Instances
ShowPrefix Peta Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Peta a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Peta u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Peta u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Peta u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Peta u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Peta u a -> BaseUnitOf (Peta u) a Source # fromBaseUnit :: BaseUnitOf (Peta u) a -> Peta u a Source # | |||||
Floating (u a) => Floating (Peta u a) Source # | |||||
RealFloat (u a) => RealFloat (Peta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Peta u a -> Integer floatDigits :: Peta u a -> Int floatRange :: Peta u a -> (Int, Int) decodeFloat :: Peta u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Peta u a significand :: Peta u a -> Peta u a scaleFloat :: Int -> Peta u a -> Peta u a isInfinite :: Peta u a -> Bool isDenormalized :: Peta u a -> Bool isNegativeZero :: Peta u a -> Bool | |||||
Num (u a) => Num (Peta u a) Source # | |||||
Fractional (u a) => Fractional (Peta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Peta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Peta u a -> Rational | |||||
RealFrac (u a) => RealFrac (Peta u a) Source # | |||||
(Show a, ShowUnit u) => Show (Peta u a) Source # | |||||
Eq (u a) => Eq (Peta u a) Source # | |||||
Ord (u a) => Ord (Peta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Peta Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Peta u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Peta u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Exa (u :: Unit) a Source #
SI prefix for 10¹⁸
Constructors
Exa (u a) |
Instances
ShowPrefix Exa Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Exa a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Exa u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Exa u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Exa u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Exa u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Exa u a -> BaseUnitOf (Exa u) a Source # fromBaseUnit :: BaseUnitOf (Exa u) a -> Exa u a Source # | |||||
Floating (u a) => Floating (Exa u a) Source # | |||||
RealFloat (u a) => RealFloat (Exa u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Exa u a -> Integer floatDigits :: Exa u a -> Int floatRange :: Exa u a -> (Int, Int) decodeFloat :: Exa u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Exa u a significand :: Exa u a -> Exa u a scaleFloat :: Int -> Exa u a -> Exa u a isInfinite :: Exa u a -> Bool isDenormalized :: Exa u a -> Bool isNegativeZero :: Exa u a -> Bool | |||||
Num (u a) => Num (Exa u a) Source # | |||||
Fractional (u a) => Fractional (Exa u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Exa u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Exa u a -> Rational | |||||
RealFrac (u a) => RealFrac (Exa u a) Source # | |||||
(Show a, ShowUnit u) => Show (Exa u a) Source # | |||||
Eq (u a) => Eq (Exa u a) Source # | |||||
Ord (u a) => Ord (Exa u a) Source # | |||||
type ShowPrefixType Exa Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Exa u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Exa u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Zetta (u :: Unit) a Source #
SI prefix for 10²¹
Constructors
Zetta (u a) |
Instances
ShowPrefix Zetta Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Zetta a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Zetta u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Zetta u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Zetta u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Zetta u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Zetta u a -> BaseUnitOf (Zetta u) a Source # fromBaseUnit :: BaseUnitOf (Zetta u) a -> Zetta u a Source # | |||||
Floating (u a) => Floating (Zetta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Zetta u a -> Zetta u a (**) :: Zetta u a -> Zetta u a -> Zetta u a logBase :: Zetta u a -> Zetta u a -> Zetta u a asin :: Zetta u a -> Zetta u a acos :: Zetta u a -> Zetta u a atan :: Zetta u a -> Zetta u a sinh :: Zetta u a -> Zetta u a cosh :: Zetta u a -> Zetta u a tanh :: Zetta u a -> Zetta u a asinh :: Zetta u a -> Zetta u a acosh :: Zetta u a -> Zetta u a atanh :: Zetta u a -> Zetta u a log1p :: Zetta u a -> Zetta u a expm1 :: Zetta u a -> Zetta u a | |||||
RealFloat (u a) => RealFloat (Zetta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Zetta u a -> Integer floatDigits :: Zetta u a -> Int floatRange :: Zetta u a -> (Int, Int) decodeFloat :: Zetta u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Zetta u a significand :: Zetta u a -> Zetta u a scaleFloat :: Int -> Zetta u a -> Zetta u a isInfinite :: Zetta u a -> Bool isDenormalized :: Zetta u a -> Bool isNegativeZero :: Zetta u a -> Bool | |||||
Num (u a) => Num (Zetta u a) Source # | |||||
Fractional (u a) => Fractional (Zetta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Zetta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Zetta u a -> Rational | |||||
RealFrac (u a) => RealFrac (Zetta u a) Source # | |||||
(Show a, ShowUnit u) => Show (Zetta u a) Source # | |||||
Eq (u a) => Eq (Zetta u a) Source # | |||||
Ord (u a) => Ord (Zetta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Zetta Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Zetta u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Zetta u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Yotta (u :: Unit) a Source #
SI prefix for 10²⁴
Constructors
Yotta (u a) |
Instances
ShowPrefix Yotta Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Yotta a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Yotta u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Yotta u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Yotta u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Yotta u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Yotta u a -> BaseUnitOf (Yotta u) a Source # fromBaseUnit :: BaseUnitOf (Yotta u) a -> Yotta u a Source # | |||||
Floating (u a) => Floating (Yotta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Yotta u a -> Yotta u a (**) :: Yotta u a -> Yotta u a -> Yotta u a logBase :: Yotta u a -> Yotta u a -> Yotta u a asin :: Yotta u a -> Yotta u a acos :: Yotta u a -> Yotta u a atan :: Yotta u a -> Yotta u a sinh :: Yotta u a -> Yotta u a cosh :: Yotta u a -> Yotta u a tanh :: Yotta u a -> Yotta u a asinh :: Yotta u a -> Yotta u a acosh :: Yotta u a -> Yotta u a atanh :: Yotta u a -> Yotta u a log1p :: Yotta u a -> Yotta u a expm1 :: Yotta u a -> Yotta u a | |||||
RealFloat (u a) => RealFloat (Yotta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Yotta u a -> Integer floatDigits :: Yotta u a -> Int floatRange :: Yotta u a -> (Int, Int) decodeFloat :: Yotta u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Yotta u a significand :: Yotta u a -> Yotta u a scaleFloat :: Int -> Yotta u a -> Yotta u a isInfinite :: Yotta u a -> Bool isDenormalized :: Yotta u a -> Bool isNegativeZero :: Yotta u a -> Bool | |||||
Num (u a) => Num (Yotta u a) Source # | |||||
Fractional (u a) => Fractional (Yotta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Yotta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Yotta u a -> Rational | |||||
RealFrac (u a) => RealFrac (Yotta u a) Source # | |||||
(Show a, ShowUnit u) => Show (Yotta u a) Source # | |||||
Eq (u a) => Eq (Yotta u a) Source # | |||||
Ord (u a) => Ord (Yotta u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Yotta Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Yotta u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Yotta u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Ronna (u :: Unit) a Source #
SI prefix for 10²⁷
Constructors
Ronna (u a) |
Instances
ShowPrefix Ronna Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Ronna a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Ronna u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Ronna u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Ronna u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Ronna u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Ronna u a -> BaseUnitOf (Ronna u) a Source # fromBaseUnit :: BaseUnitOf (Ronna u) a -> Ronna u a Source # | |||||
Floating (u a) => Floating (Ronna u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods sqrt :: Ronna u a -> Ronna u a (**) :: Ronna u a -> Ronna u a -> Ronna u a logBase :: Ronna u a -> Ronna u a -> Ronna u a asin :: Ronna u a -> Ronna u a acos :: Ronna u a -> Ronna u a atan :: Ronna u a -> Ronna u a sinh :: Ronna u a -> Ronna u a cosh :: Ronna u a -> Ronna u a tanh :: Ronna u a -> Ronna u a asinh :: Ronna u a -> Ronna u a acosh :: Ronna u a -> Ronna u a atanh :: Ronna u a -> Ronna u a log1p :: Ronna u a -> Ronna u a expm1 :: Ronna u a -> Ronna u a | |||||
RealFloat (u a) => RealFloat (Ronna u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Ronna u a -> Integer floatDigits :: Ronna u a -> Int floatRange :: Ronna u a -> (Int, Int) decodeFloat :: Ronna u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Ronna u a significand :: Ronna u a -> Ronna u a scaleFloat :: Int -> Ronna u a -> Ronna u a isInfinite :: Ronna u a -> Bool isDenormalized :: Ronna u a -> Bool isNegativeZero :: Ronna u a -> Bool | |||||
Num (u a) => Num (Ronna u a) Source # | |||||
Fractional (u a) => Fractional (Ronna u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Ronna u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Ronna u a -> Rational | |||||
RealFrac (u a) => RealFrac (Ronna u a) Source # | |||||
(Show a, ShowUnit u) => Show (Ronna u a) Source # | |||||
Eq (u a) => Eq (Ronna u a) Source # | |||||
Ord (u a) => Ord (Ronna u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowPrefixType Ronna Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Ronna u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Ronna u) Source # | |||||
Defined in Data.Units.SI.Prefixes |
newtype Quecca (u :: Unit) a Source #
SI prefix for 10³⁰
Constructors
Quecca (u a) |
Instances
ShowPrefix Quecca Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsPrefixPrec :: Int -> ShowS Source # showPrefix :: String Source # prettysPrefixPrec :: Int -> ShowS Source # prettyPrefix :: String Source # | |||||
Fractional a => PrefixFactor Quecca a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods prefixFactor :: a Source # | |||||
IsUnit u => IsUnit (Quecca u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
| |||||
ShowUnit u => ShowUnit (Quecca u) Source # | |||||
Defined in Data.Units.SI.Prefixes Associated Types
Methods showsUnitPrec :: Int -> ShowS Source # prettysUnitPrec :: Int -> ShowS Source # prettyUnit :: String Source # | |||||
ConversionFactor u a => ConversionFactor (Quecca u) a Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
(ConvertibleUnit u a, Fractional a) => ConvertibleUnit (Quecca u) a Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toBaseUnit :: Quecca u a -> BaseUnitOf (Quecca u) a Source # fromBaseUnit :: BaseUnitOf (Quecca u) a -> Quecca u a Source # | |||||
Floating (u a) => Floating (Quecca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods exp :: Quecca u a -> Quecca u a log :: Quecca u a -> Quecca u a sqrt :: Quecca u a -> Quecca u a (**) :: Quecca u a -> Quecca u a -> Quecca u a logBase :: Quecca u a -> Quecca u a -> Quecca u a sin :: Quecca u a -> Quecca u a cos :: Quecca u a -> Quecca u a tan :: Quecca u a -> Quecca u a asin :: Quecca u a -> Quecca u a acos :: Quecca u a -> Quecca u a atan :: Quecca u a -> Quecca u a sinh :: Quecca u a -> Quecca u a cosh :: Quecca u a -> Quecca u a tanh :: Quecca u a -> Quecca u a asinh :: Quecca u a -> Quecca u a acosh :: Quecca u a -> Quecca u a atanh :: Quecca u a -> Quecca u a log1p :: Quecca u a -> Quecca u a expm1 :: Quecca u a -> Quecca u a | |||||
RealFloat (u a) => RealFloat (Quecca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods floatRadix :: Quecca u a -> Integer floatDigits :: Quecca u a -> Int floatRange :: Quecca u a -> (Int, Int) decodeFloat :: Quecca u a -> (Integer, Int) encodeFloat :: Integer -> Int -> Quecca u a significand :: Quecca u a -> Quecca u a scaleFloat :: Int -> Quecca u a -> Quecca u a isInfinite :: Quecca u a -> Bool isDenormalized :: Quecca u a -> Bool isNegativeZero :: Quecca u a -> Bool | |||||
Num (u a) => Num (Quecca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Fractional (u a) => Fractional (Quecca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
Real (u a) => Real (Quecca u a) Source # | |||||
Defined in Data.Units.SI.Prefixes Methods toRational :: Quecca u a -> Rational | |||||
RealFrac (u a) => RealFrac (Quecca u a) Source # | |||||
(Show a, ShowUnit u) => Show (Quecca u a) Source # | |||||
Eq (u a) => Eq (Quecca u a) Source # | |||||
Ord (u a) => Ord (Quecca u a) Source # | |||||
type ShowPrefixType Quecca Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type DimOf (Quecca u0) Source # | |||||
Defined in Data.Units.SI.Prefixes | |||||
type ShowUnitType (Quecca u) Source # | |||||
Defined in Data.Units.SI.Prefixes |