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

Data.Units.SI.System

Description

Base units and dimensions of the International System of Units (abbreviated SI).

Synopsis

Documentation

newtype Mass a Source #

The mass dimension, denotated M in SI.

This may contain a mass quantity with unspecified unit.

Constructors

Mass a 

Instances

Instances details
IsDim Mass Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit Mass 
Instance details

Defined in Data.Units.SI.System

ShowDim Mass Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType Mass 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Mass = 'Text "M"

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Mass a

exp :: Mass a -> Mass a

log :: Mass a -> Mass a

sqrt :: Mass a -> Mass a

(**) :: Mass a -> Mass a -> Mass a

logBase :: Mass a -> Mass a -> Mass a

sin :: Mass a -> Mass a

cos :: Mass a -> Mass a

tan :: Mass a -> Mass a

asin :: Mass a -> Mass a

acos :: Mass a -> Mass a

atan :: Mass a -> Mass a

sinh :: Mass a -> Mass a

cosh :: Mass a -> Mass a

tanh :: Mass a -> Mass a

asinh :: Mass a -> Mass a

acosh :: Mass a -> Mass a

atanh :: Mass a -> Mass a

log1p :: Mass a -> Mass a

expm1 :: Mass a -> Mass a

log1pexp :: Mass a -> Mass a

log1mexp :: Mass a -> Mass a

RealFloat a => RealFloat (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Mass a -> Integer

floatDigits :: Mass a -> Int

floatRange :: Mass a -> (Int, Int)

decodeFloat :: Mass a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Mass a

exponent :: Mass a -> Int

significand :: Mass a -> Mass a

scaleFloat :: Int -> Mass a -> Mass a

isNaN :: Mass a -> Bool

isInfinite :: Mass a -> Bool

isDenormalized :: Mass a -> Bool

isNegativeZero :: Mass a -> Bool

isIEEE :: Mass a -> Bool

atan2 :: Mass a -> Mass a -> Mass a

Num a => Num (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Mass a -> Mass a -> Mass a

(-) :: Mass a -> Mass a -> Mass a

(*) :: Mass a -> Mass a -> Mass a

negate :: Mass a -> Mass a

abs :: Mass a -> Mass a

signum :: Mass a -> Mass a

fromInteger :: Integer -> Mass a

Fractional a => Fractional (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Mass a -> Mass a -> Mass a

recip :: Mass a -> Mass a

fromRational :: Rational -> Mass a

Real a => Real (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Mass a -> Rational

RealFrac a => RealFrac (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Mass a -> (b, Mass a)

truncate :: Integral b => Mass a -> b

round :: Integral b => Mass a -> b

ceiling :: Integral b => Mass a -> b

floor :: Integral b => Mass a -> b

Show a => Show (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Mass a -> ShowS

show :: Mass a -> String

showList :: [Mass a] -> ShowS

Eq a => Eq (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Mass a -> Mass a -> Bool

(/=) :: Mass a -> Mass a -> Bool

Ord a => Ord (Mass a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Mass a -> Mass a -> Ordering

(<) :: Mass a -> Mass a -> Bool

(<=) :: Mass a -> Mass a -> Bool

(>) :: Mass a -> Mass a -> Bool

(>=) :: Mass a -> Mass a -> Bool

max :: Mass a -> Mass a -> Mass a

min :: Mass a -> Mass a -> Mass a

type DimId Mass Source # 
Instance details

Defined in Data.Units.SI.System

type DimId Mass = 'Pos 2000
type DimToUnit Mass Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Mass Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Mass = 'Text "M"

newtype Gram a Source #

A quantity in grams, denotated g in SI.

Notice that the base unit for the mass dimension is Kilo Gram, not Gram.

This is correctly taken into account by this library:

>>> from (Gram 8)
quantity @(Kilo Gram) 8.0e-3
>>> :kind! BaseUnitOf Gram
BaseUnitOf Gram :: * -> *
= Kilo Gram

Constructors

Gram a 

Instances

Instances details
IsUnit Gram Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Gram 
Instance details

Defined in Data.Units.SI.System

type DimOf Gram = Mass
ShowUnit Gram Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Gram 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Gram = 'Text "g"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Gram a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Gram a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Gram a

exp :: Gram a -> Gram a

log :: Gram a -> Gram a

sqrt :: Gram a -> Gram a

(**) :: Gram a -> Gram a -> Gram a

logBase :: Gram a -> Gram a -> Gram a

sin :: Gram a -> Gram a

cos :: Gram a -> Gram a

tan :: Gram a -> Gram a

asin :: Gram a -> Gram a

acos :: Gram a -> Gram a

atan :: Gram a -> Gram a

sinh :: Gram a -> Gram a

cosh :: Gram a -> Gram a

tanh :: Gram a -> Gram a

asinh :: Gram a -> Gram a

acosh :: Gram a -> Gram a

atanh :: Gram a -> Gram a

log1p :: Gram a -> Gram a

expm1 :: Gram a -> Gram a

log1pexp :: Gram a -> Gram a

log1mexp :: Gram a -> Gram a

RealFloat a => RealFloat (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Gram a -> Integer

floatDigits :: Gram a -> Int

floatRange :: Gram a -> (Int, Int)

decodeFloat :: Gram a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Gram a

exponent :: Gram a -> Int

significand :: Gram a -> Gram a

scaleFloat :: Int -> Gram a -> Gram a

isNaN :: Gram a -> Bool

isInfinite :: Gram a -> Bool

isDenormalized :: Gram a -> Bool

isNegativeZero :: Gram a -> Bool

isIEEE :: Gram a -> Bool

atan2 :: Gram a -> Gram a -> Gram a

Num a => Num (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Gram a -> Gram a -> Gram a

(-) :: Gram a -> Gram a -> Gram a

(*) :: Gram a -> Gram a -> Gram a

negate :: Gram a -> Gram a

abs :: Gram a -> Gram a

signum :: Gram a -> Gram a

fromInteger :: Integer -> Gram a

Fractional a => Fractional (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Gram a -> Gram a -> Gram a

recip :: Gram a -> Gram a

fromRational :: Rational -> Gram a

Real a => Real (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Gram a -> Rational

RealFrac a => RealFrac (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Gram a -> (b, Gram a)

truncate :: Integral b => Gram a -> b

round :: Integral b => Gram a -> b

ceiling :: Integral b => Gram a -> b

floor :: Integral b => Gram a -> b

Show a => Show (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Gram a -> ShowS

show :: Gram a -> String

showList :: [Gram a] -> ShowS

Eq a => Eq (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Gram a -> Gram a -> Bool

(/=) :: Gram a -> Gram a -> Bool

Ord a => Ord (Gram a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Gram a -> Gram a -> Ordering

(<) :: Gram a -> Gram a -> Bool

(<=) :: Gram a -> Gram a -> Bool

(>) :: Gram a -> Gram a -> Bool

(>=) :: Gram a -> Gram a -> Bool

max :: Gram a -> Gram a -> Gram a

min :: Gram a -> Gram a -> Gram a

type DimOf Gram Source # 
Instance details

Defined in Data.Units.SI.System

type DimOf Gram = Mass
type ShowUnitType Gram Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Gram = 'Text "g"

newtype Length a Source #

The length dimension, denotated L in SI.

This may contain a length quantity with unspecified unit.

Constructors

Length a 

Instances

Instances details
IsDim Length Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit Length 
Instance details

Defined in Data.Units.SI.System

ShowDim Length Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType Length 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Length = 'Text "L"

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Length a

exp :: Length a -> Length a

log :: Length a -> Length a

sqrt :: Length a -> Length a

(**) :: Length a -> Length a -> Length a

logBase :: Length a -> Length a -> Length a

sin :: Length a -> Length a

cos :: Length a -> Length a

tan :: Length a -> Length a

asin :: Length a -> Length a

acos :: Length a -> Length a

atan :: Length a -> Length a

sinh :: Length a -> Length a

cosh :: Length a -> Length a

tanh :: Length a -> Length a

asinh :: Length a -> Length a

acosh :: Length a -> Length a

atanh :: Length a -> Length a

log1p :: Length a -> Length a

expm1 :: Length a -> Length a

log1pexp :: Length a -> Length a

log1mexp :: Length a -> Length a

RealFloat a => RealFloat (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Length a -> Integer

floatDigits :: Length a -> Int

floatRange :: Length a -> (Int, Int)

decodeFloat :: Length a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Length a

exponent :: Length a -> Int

significand :: Length a -> Length a

scaleFloat :: Int -> Length a -> Length a

isNaN :: Length a -> Bool

isInfinite :: Length a -> Bool

isDenormalized :: Length a -> Bool

isNegativeZero :: Length a -> Bool

isIEEE :: Length a -> Bool

atan2 :: Length a -> Length a -> Length a

Num a => Num (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Length a -> Length a -> Length a

(-) :: Length a -> Length a -> Length a

(*) :: Length a -> Length a -> Length a

negate :: Length a -> Length a

abs :: Length a -> Length a

signum :: Length a -> Length a

fromInteger :: Integer -> Length a

Fractional a => Fractional (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Length a -> Length a -> Length a

recip :: Length a -> Length a

fromRational :: Rational -> Length a

Real a => Real (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Length a -> Rational

RealFrac a => RealFrac (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Length a -> (b, Length a)

truncate :: Integral b => Length a -> b

round :: Integral b => Length a -> b

ceiling :: Integral b => Length a -> b

floor :: Integral b => Length a -> b

Show a => Show (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Length a -> ShowS

show :: Length a -> String

showList :: [Length a] -> ShowS

Eq a => Eq (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Length a -> Length a -> Bool

(/=) :: Length a -> Length a -> Bool

Ord a => Ord (Length a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Length a -> Length a -> Ordering

(<) :: Length a -> Length a -> Bool

(<=) :: Length a -> Length a -> Bool

(>) :: Length a -> Length a -> Bool

(>=) :: Length a -> Length a -> Bool

max :: Length a -> Length a -> Length a

min :: Length a -> Length a -> Length a

type DimId Length Source # 
Instance details

Defined in Data.Units.SI.System

type DimId Length = 'Pos 3000
type DimToUnit Length Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Length Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Length = 'Text "L"

newtype Meter a Source #

A quantity in meters, denotated m in SI.

This is the base unit of the length dimension in the SI system.

Constructors

Meter a 

Instances

Instances details
IsUnit Meter Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Meter 
Instance details

Defined in Data.Units.SI.System

ShowUnit Meter Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Meter 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Meter = 'Text "m"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Meter a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Meter a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Meter a

exp :: Meter a -> Meter a

log :: Meter a -> Meter a

sqrt :: Meter a -> Meter a

(**) :: Meter a -> Meter a -> Meter a

logBase :: Meter a -> Meter a -> Meter a

sin :: Meter a -> Meter a

cos :: Meter a -> Meter a

tan :: Meter a -> Meter a

asin :: Meter a -> Meter a

acos :: Meter a -> Meter a

atan :: Meter a -> Meter a

sinh :: Meter a -> Meter a

cosh :: Meter a -> Meter a

tanh :: Meter a -> Meter a

asinh :: Meter a -> Meter a

acosh :: Meter a -> Meter a

atanh :: Meter a -> Meter a

log1p :: Meter a -> Meter a

expm1 :: Meter a -> Meter a

log1pexp :: Meter a -> Meter a

log1mexp :: Meter a -> Meter a

RealFloat a => RealFloat (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Meter a -> Integer

floatDigits :: Meter a -> Int

floatRange :: Meter a -> (Int, Int)

decodeFloat :: Meter a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Meter a

exponent :: Meter a -> Int

significand :: Meter a -> Meter a

scaleFloat :: Int -> Meter a -> Meter a

isNaN :: Meter a -> Bool

isInfinite :: Meter a -> Bool

isDenormalized :: Meter a -> Bool

isNegativeZero :: Meter a -> Bool

isIEEE :: Meter a -> Bool

atan2 :: Meter a -> Meter a -> Meter a

Num a => Num (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Meter a -> Meter a -> Meter a

(-) :: Meter a -> Meter a -> Meter a

(*) :: Meter a -> Meter a -> Meter a

negate :: Meter a -> Meter a

abs :: Meter a -> Meter a

signum :: Meter a -> Meter a

fromInteger :: Integer -> Meter a

Fractional a => Fractional (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Meter a -> Meter a -> Meter a

recip :: Meter a -> Meter a

fromRational :: Rational -> Meter a

Real a => Real (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Meter a -> Rational

RealFrac a => RealFrac (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Meter a -> (b, Meter a)

truncate :: Integral b => Meter a -> b

round :: Integral b => Meter a -> b

ceiling :: Integral b => Meter a -> b

floor :: Integral b => Meter a -> b

Show a => Show (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Meter a -> ShowS

show :: Meter a -> String

showList :: [Meter a] -> ShowS

Eq a => Eq (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Meter a -> Meter a -> Bool

(/=) :: Meter a -> Meter a -> Bool

Ord a => Ord (Meter a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Meter a -> Meter a -> Ordering

(<) :: Meter a -> Meter a -> Bool

(<=) :: Meter a -> Meter a -> Bool

(>) :: Meter a -> Meter a -> Bool

(>=) :: Meter a -> Meter a -> Bool

max :: Meter a -> Meter a -> Meter a

min :: Meter a -> Meter a -> Meter a

type DimOf Meter Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Meter Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Meter = 'Text "m"

newtype Time a Source #

The time dimension, denotated T in SI.

This may contain a length quantity with unspecified unit.

Constructors

Time a 

Instances

Instances details
IsDim Time Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit Time 
Instance details

Defined in Data.Units.SI.System

ShowDim Time Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType Time 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Time = 'Text "T"

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Time a

exp :: Time a -> Time a

log :: Time a -> Time a

sqrt :: Time a -> Time a

(**) :: Time a -> Time a -> Time a

logBase :: Time a -> Time a -> Time a

sin :: Time a -> Time a

cos :: Time a -> Time a

tan :: Time a -> Time a

asin :: Time a -> Time a

acos :: Time a -> Time a

atan :: Time a -> Time a

sinh :: Time a -> Time a

cosh :: Time a -> Time a

tanh :: Time a -> Time a

asinh :: Time a -> Time a

acosh :: Time a -> Time a

atanh :: Time a -> Time a

log1p :: Time a -> Time a

expm1 :: Time a -> Time a

log1pexp :: Time a -> Time a

log1mexp :: Time a -> Time a

RealFloat a => RealFloat (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Time a -> Integer

floatDigits :: Time a -> Int

floatRange :: Time a -> (Int, Int)

decodeFloat :: Time a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Time a

exponent :: Time a -> Int

significand :: Time a -> Time a

scaleFloat :: Int -> Time a -> Time a

isNaN :: Time a -> Bool

isInfinite :: Time a -> Bool

isDenormalized :: Time a -> Bool

isNegativeZero :: Time a -> Bool

isIEEE :: Time a -> Bool

atan2 :: Time a -> Time a -> Time a

Num a => Num (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Time a -> Time a -> Time a

(-) :: Time a -> Time a -> Time a

(*) :: Time a -> Time a -> Time a

negate :: Time a -> Time a

abs :: Time a -> Time a

signum :: Time a -> Time a

fromInteger :: Integer -> Time a

Fractional a => Fractional (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Time a -> Time a -> Time a

recip :: Time a -> Time a

fromRational :: Rational -> Time a

Real a => Real (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Time a -> Rational

RealFrac a => RealFrac (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Time a -> (b, Time a)

truncate :: Integral b => Time a -> b

round :: Integral b => Time a -> b

ceiling :: Integral b => Time a -> b

floor :: Integral b => Time a -> b

Show a => Show (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Time a -> ShowS

show :: Time a -> String

showList :: [Time a] -> ShowS

Eq a => Eq (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Time a -> Time a -> Bool

(/=) :: Time a -> Time a -> Bool

Ord a => Ord (Time a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Time a -> Time a -> Ordering

(<) :: Time a -> Time a -> Bool

(<=) :: Time a -> Time a -> Bool

(>) :: Time a -> Time a -> Bool

(>=) :: Time a -> Time a -> Bool

max :: Time a -> Time a -> Time a

min :: Time a -> Time a -> Time a

type DimId Time Source # 
Instance details

Defined in Data.Units.SI.System

type DimId Time = 'Pos 4000
type DimToUnit Time Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Time Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Time = 'Text "T"

newtype Second a Source #

A quantity in seconds, denotated s in SI.

This is the base unit of the time dimension in the SI system.

Constructors

Second a 

Instances

Instances details
IsUnit Second Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Second 
Instance details

Defined in Data.Units.SI.System

ShowUnit Second Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Second 
Instance details

Defined in Data.Units.SI.System

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Second a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Second a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Second a

exp :: Second a -> Second a

log :: Second a -> Second a

sqrt :: Second a -> Second a

(**) :: Second a -> Second a -> Second a

logBase :: Second a -> Second a -> Second a

sin :: Second a -> Second a

cos :: Second a -> Second a

tan :: Second a -> Second a

asin :: Second a -> Second a

acos :: Second a -> Second a

atan :: Second a -> Second a

sinh :: Second a -> Second a

cosh :: Second a -> Second a

tanh :: Second a -> Second a

asinh :: Second a -> Second a

acosh :: Second a -> Second a

atanh :: Second a -> Second a

log1p :: Second a -> Second a

expm1 :: Second a -> Second a

log1pexp :: Second a -> Second a

log1mexp :: Second a -> Second a

RealFloat a => RealFloat (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Second a -> Integer

floatDigits :: Second a -> Int

floatRange :: Second a -> (Int, Int)

decodeFloat :: Second a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Second a

exponent :: Second a -> Int

significand :: Second a -> Second a

scaleFloat :: Int -> Second a -> Second a

isNaN :: Second a -> Bool

isInfinite :: Second a -> Bool

isDenormalized :: Second a -> Bool

isNegativeZero :: Second a -> Bool

isIEEE :: Second a -> Bool

atan2 :: Second a -> Second a -> Second a

Num a => Num (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Second a -> Second a -> Second a

(-) :: Second a -> Second a -> Second a

(*) :: Second a -> Second a -> Second a

negate :: Second a -> Second a

abs :: Second a -> Second a

signum :: Second a -> Second a

fromInteger :: Integer -> Second a

Fractional a => Fractional (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Second a -> Second a -> Second a

recip :: Second a -> Second a

fromRational :: Rational -> Second a

Real a => Real (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Second a -> Rational

RealFrac a => RealFrac (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Second a -> (b, Second a)

truncate :: Integral b => Second a -> b

round :: Integral b => Second a -> b

ceiling :: Integral b => Second a -> b

floor :: Integral b => Second a -> b

Show a => Show (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Second a -> ShowS

show :: Second a -> String

showList :: [Second a] -> ShowS

Eq a => Eq (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Second a -> Second a -> Bool

(/=) :: Second a -> Second a -> Bool

Ord a => Ord (Second a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Second a -> Second a -> Ordering

(<) :: Second a -> Second a -> Bool

(<=) :: Second a -> Second a -> Bool

(>) :: Second a -> Second a -> Bool

(>=) :: Second a -> Second a -> Bool

max :: Second a -> Second a -> Second a

min :: Second a -> Second a -> Second a

type DimOf Second Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Second Source # 
Instance details

Defined in Data.Units.SI.System

newtype Temperature a Source #

The thermodynamic temperature dimension, denotated Θ in SI.

This may contain a temperature quantity with unspecified unit.

Constructors

Temperature a 

Instances

Instances details
IsDim Temperature Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit Temperature 
Instance details

Defined in Data.Units.SI.System

ShowDim Temperature Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType Temperature 
Instance details

Defined in Data.Units.SI.System

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

RealFloat a => RealFloat (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Temperature a -> Integer

floatDigits :: Temperature a -> Int

floatRange :: Temperature a -> (Int, Int)

decodeFloat :: Temperature a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Temperature a

exponent :: Temperature a -> Int

significand :: Temperature a -> Temperature a

scaleFloat :: Int -> Temperature a -> Temperature a

isNaN :: Temperature a -> Bool

isInfinite :: Temperature a -> Bool

isDenormalized :: Temperature a -> Bool

isNegativeZero :: Temperature a -> Bool

isIEEE :: Temperature a -> Bool

atan2 :: Temperature a -> Temperature a -> Temperature a

Num a => Num (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Fractional a => Fractional (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Real a => Real (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Temperature a -> Rational

RealFrac a => RealFrac (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Temperature a -> (b, Temperature a)

truncate :: Integral b => Temperature a -> b

round :: Integral b => Temperature a -> b

ceiling :: Integral b => Temperature a -> b

floor :: Integral b => Temperature a -> b

Show a => Show (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Temperature a -> ShowS

show :: Temperature a -> String

showList :: [Temperature a] -> ShowS

Eq a => Eq (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Temperature a -> Temperature a -> Bool

(/=) :: Temperature a -> Temperature a -> Bool

Ord a => Ord (Temperature a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Temperature a -> Temperature a -> Ordering

(<) :: Temperature a -> Temperature a -> Bool

(<=) :: Temperature a -> Temperature a -> Bool

(>) :: Temperature a -> Temperature a -> Bool

(>=) :: Temperature a -> Temperature a -> Bool

max :: Temperature a -> Temperature a -> Temperature a

min :: Temperature a -> Temperature a -> Temperature a

type DimId Temperature Source # 
Instance details

Defined in Data.Units.SI.System

type DimId Temperature = 'Pos 6000
type DimToUnit Temperature Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Temperature Source # 
Instance details

Defined in Data.Units.SI.System

newtype Kelvin a Source #

A quantity in Kelvin, denotated K in SI.

This is the base unit of the thermodynamic temperature dimension in the SI system.

Constructors

Kelvin a 

Instances

Instances details
IsUnit Kelvin Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Kelvin 
Instance details

Defined in Data.Units.SI.System

ShowUnit Kelvin Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Kelvin 
Instance details

Defined in Data.Units.SI.System

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Kelvin a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Kelvin a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Kelvin a

exp :: Kelvin a -> Kelvin a

log :: Kelvin a -> Kelvin a

sqrt :: Kelvin a -> Kelvin a

(**) :: Kelvin a -> Kelvin a -> Kelvin a

logBase :: Kelvin a -> Kelvin a -> Kelvin a

sin :: Kelvin a -> Kelvin a

cos :: Kelvin a -> Kelvin a

tan :: Kelvin a -> Kelvin a

asin :: Kelvin a -> Kelvin a

acos :: Kelvin a -> Kelvin a

atan :: Kelvin a -> Kelvin a

sinh :: Kelvin a -> Kelvin a

cosh :: Kelvin a -> Kelvin a

tanh :: Kelvin a -> Kelvin a

asinh :: Kelvin a -> Kelvin a

acosh :: Kelvin a -> Kelvin a

atanh :: Kelvin a -> Kelvin a

log1p :: Kelvin a -> Kelvin a

expm1 :: Kelvin a -> Kelvin a

log1pexp :: Kelvin a -> Kelvin a

log1mexp :: Kelvin a -> Kelvin a

RealFloat a => RealFloat (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Kelvin a -> Integer

floatDigits :: Kelvin a -> Int

floatRange :: Kelvin a -> (Int, Int)

decodeFloat :: Kelvin a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Kelvin a

exponent :: Kelvin a -> Int

significand :: Kelvin a -> Kelvin a

scaleFloat :: Int -> Kelvin a -> Kelvin a

isNaN :: Kelvin a -> Bool

isInfinite :: Kelvin a -> Bool

isDenormalized :: Kelvin a -> Bool

isNegativeZero :: Kelvin a -> Bool

isIEEE :: Kelvin a -> Bool

atan2 :: Kelvin a -> Kelvin a -> Kelvin a

Num a => Num (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Kelvin a -> Kelvin a -> Kelvin a

(-) :: Kelvin a -> Kelvin a -> Kelvin a

(*) :: Kelvin a -> Kelvin a -> Kelvin a

negate :: Kelvin a -> Kelvin a

abs :: Kelvin a -> Kelvin a

signum :: Kelvin a -> Kelvin a

fromInteger :: Integer -> Kelvin a

Fractional a => Fractional (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Kelvin a -> Kelvin a -> Kelvin a

recip :: Kelvin a -> Kelvin a

fromRational :: Rational -> Kelvin a

Real a => Real (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Kelvin a -> Rational

RealFrac a => RealFrac (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Kelvin a -> (b, Kelvin a)

truncate :: Integral b => Kelvin a -> b

round :: Integral b => Kelvin a -> b

ceiling :: Integral b => Kelvin a -> b

floor :: Integral b => Kelvin a -> b

Show a => Show (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Kelvin a -> ShowS

show :: Kelvin a -> String

showList :: [Kelvin a] -> ShowS

Eq a => Eq (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Kelvin a -> Kelvin a -> Bool

(/=) :: Kelvin a -> Kelvin a -> Bool

Ord a => Ord (Kelvin a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Kelvin a -> Kelvin a -> Ordering

(<) :: Kelvin a -> Kelvin a -> Bool

(<=) :: Kelvin a -> Kelvin a -> Bool

(>) :: Kelvin a -> Kelvin a -> Bool

(>=) :: Kelvin a -> Kelvin a -> Bool

max :: Kelvin a -> Kelvin a -> Kelvin a

min :: Kelvin a -> Kelvin a -> Kelvin a

type DimOf Kelvin Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Kelvin Source # 
Instance details

Defined in Data.Units.SI.System

newtype AmountOfSubstance a Source #

The amount of substance dimension, denotated N in SI.

This may contain an amount of substance quantity with unspecified unit.

Constructors

AmountOfSubstance a 

Instances

Instances details
IsDim AmountOfSubstance Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit AmountOfSubstance 
Instance details

Defined in Data.Units.SI.System

ShowDim AmountOfSubstance Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType AmountOfSubstance 
Instance details

Defined in Data.Units.SI.System

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

RealFloat a => RealFloat (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Num a => Num (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Fractional a => Fractional (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Real a => Real (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: AmountOfSubstance a -> Rational

RealFrac a => RealFrac (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => AmountOfSubstance a -> (b, AmountOfSubstance a)

truncate :: Integral b => AmountOfSubstance a -> b

round :: Integral b => AmountOfSubstance a -> b

ceiling :: Integral b => AmountOfSubstance a -> b

floor :: Integral b => AmountOfSubstance a -> b

Show a => Show (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> AmountOfSubstance a -> ShowS

show :: AmountOfSubstance a -> String

showList :: [AmountOfSubstance a] -> ShowS

Eq a => Eq (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

Ord a => Ord (AmountOfSubstance a) Source # 
Instance details

Defined in Data.Units.SI.System

type DimId AmountOfSubstance Source # 
Instance details

Defined in Data.Units.SI.System

type DimToUnit AmountOfSubstance Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType AmountOfSubstance Source # 
Instance details

Defined in Data.Units.SI.System

newtype Mole a Source #

A quantity in moles, denotated mol in SI.

This is the base unit of the amount of substance dimension in the SI system.

Constructors

Mole a 

Instances

Instances details
IsUnit Mole Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Mole 
Instance details

Defined in Data.Units.SI.System

ShowUnit Mole Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Mole 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Mole = 'Text "mol"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Mole a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Mole a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Mole a

exp :: Mole a -> Mole a

log :: Mole a -> Mole a

sqrt :: Mole a -> Mole a

(**) :: Mole a -> Mole a -> Mole a

logBase :: Mole a -> Mole a -> Mole a

sin :: Mole a -> Mole a

cos :: Mole a -> Mole a

tan :: Mole a -> Mole a

asin :: Mole a -> Mole a

acos :: Mole a -> Mole a

atan :: Mole a -> Mole a

sinh :: Mole a -> Mole a

cosh :: Mole a -> Mole a

tanh :: Mole a -> Mole a

asinh :: Mole a -> Mole a

acosh :: Mole a -> Mole a

atanh :: Mole a -> Mole a

log1p :: Mole a -> Mole a

expm1 :: Mole a -> Mole a

log1pexp :: Mole a -> Mole a

log1mexp :: Mole a -> Mole a

RealFloat a => RealFloat (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Mole a -> Integer

floatDigits :: Mole a -> Int

floatRange :: Mole a -> (Int, Int)

decodeFloat :: Mole a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Mole a

exponent :: Mole a -> Int

significand :: Mole a -> Mole a

scaleFloat :: Int -> Mole a -> Mole a

isNaN :: Mole a -> Bool

isInfinite :: Mole a -> Bool

isDenormalized :: Mole a -> Bool

isNegativeZero :: Mole a -> Bool

isIEEE :: Mole a -> Bool

atan2 :: Mole a -> Mole a -> Mole a

Num a => Num (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Mole a -> Mole a -> Mole a

(-) :: Mole a -> Mole a -> Mole a

(*) :: Mole a -> Mole a -> Mole a

negate :: Mole a -> Mole a

abs :: Mole a -> Mole a

signum :: Mole a -> Mole a

fromInteger :: Integer -> Mole a

Fractional a => Fractional (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Mole a -> Mole a -> Mole a

recip :: Mole a -> Mole a

fromRational :: Rational -> Mole a

Real a => Real (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Mole a -> Rational

RealFrac a => RealFrac (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Mole a -> (b, Mole a)

truncate :: Integral b => Mole a -> b

round :: Integral b => Mole a -> b

ceiling :: Integral b => Mole a -> b

floor :: Integral b => Mole a -> b

Show a => Show (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Mole a -> ShowS

show :: Mole a -> String

showList :: [Mole a] -> ShowS

Eq a => Eq (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Mole a -> Mole a -> Bool

(/=) :: Mole a -> Mole a -> Bool

Ord a => Ord (Mole a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Mole a -> Mole a -> Ordering

(<) :: Mole a -> Mole a -> Bool

(<=) :: Mole a -> Mole a -> Bool

(>) :: Mole a -> Mole a -> Bool

(>=) :: Mole a -> Mole a -> Bool

max :: Mole a -> Mole a -> Mole a

min :: Mole a -> Mole a -> Mole a

type DimOf Mole Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Mole Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Mole = 'Text "mol"

newtype Current a Source #

The electric current dimension, denotated I in SI.

This may contain an electric current quantity with unspecified unit.

Constructors

Current a 

Instances

Instances details
IsDim Current Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit Current 
Instance details

Defined in Data.Units.SI.System

ShowDim Current Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType Current 
Instance details

Defined in Data.Units.SI.System

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Current a

exp :: Current a -> Current a

log :: Current a -> Current a

sqrt :: Current a -> Current a

(**) :: Current a -> Current a -> Current a

logBase :: Current a -> Current a -> Current a

sin :: Current a -> Current a

cos :: Current a -> Current a

tan :: Current a -> Current a

asin :: Current a -> Current a

acos :: Current a -> Current a

atan :: Current a -> Current a

sinh :: Current a -> Current a

cosh :: Current a -> Current a

tanh :: Current a -> Current a

asinh :: Current a -> Current a

acosh :: Current a -> Current a

atanh :: Current a -> Current a

log1p :: Current a -> Current a

expm1 :: Current a -> Current a

log1pexp :: Current a -> Current a

log1mexp :: Current a -> Current a

RealFloat a => RealFloat (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Current a -> Integer

floatDigits :: Current a -> Int

floatRange :: Current a -> (Int, Int)

decodeFloat :: Current a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Current a

exponent :: Current a -> Int

significand :: Current a -> Current a

scaleFloat :: Int -> Current a -> Current a

isNaN :: Current a -> Bool

isInfinite :: Current a -> Bool

isDenormalized :: Current a -> Bool

isNegativeZero :: Current a -> Bool

isIEEE :: Current a -> Bool

atan2 :: Current a -> Current a -> Current a

Num a => Num (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Current a -> Current a -> Current a

(-) :: Current a -> Current a -> Current a

(*) :: Current a -> Current a -> Current a

negate :: Current a -> Current a

abs :: Current a -> Current a

signum :: Current a -> Current a

fromInteger :: Integer -> Current a

Fractional a => Fractional (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Current a -> Current a -> Current a

recip :: Current a -> Current a

fromRational :: Rational -> Current a

Real a => Real (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Current a -> Rational

RealFrac a => RealFrac (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Current a -> (b, Current a)

truncate :: Integral b => Current a -> b

round :: Integral b => Current a -> b

ceiling :: Integral b => Current a -> b

floor :: Integral b => Current a -> b

Show a => Show (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Current a -> ShowS

show :: Current a -> String

showList :: [Current a] -> ShowS

Eq a => Eq (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Current a -> Current a -> Bool

(/=) :: Current a -> Current a -> Bool

Ord a => Ord (Current a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Current a -> Current a -> Ordering

(<) :: Current a -> Current a -> Bool

(<=) :: Current a -> Current a -> Bool

(>) :: Current a -> Current a -> Bool

(>=) :: Current a -> Current a -> Bool

max :: Current a -> Current a -> Current a

min :: Current a -> Current a -> Current a

type DimId Current Source # 
Instance details

Defined in Data.Units.SI.System

type DimId Current = 'Pos 5000
type DimToUnit Current Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType Current Source # 
Instance details

Defined in Data.Units.SI.System

newtype Ampere a Source #

A quantity in amperes, denotated A in SI.

This is the base unit of the electric current dimension in the SI system.

Constructors

Ampere a 

Instances

Instances details
IsUnit Ampere Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Ampere 
Instance details

Defined in Data.Units.SI.System

ShowUnit Ampere Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Ampere 
Instance details

Defined in Data.Units.SI.System

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Ampere a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Ampere a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Ampere a

exp :: Ampere a -> Ampere a

log :: Ampere a -> Ampere a

sqrt :: Ampere a -> Ampere a

(**) :: Ampere a -> Ampere a -> Ampere a

logBase :: Ampere a -> Ampere a -> Ampere a

sin :: Ampere a -> Ampere a

cos :: Ampere a -> Ampere a

tan :: Ampere a -> Ampere a

asin :: Ampere a -> Ampere a

acos :: Ampere a -> Ampere a

atan :: Ampere a -> Ampere a

sinh :: Ampere a -> Ampere a

cosh :: Ampere a -> Ampere a

tanh :: Ampere a -> Ampere a

asinh :: Ampere a -> Ampere a

acosh :: Ampere a -> Ampere a

atanh :: Ampere a -> Ampere a

log1p :: Ampere a -> Ampere a

expm1 :: Ampere a -> Ampere a

log1pexp :: Ampere a -> Ampere a

log1mexp :: Ampere a -> Ampere a

RealFloat a => RealFloat (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Ampere a -> Integer

floatDigits :: Ampere a -> Int

floatRange :: Ampere a -> (Int, Int)

decodeFloat :: Ampere a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Ampere a

exponent :: Ampere a -> Int

significand :: Ampere a -> Ampere a

scaleFloat :: Int -> Ampere a -> Ampere a

isNaN :: Ampere a -> Bool

isInfinite :: Ampere a -> Bool

isDenormalized :: Ampere a -> Bool

isNegativeZero :: Ampere a -> Bool

isIEEE :: Ampere a -> Bool

atan2 :: Ampere a -> Ampere a -> Ampere a

Num a => Num (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Ampere a -> Ampere a -> Ampere a

(-) :: Ampere a -> Ampere a -> Ampere a

(*) :: Ampere a -> Ampere a -> Ampere a

negate :: Ampere a -> Ampere a

abs :: Ampere a -> Ampere a

signum :: Ampere a -> Ampere a

fromInteger :: Integer -> Ampere a

Fractional a => Fractional (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Ampere a -> Ampere a -> Ampere a

recip :: Ampere a -> Ampere a

fromRational :: Rational -> Ampere a

Real a => Real (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Ampere a -> Rational

RealFrac a => RealFrac (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Ampere a -> (b, Ampere a)

truncate :: Integral b => Ampere a -> b

round :: Integral b => Ampere a -> b

ceiling :: Integral b => Ampere a -> b

floor :: Integral b => Ampere a -> b

Show a => Show (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Ampere a -> ShowS

show :: Ampere a -> String

showList :: [Ampere a] -> ShowS

Eq a => Eq (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Ampere a -> Ampere a -> Bool

(/=) :: Ampere a -> Ampere a -> Bool

Ord a => Ord (Ampere a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Ampere a -> Ampere a -> Ordering

(<) :: Ampere a -> Ampere a -> Bool

(<=) :: Ampere a -> Ampere a -> Bool

(>) :: Ampere a -> Ampere a -> Bool

(>=) :: Ampere a -> Ampere a -> Bool

max :: Ampere a -> Ampere a -> Ampere a

min :: Ampere a -> Ampere a -> Ampere a

type DimOf Ampere Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Ampere Source # 
Instance details

Defined in Data.Units.SI.System

newtype LuminousIntensity a Source #

The luminous intensity dimension, denotated J in SI.

This may contain a luminous intensity quantity with unspecified unit.

Constructors

LuminousIntensity a 

Instances

Instances details
IsDim LuminousIntensity Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimToUnit LuminousIntensity 
Instance details

Defined in Data.Units.SI.System

ShowDim LuminousIntensity Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowDimType LuminousIntensity 
Instance details

Defined in Data.Units.SI.System

Methods

showsDimPrec :: Int -> ShowS Source #

showDim :: String Source #

prettysDimPrec :: Int -> ShowS Source #

prettyDim :: String Source #

Floating a => Floating (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

RealFloat a => RealFloat (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Num a => Num (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Fractional a => Fractional (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Real a => Real (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: LuminousIntensity a -> Rational

RealFrac a => RealFrac (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => LuminousIntensity a -> (b, LuminousIntensity a)

truncate :: Integral b => LuminousIntensity a -> b

round :: Integral b => LuminousIntensity a -> b

ceiling :: Integral b => LuminousIntensity a -> b

floor :: Integral b => LuminousIntensity a -> b

Show a => Show (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> LuminousIntensity a -> ShowS

show :: LuminousIntensity a -> String

showList :: [LuminousIntensity a] -> ShowS

Eq a => Eq (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

Ord a => Ord (LuminousIntensity a) Source # 
Instance details

Defined in Data.Units.SI.System

type DimId LuminousIntensity Source # 
Instance details

Defined in Data.Units.SI.System

type DimToUnit LuminousIntensity Source # 
Instance details

Defined in Data.Units.SI.System

type ShowDimType LuminousIntensity Source # 
Instance details

Defined in Data.Units.SI.System

newtype Candela a Source #

A quantity in candelas, denotated cd in SI.

This is the base unit of the luminous intensity dimension in the SI system.

Constructors

Candela a 

Instances

Instances details
IsUnit Candela Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type DimOf Candela 
Instance details

Defined in Data.Units.SI.System

ShowUnit Candela Source # 
Instance details

Defined in Data.Units.SI.System

Associated Types

type ShowUnitType Candela 
Instance details

Defined in Data.Units.SI.System

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Candela a Source # 
Instance details

Defined in Data.Units.SI.System

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Candela a Source # 
Instance details

Defined in Data.Units.SI.System

Floating a => Floating (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

pi :: Candela a

exp :: Candela a -> Candela a

log :: Candela a -> Candela a

sqrt :: Candela a -> Candela a

(**) :: Candela a -> Candela a -> Candela a

logBase :: Candela a -> Candela a -> Candela a

sin :: Candela a -> Candela a

cos :: Candela a -> Candela a

tan :: Candela a -> Candela a

asin :: Candela a -> Candela a

acos :: Candela a -> Candela a

atan :: Candela a -> Candela a

sinh :: Candela a -> Candela a

cosh :: Candela a -> Candela a

tanh :: Candela a -> Candela a

asinh :: Candela a -> Candela a

acosh :: Candela a -> Candela a

atanh :: Candela a -> Candela a

log1p :: Candela a -> Candela a

expm1 :: Candela a -> Candela a

log1pexp :: Candela a -> Candela a

log1mexp :: Candela a -> Candela a

RealFloat a => RealFloat (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

floatRadix :: Candela a -> Integer

floatDigits :: Candela a -> Int

floatRange :: Candela a -> (Int, Int)

decodeFloat :: Candela a -> (Integer, Int)

encodeFloat :: Integer -> Int -> Candela a

exponent :: Candela a -> Int

significand :: Candela a -> Candela a

scaleFloat :: Int -> Candela a -> Candela a

isNaN :: Candela a -> Bool

isInfinite :: Candela a -> Bool

isDenormalized :: Candela a -> Bool

isNegativeZero :: Candela a -> Bool

isIEEE :: Candela a -> Bool

atan2 :: Candela a -> Candela a -> Candela a

Num a => Num (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(+) :: Candela a -> Candela a -> Candela a

(-) :: Candela a -> Candela a -> Candela a

(*) :: Candela a -> Candela a -> Candela a

negate :: Candela a -> Candela a

abs :: Candela a -> Candela a

signum :: Candela a -> Candela a

fromInteger :: Integer -> Candela a

Fractional a => Fractional (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(/) :: Candela a -> Candela a -> Candela a

recip :: Candela a -> Candela a

fromRational :: Rational -> Candela a

Real a => Real (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

toRational :: Candela a -> Rational

RealFrac a => RealFrac (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

properFraction :: Integral b => Candela a -> (b, Candela a)

truncate :: Integral b => Candela a -> b

round :: Integral b => Candela a -> b

ceiling :: Integral b => Candela a -> b

floor :: Integral b => Candela a -> b

Show a => Show (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

showsPrec :: Int -> Candela a -> ShowS

show :: Candela a -> String

showList :: [Candela a] -> ShowS

Eq a => Eq (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

(==) :: Candela a -> Candela a -> Bool

(/=) :: Candela a -> Candela a -> Bool

Ord a => Ord (Candela a) Source # 
Instance details

Defined in Data.Units.SI.System

Methods

compare :: Candela a -> Candela a -> Ordering

(<) :: Candela a -> Candela a -> Bool

(<=) :: Candela a -> Candela a -> Bool

(>) :: Candela a -> Candela a -> Bool

(>=) :: Candela a -> Candela a -> Bool

max :: Candela a -> Candela a -> Candela a

min :: Candela a -> Candela a -> Candela a

type DimOf Candela Source # 
Instance details

Defined in Data.Units.SI.System

type ShowUnitType Candela Source # 
Instance details

Defined in Data.Units.SI.System