{-# LANGUAGE NoImplicitPrelude #-}
module Number.DimensionTerm.SI (
second, minute, hour, day, year,
hertz,
meter,
gramm, tonne,
coulomb,
volt,
kelvin,
bit, byte,
inch, foot, yard, astronomicUnit, parsec,
SI.yocto, SI.zepto, SI.atto, SI.femto, SI.pico, SI.nano,
SI.micro, SI.milli, SI.centi, SI.deci, SI.one, SI.deca,
SI.hecto, SI.kilo, SI.mega, SI.giga, SI.tera, SI.peta,
SI.exa, SI.zetta, SI.yotta,
) where
import qualified Algebra.Field as Field
import qualified Number.DimensionTerm as DN
import qualified Number.SI.Unit as SI
import NumericPrelude.Numeric hiding (one)
second :: Field.C a => DN.Time a
second = DN.time 1e+0
minute :: Field.C a => DN.Time a
minute = DN.time SI.secondsPerMinute
hour :: Field.C a => DN.Time a
hour = DN.time SI.secondsPerHour
day :: Field.C a => DN.Time a
day = DN.time SI.secondsPerDay
year :: Field.C a => DN.Time a
year = DN.time SI.secondsPerYear
hertz :: Field.C a => DN.Frequency a
hertz = DN.frequency 1e+0
meter :: Field.C a => DN.Length a
meter = DN.length 1e+0
gramm :: Field.C a => DN.Mass a
gramm = DN.mass 1e-3
tonne :: Field.C a => DN.Mass a
tonne = DN.mass 1e+3
coulomb :: Field.C a => DN.Charge a
coulomb = DN.charge 1e+0
volt :: Field.C a => DN.Voltage a
volt = DN.voltage 1e+0
kelvin :: Field.C a => DN.Temperature a
kelvin = DN.temperature 1e+0
bit :: Field.C a => DN.Information a
bit = DN.information 1e+0
byte :: Field.C a => DN.Information a
byte = DN.information SI.bytesize
inch, foot, yard, astronomicUnit, parsec
:: Field.C a => DN.Length a
inch = DN.length SI.meterPerInch
foot = DN.length SI.meterPerFoot
yard = DN.length SI.meterPerYard
astronomicUnit = DN.length SI.meterPerAstronomicUnit
parsec = DN.length SI.meterPerParsec