module Data.Units.SI.Derived.NonAngle
(
Celsius (..)
, Area
, Volume
, Frequency
, Hertz (..)
, Radioactivity
, Becquerel (..)
, Speed
, Acceleration
, Force
, Newton (..)
, Pressure
, Pascal (..)
, Stress
, Energy
, Joule (..)
, Work
, Heat
, Power
, RadiantFlux
, Watt (..)
, ElectricCharge
, Coulomb (..)
, QuantityOfElectricity
, Voltage
, Volt (..)
, ElectricPotential
, ElectromotiveForce
, Capacitance
, Farad (..)
, Resistance
, Ohm (..)
, Impedance
, Reactance
, Conductance
, Siemens (..)
, MagneticFlux
, Weber (..)
, MagneticInduction
, MagneticFluxDensity
, Tesla (..)
, Inductance
, Henry (..)
, EquivalentDose
, AbsorbedDose
, Gray (..)
, Sievert (..)
, CatalyticActivity
, Katal (..)
)
where
import Data.Units.Base
import Data.Units.SI.System
type Area = Length .^+ 2
type Volume = Length .^+ 3
type Frequency = Time .^- 1
$(mkUnit "Hertz" "Hz" ''Frequency 1)
type Radioactivity = Time .^- 1
$(mkUnit "Becquerel" "Bq" ''Radioactivity 1)
type Speed = NormalizeDim (Length ./. Time)
type Acceleration = NormalizeDim (Length ./. Time .^+ 2)
type Force = NormalizeDim (Mass .*. Acceleration)
$(mkUnit "Newton" "N" ''Force 1)
type Pressure = NormalizeDim (Force ./. (Length .^+ 2))
type Stress = Pressure
$(mkUnit "Pascal" "Pa" ''Pressure 1)
type Energy = NormalizeDim (Length .*. Force)
type Work = Energy
type Heat = Energy
$(mkUnit "Joule" "J" ''Energy 1)
type Power = NormalizeDim (Energy ./. Time)
type RadiantFlux = Power
$(mkUnit "Watt" "W" ''Power 1)
type ElectricCharge = NormalizeDim (Time .*. Current)
type QuantityOfElectricity = ElectricCharge
$(mkUnit "Coulomb" "C" ''ElectricCharge 1)
type Voltage = NormalizeDim (Power ./. Current)
type ElectricPotential = Voltage
type ElectromotiveForce = Voltage
$(mkUnit "Volt" "V" ''Voltage 1)
type Capacitance = NormalizeDim (ElectricCharge ./. Voltage)
$(mkUnit "Farad" "F" ''Capacitance 1)
type Resistance = NormalizeDim (Voltage ./. Current)
type Impedance = Resistance
type Reactance = Resistance
$(mkUnit "Ohm" "Ω" ''Resistance 1)
type Conductance = NormalizeDim (Current ./. Voltage)
$(mkUnit "Siemens" "S" ''Conductance 1)
type MagneticFlux = NormalizeDim (Voltage .*. Time)
$(mkUnit "Weber" "Wb" ''MagneticFlux 1)
type MagneticInduction = NormalizeDim (MagneticFlux ./. (Length .^+ 2))
type MagneticFluxDensity = MagneticInduction
$(mkUnit "Tesla" "T" ''MagneticInduction 1)
type Inductance = NormalizeDim (MagneticFlux ./. Current)
$(mkUnit "Henry" "H" ''Inductance 1)
$(mkUnitNoFactor "Celsius" "°C" ''Temperature)
instance Fractional a => ConversionFactor Celsius a where
factor :: a
factor = a
1
{-# INLINE factor #-}
instance Fractional a => ConvertibleUnit Celsius a where
toBaseUnit :: Celsius a -> BaseUnitOf Celsius a
toBaseUnit (Celsius a
x) = a -> Kelvin a
forall a. a -> Kelvin a
Kelvin (a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
273.15)
{-# INLINE toBaseUnit #-}
fromBaseUnit :: BaseUnitOf Celsius a -> Celsius a
fromBaseUnit (Kelvin a
x) = a -> Celsius a
forall a. a -> Celsius a
Celsius (a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
273.15)
{-# INLINE fromBaseUnit #-}
type AbsorbedDose = NormalizeDim (Energy ./. Mass)
type EquivalentDose = AbsorbedDose
$(mkUnit "Gray" "Gy" ''AbsorbedDose 1)
$(mkUnit "Sievert" "Sv" ''EquivalentDose 1)
type CatalyticActivity = NormalizeDim (AmountOfSubstance ./. Time)
$(mkUnit "Katal" "kat" ''CatalyticActivity 1)