cifl-math-library-1.1.1.0: Math libraries
Safe HaskellSafe
LanguageHaskell2010

Math.Number.DimensionalAnalysis

Description

This module provides dimensional analysis according to SI system of units. For reference have used https://en.wikipedia.org/wiki/Dimensional_analysis and https://en.wikipedia.org/wiki/International_System_of_Units.

This module supports run-time checked quantities.

In reality this should be according to the International system of units, but I have not used the official standard documents when writing this code. However it is recognized that any major deviation from the standard would be considered a bug in this code. And definitely the International system of units is basis for this code.

For official references, see e.g. "ISO80000-1:2009:Quantities and Units" and "NIST Special Publication 330, 2008: The International system of units".

For c++ approach to dimensional analysis, see "Barton&Nackman: Scientific and Engineering C++".

Example uses:

show (3 %* meter) = "3 m"
3 %* meter + 4 %* kilogram == throw (InvalidDimensionsException meter_dimension kilogram_dimension "...")
convert (3 %* meter) (milli meter) == return 3000.0
convert (3 %* meter) kilogram == fail "..."
(3 %* meter) =/ (milli meter) == 3000.0
(3 %* meter) =/ kilogram == error "..."
convert lightyear (kilo meter) == return 9.4607304725808e12
3 logarithmic dBV == 1000.0 %* volt
Synopsis

Documentation

data Quantity r Source #

Constructors

As 

Instances

Instances details
Foldable Quantity Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

fold :: Monoid m => Quantity m -> m #

foldMap :: Monoid m => (a -> m) -> Quantity a -> m #

foldMap' :: Monoid m => (a -> m) -> Quantity a -> m #

foldr :: (a -> b -> b) -> b -> Quantity a -> b #

foldr' :: (a -> b -> b) -> b -> Quantity a -> b #

foldl :: (b -> a -> b) -> b -> Quantity a -> b #

foldl' :: (b -> a -> b) -> b -> Quantity a -> b #

foldr1 :: (a -> a -> a) -> Quantity a -> a #

foldl1 :: (a -> a -> a) -> Quantity a -> a #

toList :: Quantity a -> [a] #

null :: Quantity a -> Bool #

length :: Quantity a -> Int #

elem :: Eq a => a -> Quantity a -> Bool #

maximum :: Ord a => Quantity a -> a #

minimum :: Ord a => Quantity a -> a #

sum :: Num a => Quantity a -> a #

product :: Num a => Quantity a -> a #

Traversable Quantity Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

traverse :: Applicative f => (a -> f b) -> Quantity a -> f (Quantity b) #

sequenceA :: Applicative f => Quantity (f a) -> f (Quantity a) #

mapM :: Monad m => (a -> m b) -> Quantity a -> m (Quantity b) #

sequence :: Monad m => Quantity (m a) -> m (Quantity a) #

Applicative Quantity Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

pure :: a -> Quantity a #

(<*>) :: Quantity (a -> b) -> Quantity a -> Quantity b #

liftA2 :: (a -> b -> c) -> Quantity a -> Quantity b -> Quantity c #

(*>) :: Quantity a -> Quantity b -> Quantity b #

(<*) :: Quantity a -> Quantity b -> Quantity a #

Functor Quantity Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

fmap :: (a -> b) -> Quantity a -> Quantity b #

(<$) :: a -> Quantity b -> Quantity a #

DedekindCut Double (Quantity Double) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

DedekindCut Float (Quantity Float) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show r, Infinitesimal Stream r) => Infinitesimal Stream (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show r, Limiting Stream r) => Limiting Stream (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

data Closure Stream (Quantity r) Source #

Data r => Data (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quantity r -> c (Quantity r) #

gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (Quantity r) #

toConstr :: Quantity r -> Constr #

dataTypeOf :: Quantity r -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Quantity r)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Quantity r)) #

gmapT :: (forall b. Data b => b -> b) -> Quantity r -> Quantity r #

gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> Quantity r -> r0 #

gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> Quantity r -> r0 #

gmapQ :: (forall d. Data d => d -> u) -> Quantity r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quantity r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quantity r -> m (Quantity r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity r -> m (Quantity r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity r -> m (Quantity r) #

(Enum r, Show r) => Enum (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Real a, Floating a, Show a) => Floating (Quantity a) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show a, RealFloat a) => RealFloat (Quantity a) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Generic (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

type Rep (Quantity r) :: Type -> Type #

Methods

from :: Quantity r -> Rep (Quantity r) x #

to :: Rep (Quantity r) x -> Quantity r #

(Num r, Show r) => Num (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Quantity (Complex Double)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Quantity (Complex Float)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Quantity Integer) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Quantity Double) Source #

This read instance handles input examples such as "10 m(s*s)", "38.4 F", "12 As", "13 kgm(s*s)", "3.4 mm"

Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Quantity Int) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show r, Fractional r) => Fractional (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Integral r, Show r) => Integral (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show r, Real r) => Real (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

toRational :: Quantity r -> Rational #

(Show r, RealFrac r) => RealFrac (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

properFraction :: Integral b => Quantity r -> (b, Quantity r) #

truncate :: Integral b => Quantity r -> b #

round :: Integral b => Quantity r -> b #

ceiling :: Integral b => Quantity r -> b #

floor :: Integral b => Quantity r -> b #

ShowPrecision r => Show (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

showsPrec :: Int -> Quantity r -> ShowS #

show :: Quantity r -> String #

showList :: [Quantity r] -> ShowS #

Binary r => Binary (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

put :: Quantity r -> Put #

get :: Get (Quantity r) #

putList :: [Quantity r] -> Put #

(Show r, ConjugateSymmetric r) => ConjugateSymmetric (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

conj :: Quantity r -> Quantity r Source #

(Show r, InnerProductSpace r, Scalar (Quantity r) ~ Scalar r) => InnerProductSpace (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

(%.) :: Quantity r -> Quantity r -> Scalar (Quantity r) Source #

(Num r, NormedSpace r) => NormedSpace (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Num r => VectorSpace (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

type Scalar (Quantity r) Source #

(Num r, VectorSpace r) => Unit (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show r, DifferentiallyClosed r, VectorSpace r) => DifferentiallyClosed (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

derivate :: (Quantity r -> Quantity r) -> Quantity r -> Quantity r Source #

integral :: (Quantity r, Quantity r) -> (Quantity r -> Quantity r) -> Quantity r Source #

RationalRoots a => RationalRoots (Quantity a) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Closed a, Show a) => Closed (Quantity a) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

ShowPrecision r => PpShow (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

pp :: Quantity r -> Doc Source #

(Show r, Ord r) => Eq (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

(==) :: Quantity r -> Quantity r -> Bool #

(/=) :: Quantity r -> Quantity r -> Bool #

(Ord r, Num r, Show r) => Ord (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

compare :: Quantity r -> Quantity r -> Ordering #

(<) :: Quantity r -> Quantity r -> Bool #

(<=) :: Quantity r -> Quantity r -> Bool #

(>) :: Quantity r -> Quantity r -> Bool #

(>=) :: Quantity r -> Quantity r -> Bool #

max :: Quantity r -> Quantity r -> Quantity r #

min :: Quantity r -> Quantity r -> Quantity r #

(DedekindCut a b, Show a, Num a) => DedekindCut (Quantity a) (Quantity b) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), Floating (Closure Stream r)) => Floating (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

pi :: Closure Stream (Quantity r) #

exp :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

log :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

sqrt :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

(**) :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

logBase :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

sin :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

cos :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

tan :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

asin :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

acos :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

atan :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

sinh :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

cosh :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

tanh :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

asinh :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

acosh :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

atanh :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

log1p :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

expm1 :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

log1pexp :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

log1mexp :: Closure Stream (Quantity r) -> Closure Stream (Quantity r) #

(Show (Closure Stream a), RealFloat (Closure Stream a)) => RealFloat (Closure Stream (Quantity a)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), Num (Closure Stream r)) => Num (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), Fractional (Closure Stream r)) => Fractional (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), Real (Closure Stream r)) => Real (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), RealFrac (Closure Stream r)) => RealFrac (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(ShowPrecision r, Show (Closure Stream r), Floating r, Ord r) => Show (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), Eq (Closure Stream r)) => Eq (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

(Show (Closure Stream r), Num (Closure Stream r), Ord (Closure Stream r)) => Ord (Closure Stream (Quantity r)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

data Closure Stream (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

type Rep (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

type Rep (Quantity r) = D1 ('MetaData "Quantity" "Math.Number.DimensionalAnalysis" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "As" 'PrefixI 'True) (S1 ('MetaSel ('Just "value_amount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 r) :*: S1 ('MetaSel ('Just "value_dimension") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Dimension)))
type Scalar (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

type Scalar (Quantity r) = r

dimensionless_amount :: Show r => Quantity r -> r Source #

checked projection

equal_up_to :: (Floating a, Show a, Ord a) => a -> Quantity a -> Quantity a -> Bool Source #

data Dimension Source #

Instances

Instances details
Data Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dimension -> c Dimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dimension #

toConstr :: Dimension -> Constr #

dataTypeOf :: Dimension -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dimension) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dimension) #

gmapT :: (forall b. Data b => b -> b) -> Dimension -> Dimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dimension -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

Monoid Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Semigroup Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Generic Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

type Rep Dimension :: Type -> Type #

Num Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Fractional Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Show Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Binary Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

InnerProductSpace Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

StandardBasis Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

VectorSpace Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Associated Types

type Scalar Dimension Source #

Group Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

PpShow Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Methods

pp :: Dimension -> Doc Source #

Eq Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Ord Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

type Rep Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

type Rep Dimension = D1 ('MetaData "Dimension" "Math.Number.DimensionalAnalysis" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "Dimension" 'PrefixI 'True) ((S1 ('MetaSel ('Just "length_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational) :*: (S1 ('MetaSel ('Just "weight_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational) :*: S1 ('MetaSel ('Just "time_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational))) :*: ((S1 ('MetaSel ('Just "current_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational) :*: S1 ('MetaSel ('Just "temperature_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational)) :*: (S1 ('MetaSel ('Just "luminosity_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational) :*: S1 ('MetaSel ('Just "substance_power") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational)))))
type Scalar Dimension Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

isFractionalDimensional :: Dimension -> Bool Source #

isFractionalDimensional checks if a dimension is fractional dimensional

type Prefix r = Quantity r -> Quantity r Source #

mapQuantity :: (a -> b) -> (Dimension -> Dimension) -> Quantity a -> Quantity b Source #

mapQuantity2 :: (a -> b -> c) -> (Dimension -> Dimension -> Dimension) -> Quantity a -> Quantity b -> Quantity c Source #

class VectorSpace u => Unit u where Source #

the Unit class should be defined by any newtype based types that should interact well with the dimensional analysis mechanism.

Instances

Instances details
Unit R Source # 
Instance details

Defined in Math.Number.Units

Unit AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Unit Acceleration Source # 
Instance details

Defined in Math.Number.Units

Unit Angle Source # 
Instance details

Defined in Math.Number.Units

Unit Capacitance Source # 
Instance details

Defined in Math.Number.Units

Unit CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Unit Charge Source # 
Instance details

Defined in Math.Number.Units

Unit Conductance Source # 
Instance details

Defined in Math.Number.Units

Unit CubicLength Source # 
Instance details

Defined in Math.Number.Units

Unit Current Source # 
Instance details

Defined in Math.Number.Units

Unit DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Unit DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Unit DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Unit Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Unit Energy Source # 
Instance details

Defined in Math.Number.Units

Unit EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Unit Flux Source # 
Instance details

Defined in Math.Number.Units

Unit FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Unit Force Source # 
Instance details

Defined in Math.Number.Units

Unit Frequency Source # 
Instance details

Defined in Math.Number.Units

Unit Illuminance Source # 
Instance details

Defined in Math.Number.Units

Unit Inductance Source # 
Instance details

Defined in Math.Number.Units

Unit Information Source # 
Instance details

Defined in Math.Number.Units

Unit Intensity Source # 
Instance details

Defined in Math.Number.Units

Unit Length Source # 
Instance details

Defined in Math.Number.Units

Unit LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Unit Mass Source # 
Instance details

Defined in Math.Number.Units

Unit Percentage Source # 
Instance details

Defined in Math.Number.Units

Unit Power Source # 
Instance details

Defined in Math.Number.Units

Unit Pressure Source # 
Instance details

Defined in Math.Number.Units

Unit Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Unit Resistance Source # 
Instance details

Defined in Math.Number.Units

Unit SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Unit SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Unit SquareLength Source # 
Instance details

Defined in Math.Number.Units

Unit Substance Source # 
Instance details

Defined in Math.Number.Units

Unit Temperature Source # 
Instance details

Defined in Math.Number.Units

Unit Time Source # 
Instance details

Defined in Math.Number.Units

Unit Torque Source # 
Instance details

Defined in Math.Number.Units

Unit Velocity Source # 
Instance details

Defined in Math.Number.Units

Unit Voltage Source # 
Instance details

Defined in Math.Number.Units

Unit Double Source # 
Instance details

Defined in Math.Number.Units

Unit Float Source # 
Instance details

Defined in Math.Number.Units

(Num r, VectorSpace r) => Unit (Quantity r) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Unit (DUnit DAbsorbedDose) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DAcceleration) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DCapacitance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DCatalyticActivity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DCharge) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DCubicLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DCurrent) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DFlux) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DFluxDensity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DForce) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DFrequency) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DIlluminance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DInductance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DMass) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DPower) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DPressure) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DRadioactivity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DResistance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DSquareLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DSubstance) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DTime) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DVelocity) Source # 
Instance details

Defined in Math.Number.TypeUnits

Unit (DUnit DVoltage) Source # 
Instance details

Defined in Math.Number.TypeUnits

(LiteralUnit a, LiteralUnit b, Show (Scalar a), Scalar a ~ Scalar b) => Unit (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Methods

amount :: (a :* b) -> Scalar (a :* b) Source #

fromQuantity :: (Alternative m, MonadFail m) => Quantity (Scalar (a :* b)) -> m (a :* b) Source #

unitOf :: (a :* b) -> String Source #

dimension :: (a :* b) -> Dimension Source #

(LiteralUnit a, LiteralUnit b, Show (Scalar a), Scalar a ~ Scalar b) => Unit (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Methods

amount :: (a :/ b) -> Scalar (a :/ b) Source #

fromQuantity :: (Alternative m, MonadFail m) => Quantity (Scalar (a :/ b)) -> m (a :/ b) Source #

unitOf :: (a :/ b) -> String Source #

dimension :: (a :/ b) -> Dimension Source #

class Unit u => LiteralUnit u where Source #

The fromAmount method must check that compile-time information about dimensions is sufficient to determine dimension of the given input e.g. (fromAmount 3 :: Mass) is ok, but (fromAmount 3 :: Quantity Double) is not.

Minimal complete definition

fromAmount

Methods

fromAmount :: Scalar u -> u Source #

zeroAmount :: (Scalar u -> u) -> Scalar u Source #

conversionFactor :: (Scalar u -> u) -> Scalar u Source #

Instances

Instances details
LiteralUnit R Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Acceleration Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Angle Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Capacitance Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Charge Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Conductance Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit CubicLength Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Current Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Dimensionless Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Energy Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Flux Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit FluxDensity Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Force Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Frequency Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Illuminance Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Inductance Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Information Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Intensity Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Length Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Mass Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Percentage Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Power Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Pressure Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Radioactivity Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Resistance Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit SolidAngle Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit SoundLevel Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit SquareLength Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Substance Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Temperature Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Time Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Torque Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Velocity Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Voltage Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Double Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit Float Source # 
Instance details

Defined in Math.Number.Units

LiteralUnit (DUnit DAbsorbedDose) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DAcceleration) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DCapacitance) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DCatalyticActivity) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DCharge) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DCubicLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DCurrent) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DFlux) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DFluxDensity) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DForce) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DFrequency) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DIlluminance) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DInductance) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DMass) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DPower) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DPressure) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DRadioactivity) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DResistance) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DSquareLength) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DSubstance) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DTime) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DVelocity) Source # 
Instance details

Defined in Math.Number.TypeUnits

LiteralUnit (DUnit DVoltage) Source # 
Instance details

Defined in Math.Number.TypeUnits

(Scalar a ~ Scalar b, Show (Scalar a), LiteralUnit a, LiteralUnit b) => LiteralUnit (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Methods

fromAmount :: Scalar (a :* b) -> a :* b Source #

zeroAmount :: (Scalar (a :* b) -> a :* b) -> Scalar (a :* b) Source #

conversionFactor :: (Scalar (a :* b) -> a :* b) -> Scalar (a :* b) Source #

(Scalar a ~ Scalar b, Show (Scalar a), LiteralUnit a, LiteralUnit b) => LiteralUnit (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Methods

fromAmount :: Scalar (a :/ b) -> a :/ b Source #

zeroAmount :: (Scalar (a :/ b) -> a :/ b) -> Scalar (a :/ b) Source #

conversionFactor :: (Scalar (a :/ b) -> a :/ b) -> Scalar (a :/ b) Source #

fromQuantityDef :: (MonadFail m, Alternative m, Show a) => Dimension -> (a -> b) -> Quantity a -> m b Source #

data Level r Source #

<https://en.wikipedia.org/wiki/Level_(logarithmic_quantity) Level represents a reference to which computations involving logarithmic scales are compared to.

Constructors

Level 

Instances

Instances details
Read (Level (Complex Double)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Level Integer) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Level Double) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Read (Level Int) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Show (Level (Complex Double)) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Show (Level Integer) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Show (Level Double) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

Show (Level Int) Source # 
Instance details

Defined in Math.Number.DimensionalAnalysis

scale :: (Show a, Floating a, Real a) => Quantity a -> Level a -> Quantity a Source #

radian_scale :: RealFloat a => Level (Complex a) Source #

This is a way to convert radians to complex numbers e.g. (pi/2) logarithmic radian_scale == 0 :+ 1.

dBV :: Floating a => Level a Source #

logarithmic voltage with respect to base 10 relative to 1V. https://en.wikipedia.org/wiki/Decibel

dBu :: Floating a => Level a Source #

https://en.wikipedia.org/wiki/Decibel logarithmic voltage in base 10 relative to \(\sqrt{0.6}V\).

dB_SPL :: Floating a => Level a Source #

https://en.wikipedia.org/wiki/Decibel logarithmic pressure in base 10 compared to 20 micro pascals.

length_scale :: Floating a => Level a Source #

for logarithmic lengths in base 10.

frequency_scale :: Floating a => Level a Source #

https://en.wikipedia.org/wiki/Octave logarithmic frequency in base 2 relative to 16.352 Hz. a.k.a. in scientific designation. middle-C is fourth octave, e.g. 4 `logarithmic` octave == 261.626 %* hertz

octave :: Floating a => Level a Source #

https://en.wikipedia.org/wiki/Octave logarithmic frequency in base 2 relative to 16.352 Hz. a.k.a. in scientific designation. middle-C is fourth octave, e.g. 4 `logarithmic` octave == 261.626 %* hertz octave is just a different name for frequency_scale.

nines :: Double -> Double Source #

compute how many nines a probability has. nines 0.99999 == 5.0. https://en.wikipedia.org/wiki/9#Probability

fromNines :: Double -> Double Source #

compute probability when given number of nines. https://en.wikipedia.org/wiki/9#Probability

note_pitch :: Int -> Int -> Quantity Double Source #

note frequency from octave and index of note within octave. note_pitch 4 0 is middle-C.

bit :: (Floating a, Real a, Show a) => Quantity a Source #

WARNING: native representation is in number of bits. Use code such as the following for conversion: gibi byte `convert` kilo bit == return 8589934.592

byte :: (Floating a, Real a, Show a) => Quantity a Source #

Byte as the number of bits. WARNING: native representation is in number of bits. use code such as the following for conversion: gibi byte `convert` kilo bit == return 8589934.592

toAlternatives :: (Floating a, Ord a, ShowPrecision a, MonadFail m) => Quantity a -> m a Source #

Note that the number of alternatives grows quickly.

(=/) :: (Fractional (Scalar a), Unit a, Show a) => a -> a -> Scalar a Source #

convert :: (Scalar u ~ Scalar v, Unit v, Unit u, Show v, Show u, MonadFail m, Fractional (Scalar u)) => v -> u -> m (Scalar u) Source #

conversions between units. Dimensions have to match.

(=*) :: VectorSpace v => Scalar v -> v -> v Source #

prefix_value :: Num a => Prefix a -> a Source #

deci :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

centi :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

milli :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

micro :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

nano :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

pico :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

femto :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

atto :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

zepto :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

yocto :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

ronto :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

quecto :: (VectorSpace u, Floating (Scalar u)) => u -> u Source #

(=+=) :: VectorSpace v => v -> v -> v Source #

(=-=) :: VectorSpace v => v -> v -> v Source #

require_dimensionless :: Show a => String -> (a -> a) -> Quantity a -> Quantity a Source #

invalidDimensions :: (Show b, Show c) => String -> Dimension -> Dimension -> b -> c -> a Source #

invalidDimensionsM :: (MonadFail m, Show b, Show c) => String -> Dimension -> Dimension -> b -> c -> m a Source #

plusQ :: (MonadFail m, Num r, Show r) => Quantity r -> Quantity r -> m (Quantity r) Source #

minusQ :: (MonadFail m, Num r, Show r) => Quantity r -> Quantity r -> m (Quantity r) Source #

pp_dimension :: Dimension -> Doc Source #

pp_dimension prints dimension in a simple way without interpreting derived dimensions for example, pp_dimension newton_dimension == pp "kg m s^-2"

radian_dimension :: Dimension Source #

radian_dimension is basically same as dimensionless, using separate name anyway to allow clients to distinguish. No checking for this distinction is implemented.

steradian_dimension :: Dimension Source #

steradian_dimension is basically same as dimensionless, redefining anyway to allow clients to distinguish steradians. No checking for this distinction is implemented.

degree :: Floating a => Quantity a Source #

one degree angle

fromCelsius :: (Show a, Fractional a) => a -> Quantity a Source #

conversion from degrees celcius. WARNING: produces degrees in kelvin, so computations intended in degrees celcius should be done before conversion!

fromDegreesAngle :: Floating a => a -> Quantity a Source #

conversion from angle. WARNING: produces degrees in radian, so computations intended in degrees should be done before conversion!

stefan_boltzmann_constant :: (Floating a, Show a) => Quantity a Source #

Warning: don't confuse with boltzmann_constant.

siZeros :: [(String, Quantity Double)] Source #

this contains a list of quantities where basis of measurement is not zero in the dimension because the corresponding SI unit has different zero