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.Derived.NonAngle

Description

Derived units and dimensions for the International System of Units that do not contain angles.

This follows the wikipedia page https://en.wikipedia.org/wiki/SI_derived_unit.

Synopsis

Official derived units from SI

newtype Celsius a Source #

Thermodynamic temperature in Celsius degrees

Constructors

Celsius a 

Instances

Instances details
IsUnit Celsius Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Celsius 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Celsius Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Celsius 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Celsius = 'Text "\176C"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Celsius a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Celsius a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Celsius a

exp :: Celsius a -> Celsius a

log :: Celsius a -> Celsius a

sqrt :: Celsius a -> Celsius a

(**) :: Celsius a -> Celsius a -> Celsius a

logBase :: Celsius a -> Celsius a -> Celsius a

sin :: Celsius a -> Celsius a

cos :: Celsius a -> Celsius a

tan :: Celsius a -> Celsius a

asin :: Celsius a -> Celsius a

acos :: Celsius a -> Celsius a

atan :: Celsius a -> Celsius a

sinh :: Celsius a -> Celsius a

cosh :: Celsius a -> Celsius a

tanh :: Celsius a -> Celsius a

asinh :: Celsius a -> Celsius a

acosh :: Celsius a -> Celsius a

atanh :: Celsius a -> Celsius a

log1p :: Celsius a -> Celsius a

expm1 :: Celsius a -> Celsius a

log1pexp :: Celsius a -> Celsius a

log1mexp :: Celsius a -> Celsius a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Celsius a -> Integer

floatDigits :: Celsius a -> Int

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

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

encodeFloat :: Integer -> Int -> Celsius a

exponent :: Celsius a -> Int

significand :: Celsius a -> Celsius a

scaleFloat :: Int -> Celsius a -> Celsius a

isNaN :: Celsius a -> Bool

isInfinite :: Celsius a -> Bool

isDenormalized :: Celsius a -> Bool

isNegativeZero :: Celsius a -> Bool

isIEEE :: Celsius a -> Bool

atan2 :: Celsius a -> Celsius a -> Celsius a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Celsius a -> Celsius a -> Celsius a

(-) :: Celsius a -> Celsius a -> Celsius a

(*) :: Celsius a -> Celsius a -> Celsius a

negate :: Celsius a -> Celsius a

abs :: Celsius a -> Celsius a

signum :: Celsius a -> Celsius a

fromInteger :: Integer -> Celsius a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Celsius a -> Celsius a -> Celsius a

recip :: Celsius a -> Celsius a

fromRational :: Rational -> Celsius a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Celsius a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Celsius a -> ShowS

show :: Celsius a -> String

showList :: [Celsius a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Celsius a -> Celsius a -> Ordering

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

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

(>) :: Celsius a -> Celsius a -> Bool

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

max :: Celsius a -> Celsius a -> Celsius a

min :: Celsius a -> Celsius a -> Celsius a

type DimOf Celsius Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Celsius Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Celsius = 'Text "\176C"

newtype Hertz a Source #

Frequency in hertz

Constructors

Hertz a 

Instances

Instances details
IsUnit Hertz Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Hertz 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Hertz Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Hertz 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Hertz = 'Text "Hz"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Hertz a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Hertz a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Hertz a

exp :: Hertz a -> Hertz a

log :: Hertz a -> Hertz a

sqrt :: Hertz a -> Hertz a

(**) :: Hertz a -> Hertz a -> Hertz a

logBase :: Hertz a -> Hertz a -> Hertz a

sin :: Hertz a -> Hertz a

cos :: Hertz a -> Hertz a

tan :: Hertz a -> Hertz a

asin :: Hertz a -> Hertz a

acos :: Hertz a -> Hertz a

atan :: Hertz a -> Hertz a

sinh :: Hertz a -> Hertz a

cosh :: Hertz a -> Hertz a

tanh :: Hertz a -> Hertz a

asinh :: Hertz a -> Hertz a

acosh :: Hertz a -> Hertz a

atanh :: Hertz a -> Hertz a

log1p :: Hertz a -> Hertz a

expm1 :: Hertz a -> Hertz a

log1pexp :: Hertz a -> Hertz a

log1mexp :: Hertz a -> Hertz a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Hertz a -> Integer

floatDigits :: Hertz a -> Int

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

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

encodeFloat :: Integer -> Int -> Hertz a

exponent :: Hertz a -> Int

significand :: Hertz a -> Hertz a

scaleFloat :: Int -> Hertz a -> Hertz a

isNaN :: Hertz a -> Bool

isInfinite :: Hertz a -> Bool

isDenormalized :: Hertz a -> Bool

isNegativeZero :: Hertz a -> Bool

isIEEE :: Hertz a -> Bool

atan2 :: Hertz a -> Hertz a -> Hertz a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Hertz a -> Hertz a -> Hertz a

(-) :: Hertz a -> Hertz a -> Hertz a

(*) :: Hertz a -> Hertz a -> Hertz a

negate :: Hertz a -> Hertz a

abs :: Hertz a -> Hertz a

signum :: Hertz a -> Hertz a

fromInteger :: Integer -> Hertz a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Hertz a -> Hertz a -> Hertz a

recip :: Hertz a -> Hertz a

fromRational :: Rational -> Hertz a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Hertz a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Hertz a -> ShowS

show :: Hertz a -> String

showList :: [Hertz a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Hertz a -> Hertz a -> Ordering

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

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

(>) :: Hertz a -> Hertz a -> Bool

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

max :: Hertz a -> Hertz a -> Hertz a

min :: Hertz a -> Hertz a -> Hertz a

type DimOf Hertz Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Hertz Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Hertz = 'Text "Hz"

newtype Becquerel a Source #

Radioactivity in becquerels

Constructors

Becquerel a 

Instances

Instances details
IsUnit Becquerel Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Becquerel 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Becquerel Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Becquerel 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Becquerel a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Becquerel a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Becquerel a -> Integer

floatDigits :: Becquerel a -> Int

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

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

encodeFloat :: Integer -> Int -> Becquerel a

exponent :: Becquerel a -> Int

significand :: Becquerel a -> Becquerel a

scaleFloat :: Int -> Becquerel a -> Becquerel a

isNaN :: Becquerel a -> Bool

isInfinite :: Becquerel a -> Bool

isDenormalized :: Becquerel a -> Bool

isNegativeZero :: Becquerel a -> Bool

isIEEE :: Becquerel a -> Bool

atan2 :: Becquerel a -> Becquerel a -> Becquerel a

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

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Becquerel a -> Becquerel a -> Becquerel a

recip :: Becquerel a -> Becquerel a

fromRational :: Rational -> Becquerel a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Becquerel a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Becquerel a -> ShowS

show :: Becquerel a -> String

showList :: [Becquerel a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Becquerel a -> Becquerel a -> Ordering

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

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

(>) :: Becquerel a -> Becquerel a -> Bool

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

max :: Becquerel a -> Becquerel a -> Becquerel a

min :: Becquerel a -> Becquerel a -> Becquerel a

type DimOf Becquerel Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Becquerel Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type Speed = NormalizeDim (Length ./. Time) Source #

Speed quantity. Equal to

Length .*. Time.^-1

type Force = NormalizeDim (Mass .*. Acceleration) Source #

Acceleration quantity. Equal to

Length .*. Time.^-2

newtype Newton a Source #

Force in newtons

Constructors

Newton a 

Instances

Instances details
IsUnit Newton Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Newton 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Newton Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Newton 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Newton a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Newton a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Newton a

exp :: Newton a -> Newton a

log :: Newton a -> Newton a

sqrt :: Newton a -> Newton a

(**) :: Newton a -> Newton a -> Newton a

logBase :: Newton a -> Newton a -> Newton a

sin :: Newton a -> Newton a

cos :: Newton a -> Newton a

tan :: Newton a -> Newton a

asin :: Newton a -> Newton a

acos :: Newton a -> Newton a

atan :: Newton a -> Newton a

sinh :: Newton a -> Newton a

cosh :: Newton a -> Newton a

tanh :: Newton a -> Newton a

asinh :: Newton a -> Newton a

acosh :: Newton a -> Newton a

atanh :: Newton a -> Newton a

log1p :: Newton a -> Newton a

expm1 :: Newton a -> Newton a

log1pexp :: Newton a -> Newton a

log1mexp :: Newton a -> Newton a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Newton a -> Integer

floatDigits :: Newton a -> Int

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

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

encodeFloat :: Integer -> Int -> Newton a

exponent :: Newton a -> Int

significand :: Newton a -> Newton a

scaleFloat :: Int -> Newton a -> Newton a

isNaN :: Newton a -> Bool

isInfinite :: Newton a -> Bool

isDenormalized :: Newton a -> Bool

isNegativeZero :: Newton a -> Bool

isIEEE :: Newton a -> Bool

atan2 :: Newton a -> Newton a -> Newton a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Newton a -> Newton a -> Newton a

(-) :: Newton a -> Newton a -> Newton a

(*) :: Newton a -> Newton a -> Newton a

negate :: Newton a -> Newton a

abs :: Newton a -> Newton a

signum :: Newton a -> Newton a

fromInteger :: Integer -> Newton a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Newton a -> Newton a -> Newton a

recip :: Newton a -> Newton a

fromRational :: Rational -> Newton a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Newton a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Newton a -> ShowS

show :: Newton a -> String

showList :: [Newton a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Newton a -> Newton a -> Ordering

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

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

(>) :: Newton a -> Newton a -> Bool

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

max :: Newton a -> Newton a -> Newton a

min :: Newton a -> Newton a -> Newton a

type DimOf Newton Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Newton Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type Pressure = NormalizeDim (Force ./. (Length .^+ 2)) Source #

Pressure quantity. Equal to

Mass .*. Length.^-1 .*. Time.^-2

newtype Pascal a Source #

Pressure in pascals

Constructors

Pascal a 

Instances

Instances details
IsUnit Pascal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Pascal 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Pascal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Pascal 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Pascal = 'Text "Pa"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Pascal a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Pascal a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Pascal a

exp :: Pascal a -> Pascal a

log :: Pascal a -> Pascal a

sqrt :: Pascal a -> Pascal a

(**) :: Pascal a -> Pascal a -> Pascal a

logBase :: Pascal a -> Pascal a -> Pascal a

sin :: Pascal a -> Pascal a

cos :: Pascal a -> Pascal a

tan :: Pascal a -> Pascal a

asin :: Pascal a -> Pascal a

acos :: Pascal a -> Pascal a

atan :: Pascal a -> Pascal a

sinh :: Pascal a -> Pascal a

cosh :: Pascal a -> Pascal a

tanh :: Pascal a -> Pascal a

asinh :: Pascal a -> Pascal a

acosh :: Pascal a -> Pascal a

atanh :: Pascal a -> Pascal a

log1p :: Pascal a -> Pascal a

expm1 :: Pascal a -> Pascal a

log1pexp :: Pascal a -> Pascal a

log1mexp :: Pascal a -> Pascal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Pascal a -> Integer

floatDigits :: Pascal a -> Int

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

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

encodeFloat :: Integer -> Int -> Pascal a

exponent :: Pascal a -> Int

significand :: Pascal a -> Pascal a

scaleFloat :: Int -> Pascal a -> Pascal a

isNaN :: Pascal a -> Bool

isInfinite :: Pascal a -> Bool

isDenormalized :: Pascal a -> Bool

isNegativeZero :: Pascal a -> Bool

isIEEE :: Pascal a -> Bool

atan2 :: Pascal a -> Pascal a -> Pascal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Pascal a -> Pascal a -> Pascal a

(-) :: Pascal a -> Pascal a -> Pascal a

(*) :: Pascal a -> Pascal a -> Pascal a

negate :: Pascal a -> Pascal a

abs :: Pascal a -> Pascal a

signum :: Pascal a -> Pascal a

fromInteger :: Integer -> Pascal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Pascal a -> Pascal a -> Pascal a

recip :: Pascal a -> Pascal a

fromRational :: Rational -> Pascal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Pascal a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Pascal a -> ShowS

show :: Pascal a -> String

showList :: [Pascal a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Pascal a -> Pascal a -> Ordering

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

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

(>) :: Pascal a -> Pascal a -> Bool

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

max :: Pascal a -> Pascal a -> Pascal a

min :: Pascal a -> Pascal a -> Pascal a

type DimOf Pascal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Pascal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Pascal = 'Text "Pa"

type Energy = NormalizeDim (Length .*. Force) Source #

Energy quantity. Equal to

 Mass .*. Length.^+2 .*. Time.^-2

newtype Joule a Source #

Energy in joules

Constructors

Joule a 

Instances

Instances details
IsUnit Joule Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Joule 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Joule Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Joule 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Joule = 'Text "J"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Joule a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Joule a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Joule a

exp :: Joule a -> Joule a

log :: Joule a -> Joule a

sqrt :: Joule a -> Joule a

(**) :: Joule a -> Joule a -> Joule a

logBase :: Joule a -> Joule a -> Joule a

sin :: Joule a -> Joule a

cos :: Joule a -> Joule a

tan :: Joule a -> Joule a

asin :: Joule a -> Joule a

acos :: Joule a -> Joule a

atan :: Joule a -> Joule a

sinh :: Joule a -> Joule a

cosh :: Joule a -> Joule a

tanh :: Joule a -> Joule a

asinh :: Joule a -> Joule a

acosh :: Joule a -> Joule a

atanh :: Joule a -> Joule a

log1p :: Joule a -> Joule a

expm1 :: Joule a -> Joule a

log1pexp :: Joule a -> Joule a

log1mexp :: Joule a -> Joule a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Joule a -> Integer

floatDigits :: Joule a -> Int

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

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

encodeFloat :: Integer -> Int -> Joule a

exponent :: Joule a -> Int

significand :: Joule a -> Joule a

scaleFloat :: Int -> Joule a -> Joule a

isNaN :: Joule a -> Bool

isInfinite :: Joule a -> Bool

isDenormalized :: Joule a -> Bool

isNegativeZero :: Joule a -> Bool

isIEEE :: Joule a -> Bool

atan2 :: Joule a -> Joule a -> Joule a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Joule a -> Joule a -> Joule a

(-) :: Joule a -> Joule a -> Joule a

(*) :: Joule a -> Joule a -> Joule a

negate :: Joule a -> Joule a

abs :: Joule a -> Joule a

signum :: Joule a -> Joule a

fromInteger :: Integer -> Joule a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Joule a -> Joule a -> Joule a

recip :: Joule a -> Joule a

fromRational :: Rational -> Joule a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Joule a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Joule a -> ShowS

show :: Joule a -> String

showList :: [Joule a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Joule a -> Joule a -> Ordering

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

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

(>) :: Joule a -> Joule a -> Bool

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

max :: Joule a -> Joule a -> Joule a

min :: Joule a -> Joule a -> Joule a

type DimOf Joule Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Joule Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Joule = 'Text "J"

type Power = NormalizeDim (Energy ./. Time) Source #

Power quantity. Equal to

 Mass .*. Length.^+2 .*. Time.^-3

newtype Watt a Source #

Power in watts

Constructors

Watt a 

Instances

Instances details
IsUnit Watt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Watt 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Watt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Watt 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Watt = 'Text "W"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Watt a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Watt a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Watt a

exp :: Watt a -> Watt a

log :: Watt a -> Watt a

sqrt :: Watt a -> Watt a

(**) :: Watt a -> Watt a -> Watt a

logBase :: Watt a -> Watt a -> Watt a

sin :: Watt a -> Watt a

cos :: Watt a -> Watt a

tan :: Watt a -> Watt a

asin :: Watt a -> Watt a

acos :: Watt a -> Watt a

atan :: Watt a -> Watt a

sinh :: Watt a -> Watt a

cosh :: Watt a -> Watt a

tanh :: Watt a -> Watt a

asinh :: Watt a -> Watt a

acosh :: Watt a -> Watt a

atanh :: Watt a -> Watt a

log1p :: Watt a -> Watt a

expm1 :: Watt a -> Watt a

log1pexp :: Watt a -> Watt a

log1mexp :: Watt a -> Watt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Watt a -> Integer

floatDigits :: Watt a -> Int

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

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

encodeFloat :: Integer -> Int -> Watt a

exponent :: Watt a -> Int

significand :: Watt a -> Watt a

scaleFloat :: Int -> Watt a -> Watt a

isNaN :: Watt a -> Bool

isInfinite :: Watt a -> Bool

isDenormalized :: Watt a -> Bool

isNegativeZero :: Watt a -> Bool

isIEEE :: Watt a -> Bool

atan2 :: Watt a -> Watt a -> Watt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Watt a -> Watt a -> Watt a

(-) :: Watt a -> Watt a -> Watt a

(*) :: Watt a -> Watt a -> Watt a

negate :: Watt a -> Watt a

abs :: Watt a -> Watt a

signum :: Watt a -> Watt a

fromInteger :: Integer -> Watt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Watt a -> Watt a -> Watt a

recip :: Watt a -> Watt a

fromRational :: Rational -> Watt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Watt a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Watt a -> ShowS

show :: Watt a -> String

showList :: [Watt a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Watt a -> Watt a -> Ordering

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

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

(>) :: Watt a -> Watt a -> Bool

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

max :: Watt a -> Watt a -> Watt a

min :: Watt a -> Watt a -> Watt a

type DimOf Watt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Watt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Watt = 'Text "W"

type ElectricCharge = NormalizeDim (Time .*. Current) Source #

Electric charge quantity. Equal to

 Time .*. Current

newtype Coulomb a Source #

Constructors

Coulomb a 

Instances

Instances details
IsUnit Coulomb Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Coulomb 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Coulomb Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Coulomb 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Coulomb a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Coulomb a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Coulomb a

exp :: Coulomb a -> Coulomb a

log :: Coulomb a -> Coulomb a

sqrt :: Coulomb a -> Coulomb a

(**) :: Coulomb a -> Coulomb a -> Coulomb a

logBase :: Coulomb a -> Coulomb a -> Coulomb a

sin :: Coulomb a -> Coulomb a

cos :: Coulomb a -> Coulomb a

tan :: Coulomb a -> Coulomb a

asin :: Coulomb a -> Coulomb a

acos :: Coulomb a -> Coulomb a

atan :: Coulomb a -> Coulomb a

sinh :: Coulomb a -> Coulomb a

cosh :: Coulomb a -> Coulomb a

tanh :: Coulomb a -> Coulomb a

asinh :: Coulomb a -> Coulomb a

acosh :: Coulomb a -> Coulomb a

atanh :: Coulomb a -> Coulomb a

log1p :: Coulomb a -> Coulomb a

expm1 :: Coulomb a -> Coulomb a

log1pexp :: Coulomb a -> Coulomb a

log1mexp :: Coulomb a -> Coulomb a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Coulomb a -> Integer

floatDigits :: Coulomb a -> Int

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

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

encodeFloat :: Integer -> Int -> Coulomb a

exponent :: Coulomb a -> Int

significand :: Coulomb a -> Coulomb a

scaleFloat :: Int -> Coulomb a -> Coulomb a

isNaN :: Coulomb a -> Bool

isInfinite :: Coulomb a -> Bool

isDenormalized :: Coulomb a -> Bool

isNegativeZero :: Coulomb a -> Bool

isIEEE :: Coulomb a -> Bool

atan2 :: Coulomb a -> Coulomb a -> Coulomb a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Coulomb a -> Coulomb a -> Coulomb a

(-) :: Coulomb a -> Coulomb a -> Coulomb a

(*) :: Coulomb a -> Coulomb a -> Coulomb a

negate :: Coulomb a -> Coulomb a

abs :: Coulomb a -> Coulomb a

signum :: Coulomb a -> Coulomb a

fromInteger :: Integer -> Coulomb a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Coulomb a -> Coulomb a -> Coulomb a

recip :: Coulomb a -> Coulomb a

fromRational :: Rational -> Coulomb a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Coulomb a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Coulomb a -> ShowS

show :: Coulomb a -> String

showList :: [Coulomb a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Coulomb a -> Coulomb a -> Ordering

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

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

(>) :: Coulomb a -> Coulomb a -> Bool

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

max :: Coulomb a -> Coulomb a -> Coulomb a

min :: Coulomb a -> Coulomb a -> Coulomb a

type DimOf Coulomb Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Coulomb Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type Voltage = NormalizeDim (Power ./. Current) Source #

Electric voltage quantity. Equal to

 Mass .*. Length.^+2 .*. Time.^-3 .*. Current.^-1

newtype Volt a Source #

Constructors

Volt a 

Instances

Instances details
IsUnit Volt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Volt 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Volt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Volt 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Volt = 'Text "V"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Volt a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Volt a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Volt a

exp :: Volt a -> Volt a

log :: Volt a -> Volt a

sqrt :: Volt a -> Volt a

(**) :: Volt a -> Volt a -> Volt a

logBase :: Volt a -> Volt a -> Volt a

sin :: Volt a -> Volt a

cos :: Volt a -> Volt a

tan :: Volt a -> Volt a

asin :: Volt a -> Volt a

acos :: Volt a -> Volt a

atan :: Volt a -> Volt a

sinh :: Volt a -> Volt a

cosh :: Volt a -> Volt a

tanh :: Volt a -> Volt a

asinh :: Volt a -> Volt a

acosh :: Volt a -> Volt a

atanh :: Volt a -> Volt a

log1p :: Volt a -> Volt a

expm1 :: Volt a -> Volt a

log1pexp :: Volt a -> Volt a

log1mexp :: Volt a -> Volt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Volt a -> Integer

floatDigits :: Volt a -> Int

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

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

encodeFloat :: Integer -> Int -> Volt a

exponent :: Volt a -> Int

significand :: Volt a -> Volt a

scaleFloat :: Int -> Volt a -> Volt a

isNaN :: Volt a -> Bool

isInfinite :: Volt a -> Bool

isDenormalized :: Volt a -> Bool

isNegativeZero :: Volt a -> Bool

isIEEE :: Volt a -> Bool

atan2 :: Volt a -> Volt a -> Volt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Volt a -> Volt a -> Volt a

(-) :: Volt a -> Volt a -> Volt a

(*) :: Volt a -> Volt a -> Volt a

negate :: Volt a -> Volt a

abs :: Volt a -> Volt a

signum :: Volt a -> Volt a

fromInteger :: Integer -> Volt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Volt a -> Volt a -> Volt a

recip :: Volt a -> Volt a

fromRational :: Rational -> Volt a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Volt a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Volt a -> ShowS

show :: Volt a -> String

showList :: [Volt a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Volt a -> Volt a -> Ordering

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

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

(>) :: Volt a -> Volt a -> Bool

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

max :: Volt a -> Volt a -> Volt a

min :: Volt a -> Volt a -> Volt a

type DimOf Volt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Volt Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Volt = 'Text "V"

type Capacitance = NormalizeDim (ElectricCharge ./. Voltage) Source #

Electric capacitance quantity. Equal to

Mass.^-1 .*. Length.^-2 .*. Time.^+4 .*. Current.^+2.

newtype Farad a Source #

Constructors

Farad a 

Instances

Instances details
IsUnit Farad Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Farad 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Farad Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Farad 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Farad = 'Text "F"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Farad a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Farad a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Farad a

exp :: Farad a -> Farad a

log :: Farad a -> Farad a

sqrt :: Farad a -> Farad a

(**) :: Farad a -> Farad a -> Farad a

logBase :: Farad a -> Farad a -> Farad a

sin :: Farad a -> Farad a

cos :: Farad a -> Farad a

tan :: Farad a -> Farad a

asin :: Farad a -> Farad a

acos :: Farad a -> Farad a

atan :: Farad a -> Farad a

sinh :: Farad a -> Farad a

cosh :: Farad a -> Farad a

tanh :: Farad a -> Farad a

asinh :: Farad a -> Farad a

acosh :: Farad a -> Farad a

atanh :: Farad a -> Farad a

log1p :: Farad a -> Farad a

expm1 :: Farad a -> Farad a

log1pexp :: Farad a -> Farad a

log1mexp :: Farad a -> Farad a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Farad a -> Integer

floatDigits :: Farad a -> Int

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

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

encodeFloat :: Integer -> Int -> Farad a

exponent :: Farad a -> Int

significand :: Farad a -> Farad a

scaleFloat :: Int -> Farad a -> Farad a

isNaN :: Farad a -> Bool

isInfinite :: Farad a -> Bool

isDenormalized :: Farad a -> Bool

isNegativeZero :: Farad a -> Bool

isIEEE :: Farad a -> Bool

atan2 :: Farad a -> Farad a -> Farad a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Farad a -> Farad a -> Farad a

(-) :: Farad a -> Farad a -> Farad a

(*) :: Farad a -> Farad a -> Farad a

negate :: Farad a -> Farad a

abs :: Farad a -> Farad a

signum :: Farad a -> Farad a

fromInteger :: Integer -> Farad a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Farad a -> Farad a -> Farad a

recip :: Farad a -> Farad a

fromRational :: Rational -> Farad a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Farad a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Farad a -> ShowS

show :: Farad a -> String

showList :: [Farad a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Farad a -> Farad a -> Ordering

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

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

(>) :: Farad a -> Farad a -> Bool

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

max :: Farad a -> Farad a -> Farad a

min :: Farad a -> Farad a -> Farad a

type DimOf Farad Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Farad Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Farad = 'Text "F"

type Resistance = NormalizeDim (Voltage ./. Current) Source #

Electric resistance quantity. Equal to

 Mass .*. Length.^+2 .*. Time.^-3 .*. Current.^-2

newtype Ohm a Source #

Constructors

Ohm a 

Instances

Instances details
IsUnit Ohm Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Ohm 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Ohm Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Ohm 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Ohm = 'Text "\937"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Ohm a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Ohm a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Ohm a

exp :: Ohm a -> Ohm a

log :: Ohm a -> Ohm a

sqrt :: Ohm a -> Ohm a

(**) :: Ohm a -> Ohm a -> Ohm a

logBase :: Ohm a -> Ohm a -> Ohm a

sin :: Ohm a -> Ohm a

cos :: Ohm a -> Ohm a

tan :: Ohm a -> Ohm a

asin :: Ohm a -> Ohm a

acos :: Ohm a -> Ohm a

atan :: Ohm a -> Ohm a

sinh :: Ohm a -> Ohm a

cosh :: Ohm a -> Ohm a

tanh :: Ohm a -> Ohm a

asinh :: Ohm a -> Ohm a

acosh :: Ohm a -> Ohm a

atanh :: Ohm a -> Ohm a

log1p :: Ohm a -> Ohm a

expm1 :: Ohm a -> Ohm a

log1pexp :: Ohm a -> Ohm a

log1mexp :: Ohm a -> Ohm a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Ohm a -> Integer

floatDigits :: Ohm a -> Int

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

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

encodeFloat :: Integer -> Int -> Ohm a

exponent :: Ohm a -> Int

significand :: Ohm a -> Ohm a

scaleFloat :: Int -> Ohm a -> Ohm a

isNaN :: Ohm a -> Bool

isInfinite :: Ohm a -> Bool

isDenormalized :: Ohm a -> Bool

isNegativeZero :: Ohm a -> Bool

isIEEE :: Ohm a -> Bool

atan2 :: Ohm a -> Ohm a -> Ohm a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Ohm a -> Ohm a -> Ohm a

(-) :: Ohm a -> Ohm a -> Ohm a

(*) :: Ohm a -> Ohm a -> Ohm a

negate :: Ohm a -> Ohm a

abs :: Ohm a -> Ohm a

signum :: Ohm a -> Ohm a

fromInteger :: Integer -> Ohm a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Ohm a -> Ohm a -> Ohm a

recip :: Ohm a -> Ohm a

fromRational :: Rational -> Ohm a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Ohm a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Ohm a -> ShowS

show :: Ohm a -> String

showList :: [Ohm a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Ohm a -> Ohm a -> Ordering

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

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

(>) :: Ohm a -> Ohm a -> Bool

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

max :: Ohm a -> Ohm a -> Ohm a

min :: Ohm a -> Ohm a -> Ohm a

type DimOf Ohm Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Ohm Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Ohm = 'Text "\937"

type Conductance = NormalizeDim (Current ./. Voltage) Source #

Electric conductance quantity. Equal to

 Mass.^-1 .*. Length.^-2 .*. Time.^+3 .*. Current.^+2

newtype Siemens a Source #

Constructors

Siemens a 

Instances

Instances details
IsUnit Siemens Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Siemens 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Siemens Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Siemens 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Siemens a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Siemens a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Siemens a

exp :: Siemens a -> Siemens a

log :: Siemens a -> Siemens a

sqrt :: Siemens a -> Siemens a

(**) :: Siemens a -> Siemens a -> Siemens a

logBase :: Siemens a -> Siemens a -> Siemens a

sin :: Siemens a -> Siemens a

cos :: Siemens a -> Siemens a

tan :: Siemens a -> Siemens a

asin :: Siemens a -> Siemens a

acos :: Siemens a -> Siemens a

atan :: Siemens a -> Siemens a

sinh :: Siemens a -> Siemens a

cosh :: Siemens a -> Siemens a

tanh :: Siemens a -> Siemens a

asinh :: Siemens a -> Siemens a

acosh :: Siemens a -> Siemens a

atanh :: Siemens a -> Siemens a

log1p :: Siemens a -> Siemens a

expm1 :: Siemens a -> Siemens a

log1pexp :: Siemens a -> Siemens a

log1mexp :: Siemens a -> Siemens a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Siemens a -> Integer

floatDigits :: Siemens a -> Int

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

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

encodeFloat :: Integer -> Int -> Siemens a

exponent :: Siemens a -> Int

significand :: Siemens a -> Siemens a

scaleFloat :: Int -> Siemens a -> Siemens a

isNaN :: Siemens a -> Bool

isInfinite :: Siemens a -> Bool

isDenormalized :: Siemens a -> Bool

isNegativeZero :: Siemens a -> Bool

isIEEE :: Siemens a -> Bool

atan2 :: Siemens a -> Siemens a -> Siemens a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Siemens a -> Siemens a -> Siemens a

(-) :: Siemens a -> Siemens a -> Siemens a

(*) :: Siemens a -> Siemens a -> Siemens a

negate :: Siemens a -> Siemens a

abs :: Siemens a -> Siemens a

signum :: Siemens a -> Siemens a

fromInteger :: Integer -> Siemens a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Siemens a -> Siemens a -> Siemens a

recip :: Siemens a -> Siemens a

fromRational :: Rational -> Siemens a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Siemens a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Siemens a -> ShowS

show :: Siemens a -> String

showList :: [Siemens a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Siemens a -> Siemens a -> Ordering

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

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

(>) :: Siemens a -> Siemens a -> Bool

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

max :: Siemens a -> Siemens a -> Siemens a

min :: Siemens a -> Siemens a -> Siemens a

type DimOf Siemens Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Siemens Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type MagneticFlux = NormalizeDim (Voltage .*. Time) Source #

Magnetic flux quantity. Equal to

 Mass .*. Length.^+2 .*. Time.^-2 .*. Current.^-1

newtype Weber a Source #

Constructors

Weber a 

Instances

Instances details
IsUnit Weber Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Weber 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Weber Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Weber 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Weber = 'Text "Wb"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Weber a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Weber a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Weber a

exp :: Weber a -> Weber a

log :: Weber a -> Weber a

sqrt :: Weber a -> Weber a

(**) :: Weber a -> Weber a -> Weber a

logBase :: Weber a -> Weber a -> Weber a

sin :: Weber a -> Weber a

cos :: Weber a -> Weber a

tan :: Weber a -> Weber a

asin :: Weber a -> Weber a

acos :: Weber a -> Weber a

atan :: Weber a -> Weber a

sinh :: Weber a -> Weber a

cosh :: Weber a -> Weber a

tanh :: Weber a -> Weber a

asinh :: Weber a -> Weber a

acosh :: Weber a -> Weber a

atanh :: Weber a -> Weber a

log1p :: Weber a -> Weber a

expm1 :: Weber a -> Weber a

log1pexp :: Weber a -> Weber a

log1mexp :: Weber a -> Weber a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Weber a -> Integer

floatDigits :: Weber a -> Int

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

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

encodeFloat :: Integer -> Int -> Weber a

exponent :: Weber a -> Int

significand :: Weber a -> Weber a

scaleFloat :: Int -> Weber a -> Weber a

isNaN :: Weber a -> Bool

isInfinite :: Weber a -> Bool

isDenormalized :: Weber a -> Bool

isNegativeZero :: Weber a -> Bool

isIEEE :: Weber a -> Bool

atan2 :: Weber a -> Weber a -> Weber a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Weber a -> Weber a -> Weber a

(-) :: Weber a -> Weber a -> Weber a

(*) :: Weber a -> Weber a -> Weber a

negate :: Weber a -> Weber a

abs :: Weber a -> Weber a

signum :: Weber a -> Weber a

fromInteger :: Integer -> Weber a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Weber a -> Weber a -> Weber a

recip :: Weber a -> Weber a

fromRational :: Rational -> Weber a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Weber a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Weber a -> ShowS

show :: Weber a -> String

showList :: [Weber a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Weber a -> Weber a -> Ordering

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

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

(>) :: Weber a -> Weber a -> Bool

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

max :: Weber a -> Weber a -> Weber a

min :: Weber a -> Weber a -> Weber a

type DimOf Weber Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Weber Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Weber = 'Text "Wb"

type MagneticInduction = NormalizeDim (MagneticFlux ./. (Length .^+ 2)) Source #

Magnetic induction quantity. Equal to

 Mass .*. Time.^-2 .*. Current.^-1

newtype Tesla a Source #

Constructors

Tesla a 

Instances

Instances details
IsUnit Tesla Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Tesla 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Tesla Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Tesla 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Tesla = 'Text "T"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Tesla a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Tesla a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Tesla a

exp :: Tesla a -> Tesla a

log :: Tesla a -> Tesla a

sqrt :: Tesla a -> Tesla a

(**) :: Tesla a -> Tesla a -> Tesla a

logBase :: Tesla a -> Tesla a -> Tesla a

sin :: Tesla a -> Tesla a

cos :: Tesla a -> Tesla a

tan :: Tesla a -> Tesla a

asin :: Tesla a -> Tesla a

acos :: Tesla a -> Tesla a

atan :: Tesla a -> Tesla a

sinh :: Tesla a -> Tesla a

cosh :: Tesla a -> Tesla a

tanh :: Tesla a -> Tesla a

asinh :: Tesla a -> Tesla a

acosh :: Tesla a -> Tesla a

atanh :: Tesla a -> Tesla a

log1p :: Tesla a -> Tesla a

expm1 :: Tesla a -> Tesla a

log1pexp :: Tesla a -> Tesla a

log1mexp :: Tesla a -> Tesla a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Tesla a -> Integer

floatDigits :: Tesla a -> Int

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

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

encodeFloat :: Integer -> Int -> Tesla a

exponent :: Tesla a -> Int

significand :: Tesla a -> Tesla a

scaleFloat :: Int -> Tesla a -> Tesla a

isNaN :: Tesla a -> Bool

isInfinite :: Tesla a -> Bool

isDenormalized :: Tesla a -> Bool

isNegativeZero :: Tesla a -> Bool

isIEEE :: Tesla a -> Bool

atan2 :: Tesla a -> Tesla a -> Tesla a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Tesla a -> Tesla a -> Tesla a

(-) :: Tesla a -> Tesla a -> Tesla a

(*) :: Tesla a -> Tesla a -> Tesla a

negate :: Tesla a -> Tesla a

abs :: Tesla a -> Tesla a

signum :: Tesla a -> Tesla a

fromInteger :: Integer -> Tesla a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Tesla a -> Tesla a -> Tesla a

recip :: Tesla a -> Tesla a

fromRational :: Rational -> Tesla a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Tesla a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Tesla a -> ShowS

show :: Tesla a -> String

showList :: [Tesla a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Tesla a -> Tesla a -> Ordering

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

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

(>) :: Tesla a -> Tesla a -> Bool

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

max :: Tesla a -> Tesla a -> Tesla a

min :: Tesla a -> Tesla a -> Tesla a

type DimOf Tesla Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Tesla Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Tesla = 'Text "T"

type Inductance = NormalizeDim (MagneticFlux ./. Current) Source #

Inductance quantity. Equal to

 Mass .*. Length.^+2 .*. Time.^-2 .*. Current.^-2

newtype Henry a Source #

Constructors

Henry a 

Instances

Instances details
IsUnit Henry Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Henry 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Henry Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Henry 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Henry = 'Text "H"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Henry a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Henry a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Henry a

exp :: Henry a -> Henry a

log :: Henry a -> Henry a

sqrt :: Henry a -> Henry a

(**) :: Henry a -> Henry a -> Henry a

logBase :: Henry a -> Henry a -> Henry a

sin :: Henry a -> Henry a

cos :: Henry a -> Henry a

tan :: Henry a -> Henry a

asin :: Henry a -> Henry a

acos :: Henry a -> Henry a

atan :: Henry a -> Henry a

sinh :: Henry a -> Henry a

cosh :: Henry a -> Henry a

tanh :: Henry a -> Henry a

asinh :: Henry a -> Henry a

acosh :: Henry a -> Henry a

atanh :: Henry a -> Henry a

log1p :: Henry a -> Henry a

expm1 :: Henry a -> Henry a

log1pexp :: Henry a -> Henry a

log1mexp :: Henry a -> Henry a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Henry a -> Integer

floatDigits :: Henry a -> Int

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

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

encodeFloat :: Integer -> Int -> Henry a

exponent :: Henry a -> Int

significand :: Henry a -> Henry a

scaleFloat :: Int -> Henry a -> Henry a

isNaN :: Henry a -> Bool

isInfinite :: Henry a -> Bool

isDenormalized :: Henry a -> Bool

isNegativeZero :: Henry a -> Bool

isIEEE :: Henry a -> Bool

atan2 :: Henry a -> Henry a -> Henry a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Henry a -> Henry a -> Henry a

(-) :: Henry a -> Henry a -> Henry a

(*) :: Henry a -> Henry a -> Henry a

negate :: Henry a -> Henry a

abs :: Henry a -> Henry a

signum :: Henry a -> Henry a

fromInteger :: Integer -> Henry a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Henry a -> Henry a -> Henry a

recip :: Henry a -> Henry a

fromRational :: Rational -> Henry a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Henry a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Henry a -> ShowS

show :: Henry a -> String

showList :: [Henry a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Henry a -> Henry a -> Ordering

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

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

(>) :: Henry a -> Henry a -> Bool

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

max :: Henry a -> Henry a -> Henry a

min :: Henry a -> Henry a -> Henry a

type DimOf Henry Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Henry Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Henry = 'Text "H"

type AbsorbedDose = NormalizeDim (Energy ./. Mass) Source #

Absorbed dose quantity. Equal to

 Length.^+2 .*. Time.^-2

newtype Gray a Source #

Absorbed dose in grays

Constructors

Gray a 

Instances

Instances details
IsUnit Gray Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Gray 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Gray Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Gray 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Gray = 'Text "Gy"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Gray a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Gray a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Gray a

exp :: Gray a -> Gray a

log :: Gray a -> Gray a

sqrt :: Gray a -> Gray a

(**) :: Gray a -> Gray a -> Gray a

logBase :: Gray a -> Gray a -> Gray a

sin :: Gray a -> Gray a

cos :: Gray a -> Gray a

tan :: Gray a -> Gray a

asin :: Gray a -> Gray a

acos :: Gray a -> Gray a

atan :: Gray a -> Gray a

sinh :: Gray a -> Gray a

cosh :: Gray a -> Gray a

tanh :: Gray a -> Gray a

asinh :: Gray a -> Gray a

acosh :: Gray a -> Gray a

atanh :: Gray a -> Gray a

log1p :: Gray a -> Gray a

expm1 :: Gray a -> Gray a

log1pexp :: Gray a -> Gray a

log1mexp :: Gray a -> Gray a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Gray a -> Integer

floatDigits :: Gray a -> Int

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

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

encodeFloat :: Integer -> Int -> Gray a

exponent :: Gray a -> Int

significand :: Gray a -> Gray a

scaleFloat :: Int -> Gray a -> Gray a

isNaN :: Gray a -> Bool

isInfinite :: Gray a -> Bool

isDenormalized :: Gray a -> Bool

isNegativeZero :: Gray a -> Bool

isIEEE :: Gray a -> Bool

atan2 :: Gray a -> Gray a -> Gray a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Gray a -> Gray a -> Gray a

(-) :: Gray a -> Gray a -> Gray a

(*) :: Gray a -> Gray a -> Gray a

negate :: Gray a -> Gray a

abs :: Gray a -> Gray a

signum :: Gray a -> Gray a

fromInteger :: Integer -> Gray a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Gray a -> Gray a -> Gray a

recip :: Gray a -> Gray a

fromRational :: Rational -> Gray a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Gray a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Gray a -> ShowS

show :: Gray a -> String

showList :: [Gray a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Gray a -> Gray a -> Ordering

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

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

(>) :: Gray a -> Gray a -> Bool

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

max :: Gray a -> Gray a -> Gray a

min :: Gray a -> Gray a -> Gray a

type DimOf Gray Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Gray Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Gray = 'Text "Gy"

newtype Sievert a Source #

Dose equivalent in sieverts

Constructors

Sievert a 

Instances

Instances details
IsUnit Sievert Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Sievert 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Sievert Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Sievert 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Sievert a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Sievert a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Sievert a

exp :: Sievert a -> Sievert a

log :: Sievert a -> Sievert a

sqrt :: Sievert a -> Sievert a

(**) :: Sievert a -> Sievert a -> Sievert a

logBase :: Sievert a -> Sievert a -> Sievert a

sin :: Sievert a -> Sievert a

cos :: Sievert a -> Sievert a

tan :: Sievert a -> Sievert a

asin :: Sievert a -> Sievert a

acos :: Sievert a -> Sievert a

atan :: Sievert a -> Sievert a

sinh :: Sievert a -> Sievert a

cosh :: Sievert a -> Sievert a

tanh :: Sievert a -> Sievert a

asinh :: Sievert a -> Sievert a

acosh :: Sievert a -> Sievert a

atanh :: Sievert a -> Sievert a

log1p :: Sievert a -> Sievert a

expm1 :: Sievert a -> Sievert a

log1pexp :: Sievert a -> Sievert a

log1mexp :: Sievert a -> Sievert a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Sievert a -> Integer

floatDigits :: Sievert a -> Int

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

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

encodeFloat :: Integer -> Int -> Sievert a

exponent :: Sievert a -> Int

significand :: Sievert a -> Sievert a

scaleFloat :: Int -> Sievert a -> Sievert a

isNaN :: Sievert a -> Bool

isInfinite :: Sievert a -> Bool

isDenormalized :: Sievert a -> Bool

isNegativeZero :: Sievert a -> Bool

isIEEE :: Sievert a -> Bool

atan2 :: Sievert a -> Sievert a -> Sievert a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Sievert a -> Sievert a -> Sievert a

(-) :: Sievert a -> Sievert a -> Sievert a

(*) :: Sievert a -> Sievert a -> Sievert a

negate :: Sievert a -> Sievert a

abs :: Sievert a -> Sievert a

signum :: Sievert a -> Sievert a

fromInteger :: Integer -> Sievert a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Sievert a -> Sievert a -> Sievert a

recip :: Sievert a -> Sievert a

fromRational :: Rational -> Sievert a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Sievert a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Sievert a -> ShowS

show :: Sievert a -> String

showList :: [Sievert a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Sievert a -> Sievert a -> Ordering

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

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

(>) :: Sievert a -> Sievert a -> Bool

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

max :: Sievert a -> Sievert a -> Sievert a

min :: Sievert a -> Sievert a -> Sievert a

type DimOf Sievert Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Sievert Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type CatalyticActivity = NormalizeDim (AmountOfSubstance ./. Time) Source #

Catalytic activity quantity. Equal to

 Time.^-1 .*. AmountOfSubstance

newtype Katal a Source #

Catalytic activity in katal

Constructors

Katal a 

Instances

Instances details
IsUnit Katal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type DimOf Katal 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

ShowUnit Katal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Associated Types

type ShowUnitType Katal 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Katal = 'Text "kat"

Methods

showsUnitPrec :: Int -> ShowS Source #

showUnit :: String Source #

prettysUnitPrec :: Int -> ShowS Source #

prettyUnit :: String Source #

Fractional a => ConversionFactor Katal a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

Methods

factor :: a Source #

Fractional a => ConvertibleUnit Katal a Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

pi :: Katal a

exp :: Katal a -> Katal a

log :: Katal a -> Katal a

sqrt :: Katal a -> Katal a

(**) :: Katal a -> Katal a -> Katal a

logBase :: Katal a -> Katal a -> Katal a

sin :: Katal a -> Katal a

cos :: Katal a -> Katal a

tan :: Katal a -> Katal a

asin :: Katal a -> Katal a

acos :: Katal a -> Katal a

atan :: Katal a -> Katal a

sinh :: Katal a -> Katal a

cosh :: Katal a -> Katal a

tanh :: Katal a -> Katal a

asinh :: Katal a -> Katal a

acosh :: Katal a -> Katal a

atanh :: Katal a -> Katal a

log1p :: Katal a -> Katal a

expm1 :: Katal a -> Katal a

log1pexp :: Katal a -> Katal a

log1mexp :: Katal a -> Katal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

floatRadix :: Katal a -> Integer

floatDigits :: Katal a -> Int

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

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

encodeFloat :: Integer -> Int -> Katal a

exponent :: Katal a -> Int

significand :: Katal a -> Katal a

scaleFloat :: Int -> Katal a -> Katal a

isNaN :: Katal a -> Bool

isInfinite :: Katal a -> Bool

isDenormalized :: Katal a -> Bool

isNegativeZero :: Katal a -> Bool

isIEEE :: Katal a -> Bool

atan2 :: Katal a -> Katal a -> Katal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(+) :: Katal a -> Katal a -> Katal a

(-) :: Katal a -> Katal a -> Katal a

(*) :: Katal a -> Katal a -> Katal a

negate :: Katal a -> Katal a

abs :: Katal a -> Katal a

signum :: Katal a -> Katal a

fromInteger :: Integer -> Katal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

(/) :: Katal a -> Katal a -> Katal a

recip :: Katal a -> Katal a

fromRational :: Rational -> Katal a

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

toRational :: Katal a -> Rational

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

showsPrec :: Int -> Katal a -> ShowS

show :: Katal a -> String

showList :: [Katal a] -> ShowS

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

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

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

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

Defined in Data.Units.SI.Derived.NonAngle

Methods

compare :: Katal a -> Katal a -> Ordering

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

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

(>) :: Katal a -> Katal a -> Bool

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

max :: Katal a -> Katal a -> Katal a

min :: Katal a -> Katal a -> Katal a

type DimOf Katal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Katal Source # 
Instance details

Defined in Data.Units.SI.Derived.NonAngle

type ShowUnitType Katal = 'Text "kat"