Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Experimental |
Portability | GHC only? |
Safe Haskell | None |
Language | Haskell2010 |
Defines types for manipulation of quantities with fixed point representations.
Synopsis
- data family Dimensional v :: Dimension -> Type -> Type
- type Unit (m :: Metricality) = Dimensional (DUnit m)
- type Quantity = SQuantity One
- type SQuantity s = Dimensional (DQuantity s)
- data Metricality
- data Dimension = Dim TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt
- type family (a :: Dimension) * (b :: Dimension) where ...
- type family (a :: Dimension) / (d :: Dimension) where ...
- type family (d :: Dimension) ^ (x :: TypeInt) where ...
- type family NRoot (d :: Dimension) (x :: TypeInt) where ...
- type Recip (d :: Dimension) = DOne / d
- data Dimension' = Dim' !Int !Int !Int !Int !Int !Int !Int
- class HasDynamicDimension a => HasDimension a where
- dimension :: a -> Dimension'
- type KnownDimension (d :: Dimension) = HasDimension (Proxy d)
- (*~) :: forall s m d a b. (RealFrac a, Integral b, MinCtxt s a) => a -> Unit m d a -> SQuantity s d b
- (/~) :: forall s m d a b. (Real a, Fractional b, MinCtxt s b) => SQuantity s d a -> Unit m d b -> b
- (*) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 * v2), Num a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 * v2) (d1 * d2) a
- (/) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 / v2), Fractional a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 / v2) (d1 / d2) a
- (+) :: Num a => SQuantity s d a -> SQuantity s d a -> SQuantity s d a
- (-) :: Num a => SQuantity s d a -> SQuantity s d a -> SQuantity s d a
- negate :: Num a => SQuantity s d a -> SQuantity s d a
- abs :: Num a => SQuantity s d a -> SQuantity s d a
- expD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- logD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- sinD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- cosD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- tanD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- asinD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- acosD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- atanD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- sinhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- coshD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- tanhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- asinhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- acoshD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- atanhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b
- atan2D :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double, MinCtxt s3 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne a -> SQuantity s3 DOne b
- expVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- logVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- sinVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- cosVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- tanVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- asinVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- acosVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- atanVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- sinhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- coshVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- tanhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- asinhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- acoshVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- atanhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c
- atan2Via :: forall s1 s2 s3 a b c d. (Integral a, RealFloat b, Integral c, MinCtxt s1 b, MinCtxt s2 b, MinCtxt s3 b, KnownDimension d) => Proxy b -> SQuantity s1 d a -> SQuantity s2 d a -> SQuantity s3 DOne c
- (*~~) :: (Functor f, RealFrac a, Integral b, MinCtxt s a) => f a -> Unit m d a -> f (SQuantity s d b)
- (/~~) :: (Functor f, Real a, Fractional b, MinCtxt s b) => f (SQuantity s d a) -> Unit m d b -> f b
- sum :: (Num a, Foldable f) => f (SQuantity s d a) -> SQuantity s d a
- mean :: (Fractional a, Foldable f) => f (SQuantity s d a) -> SQuantity s d a
- rescale :: forall a b d s1 s2. (Integral a, Integral b, KnownExactPi s1, KnownExactPi s2) => SQuantity s1 d a -> SQuantity s2 d b
- rescaleFinite :: (Integral a, FiniteBits a, Integral b, FiniteBits b, KnownExactPi s1, KnownExactPi s2) => SQuantity s1 d a -> SQuantity s2 d b
- rescaleD :: (Integral a, Integral b, KnownExactPi s1, KnownExactPi s2) => SQuantity s1 d a -> SQuantity s2 d b
- rescaleVia :: forall a b c d s1 s2. (Integral a, RealFrac b, Floating b, Integral c, KnownExactPi s1, KnownExactPi s2) => Proxy b -> SQuantity s1 d a -> SQuantity s2 d c
- class KnownVariant (v :: Variant) where
- dmap :: (a1 -> a2) -> Dimensional v d a1 -> Dimensional v d a2
- changeRep :: forall v1 v2 d a b. (KnownVariant v1, KnownVariant v2, CompatibleVariants v1 v2, MinCtxt (ScaleFactor v1 / ScaleFactor v2) b, Real a, Fractional b) => Dimensional v1 d a -> Dimensional v2 d b
- changeRepRound :: forall v1 v2 d a b. (KnownVariant v1, KnownVariant v2, CompatibleVariants v1 v2, MinCtxt (ScaleFactor v1 / ScaleFactor v2) a, RealFrac a, Integral b) => Dimensional v1 d a -> Dimensional v2 d b
- changeRepApproximate :: (KnownVariant v, Floating b) => Dimensional v d ExactPi -> Dimensional v d b
- type DOne = Dim Zero Zero Zero Zero Zero Zero Zero
- type DLength = Dim Pos1 Zero Zero Zero Zero Zero Zero
- type DMass = Dim Zero Pos1 Zero Zero Zero Zero Zero
- type DTime = Dim Zero Zero Pos1 Zero Zero Zero Zero
- type DElectricCurrent = Dim Zero Zero Zero Pos1 Zero Zero Zero
- type DThermodynamicTemperature = Dim Zero Zero Zero Zero Pos1 Zero Zero
- type DAmountOfSubstance = Dim Zero Zero Zero Zero Zero Pos1 Zero
- type DLuminousIntensity = Dim Zero Zero Zero Zero Zero Zero Pos1
- type Dimensionless = Quantity DOne
- type Length = Quantity DLength
- type Mass = Quantity DMass
- type Time = Quantity DTime
- type ElectricCurrent = Quantity DElectricCurrent
- type ThermodynamicTemperature = Quantity DThermodynamicTemperature
- type AmountOfSubstance = Quantity DAmountOfSubstance
- type LuminousIntensity = Quantity DLuminousIntensity
- _0 :: Num a => SQuantity s d a
- epsilon :: Integral a => SQuantity s d a
- _1 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _2 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _3 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _4 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _5 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _6 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _7 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _8 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- _9 :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- pi :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- tau :: (Integral a, KnownExactPi s) => SQuantity s DOne a
- siUnit :: forall d a. (KnownDimension d, Num a) => Unit NonMetric d a
- one :: Num a => Unit NonMetric DOne a
- mkUnitR :: Floating a => UnitName m -> ExactPi -> Unit m1 d a -> Unit m d a
- mkUnitQ :: Fractional a => UnitName m -> Rational -> Unit m1 d a -> Unit m d a
- mkUnitZ :: Num a => UnitName m -> Integer -> Unit m1 d a -> Unit m d a
- name :: Unit m d a -> UnitName m
- exactValue :: Unit m d a -> ExactPi
- weaken :: Unit m d a -> Unit NonMetric d a
- strengthen :: Unit m d a -> Maybe (Unit Metric d a)
- exactify :: Unit m d a -> Unit m d ExactPi
- type Q n a = SQuantity (QScale n) DOne a
- type QScale n = One / ExactNatural (2 ^ n)
- type Angle8 = SQuantity (Pi * QScale 7) DPlaneAngle Int8
- type Angle16 = SQuantity (Pi * QScale 15) DPlaneAngle Int16
- type Angle32 = SQuantity (Pi * QScale 31) DPlaneAngle Int32
Types
We provide access to the same Dimensional
, Unit
, and Quantity
types as are exposed by Numeric.Units.Dimensional, but additionally
offer the SQuantity
type to represent scaled quantities. Fixed-point quantities are quantities backed by integers, it is frequently
necessary to scale those integers into a range appropriate for the physical problem at hand.
data family Dimensional v :: Dimension -> Type -> Type Source #
A dimensional value, either a Quantity
or a Unit
, parameterized by its Dimension
and representation.
Instances
type Unit (m :: Metricality) = Dimensional (DUnit m) Source #
A unit of measurement.
type SQuantity s = Dimensional (DQuantity s) Source #
A dimensional quantity, stored as an ExactPi'
multiple of its value in its dimension's SI coherent unit.
The name is an abbreviation for scaled quantity.
data Metricality Source #
Encodes whether a unit is a metric unit, that is, whether it can be combined with a metric prefix to form a related unit.
Instances
Physical Dimensions
Represents a physical dimension in the basis of the 7 SI base dimensions, where the respective dimensions are represented by type variables using the following convention:
- l: Length
- m: Mass
- t: Time
- i: Electric current
- th: Thermodynamic temperature
- n: Amount of substance
- j: Luminous intensity
For the equivalent term-level representation, see Dimension'
Instances
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDimension (Proxy (Dim l m t i th n j)) Source # | |
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDynamicDimension (Proxy (Dim l m t i th n j)) Source # | |
Defined in Numeric.Units.Dimensional.Dimensions.TypeLevel dynamicDimension :: Proxy (Dim l m t i th n j) -> DynamicDimension Source # |
Dimension Arithmetic
type family (a :: Dimension) * (b :: Dimension) where ... infixl 7 Source #
Multiplication of dimensions corresponds to adding of the base dimensions' exponents.
type family (a :: Dimension) / (d :: Dimension) where ... infixl 7 Source #
Division of dimensions corresponds to subtraction of the base dimensions' exponents.
type family (d :: Dimension) ^ (x :: TypeInt) where ... infixr 8 Source #
Powers of dimensions corresponds to multiplication of the base dimensions' exponents by the exponent.
We limit ourselves to integer powers of Dimensionals as fractional powers make little physical sense.
type family NRoot (d :: Dimension) (x :: TypeInt) where ... Source #
Roots of dimensions corresponds to division of the base dimensions' exponents by the order of the root.
type Recip (d :: Dimension) = DOne / d Source #
The reciprocal of a dimension is defined as the result of dividing DOne
by it,
or of negating each of the base dimensions' exponents.
Term Level Representation of Dimensions
data Dimension' Source #
A physical dimension, encoded as 7 integers, representing a factorization of the dimension into the
7 SI base dimensions. By convention they are stored in the same order as
in the Dimension
data kind.
Instances
class HasDynamicDimension a => HasDimension a where Source #
Dimensional values inhabit this class, which allows access to a term-level representation of their dimension.
dimension :: a -> Dimension' Source #
Obtains a term-level representation of a value's dimension.
Instances
HasDimension Dimension' Source # | |
Defined in Numeric.Units.Dimensional.Dimensions.TermLevel dimension :: Dimension' -> Dimension' Source # | |
HasDimension AnyUnit Source # | |
Defined in Numeric.Units.Dimensional.Dynamic dimension :: AnyUnit -> Dimension' Source # | |
HasDimension (AnyQuantity a) Source # | |
Defined in Numeric.Units.Dimensional.Dynamic dimension :: AnyQuantity a -> Dimension' Source # | |
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDimension (Proxy (Dim l m t i th n j)) Source # | |
KnownDimension d => HasDimension (Dimensional v d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal dimension :: Dimensional v d a -> Dimension' Source # |
type KnownDimension (d :: Dimension) = HasDimension (Proxy d) Source #
A KnownDimension is one for which we can construct a term-level representation.
Each validly constructed type of kind Dimension
has a KnownDimension
instance.
While KnownDimension
is a constraint synonym, the presence of
in
a context allows use of KnownDimension
d
.dimension
:: Proxy
d -> Dimension'
Dimensional Arithmetic
(*~) :: forall s m d a b. (RealFrac a, Integral b, MinCtxt s a) => a -> Unit m d a -> SQuantity s d b infixl 7 Source #
Forms a possibly scaled SQuantity
by multipliying a number and a unit.
(/~) :: forall s m d a b. (Real a, Fractional b, MinCtxt s b) => SQuantity s d a -> Unit m d b -> b infixl 7 Source #
(*) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 * v2), Num a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 * v2) (d1 * d2) a infixl 7 Source #
(/) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 / v2), Fractional a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 / v2) (d1 / d2) a infixl 7 Source #
(+) :: Num a => SQuantity s d a -> SQuantity s d a -> SQuantity s d a infixl 6 Source #
Adds two possibly scaled SQuantity
s, preserving any scale factor.
Use in conjunction with changeRepRound
to combine quantities with differing scale factors.
(-) :: Num a => SQuantity s d a -> SQuantity s d a -> SQuantity s d a infixl 6 Source #
Subtracts one possibly scaled SQuantity
from another, preserving any scale factor.
Use in conjunction with changeRepRound
to combine quantities with differing scale factors.
negate :: Num a => SQuantity s d a -> SQuantity s d a Source #
Negates the value of a possibly scaled SQuantity
, preserving any scale factor.
abs :: Num a => SQuantity s d a -> SQuantity s d a Source #
Takes the absolute value of a possibly scaled SQuantity
, preserving any scale factor.
Transcendental Functions
Via Double
expD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
logD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
sinD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
cosD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
tanD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
asinD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
acosD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
atanD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
sinhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
coshD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
tanhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
asinhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
acoshD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
atanhD :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne b Source #
atan2D :: (Integral a, Integral b, MinCtxt s1 Double, MinCtxt s2 Double, MinCtxt s3 Double) => SQuantity s1 DOne a -> SQuantity s2 DOne a -> SQuantity s3 DOne b Source #
The standard two argument arctangent function. Since it interprets its two arguments in comparison with one another, the input may have any dimension.
Via arbitary Floating
type
expVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
logVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
sinVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
cosVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
tanVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
asinVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
acosVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
atanVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
sinhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
coshVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
tanhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
asinhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
acoshVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
atanhVia :: (Integral a, RealFrac b, Floating b, Integral c, MinCtxt s1 b, MinCtxt s2 b) => Proxy b -> SQuantity s1 DOne a -> SQuantity s2 DOne c Source #
atan2Via :: forall s1 s2 s3 a b c d. (Integral a, RealFloat b, Integral c, MinCtxt s1 b, MinCtxt s2 b, MinCtxt s3 b, KnownDimension d) => Proxy b -> SQuantity s1 d a -> SQuantity s2 d a -> SQuantity s3 DOne c Source #
The standard two argument arctangent function. Since it interprets its two arguments in comparison with one another, the input may have any dimension.
Operations on Collections
(*~~) :: (Functor f, RealFrac a, Integral b, MinCtxt s a) => f a -> Unit m d a -> f (SQuantity s d b) infixl 7 Source #
Applies *~
to all values in a functor.
(/~~) :: (Functor f, Real a, Fractional b, MinCtxt s b) => f (SQuantity s d a) -> Unit m d b -> f b infixl 7 Source #
Applies /~
to all values in a functor.
sum :: (Num a, Foldable f) => f (SQuantity s d a) -> SQuantity s d a Source #
The sum of all elements in a list.
mean :: (Fractional a, Foldable f) => f (SQuantity s d a) -> SQuantity s d a Source #
The arithmetic mean of all elements in a list.
Conversion Between Representations
rescale :: forall a b d s1 s2. (Integral a, Integral b, KnownExactPi s1, KnownExactPi s2) => SQuantity s1 d a -> SQuantity s2 d b Source #
Rescales a fixed point quantity, accomodating changes both in its scale factor and its representation type.
Note that this uses an arbitrary precision representation of pi
, which may be quite slow.
rescaleFinite :: (Integral a, FiniteBits a, Integral b, FiniteBits b, KnownExactPi s1, KnownExactPi s2) => SQuantity s1 d a -> SQuantity s2 d b Source #
Rescales a fixed point quantity, accomodating changes both in its scale factor and its representation type.
Expected to outperform rescale
when a FiniteBits
context is available for the source and destination representation types.
rescaleD :: (Integral a, Integral b, KnownExactPi s1, KnownExactPi s2) => SQuantity s1 d a -> SQuantity s2 d b Source #
Approximately rescales a fixed point quantity, accomodating changes both in its scale factor and its representation type.
Uses approximate arithmetic by way of an intermediate Double
representation.
rescaleVia :: forall a b c d s1 s2. (Integral a, RealFrac b, Floating b, Integral c, KnownExactPi s1, KnownExactPi s2) => Proxy b -> SQuantity s1 d a -> SQuantity s2 d c Source #
Approximately rescales a fixed point quantity, accomodating changes both in its scale factor and its representation type.
Uses approximate arithmetic by way of an intermediate Floating
type, to which a proxy must be supplied.
class KnownVariant (v :: Variant) where Source #
A KnownVariant is one whose term-level Dimensional
values we can represent with an associated data family instance
and manipulate with certain functions, not all of which are exported from the package.
Each validly constructed type of kind Variant
has a KnownVariant
instance.
extractValue, extractName, injectValue, dmap
dmap :: (a1 -> a2) -> Dimensional v d a1 -> Dimensional v d a2 Source #
Maps over the underlying representation of a dimensional value. The caller is responsible for ensuring that the supplied function respects the dimensional abstraction. This means that the function must preserve numerical values, or linearly scale them while preserving the origin.
Instances
KnownVariant (DQuantity s) Source # | |
Defined in Numeric.Units.Dimensional.Internal extractValue :: Dimensional (DQuantity s) d a -> (a, Maybe ExactPi) extractName :: Dimensional (DQuantity s) d a -> Maybe (UnitName NonMetric) injectValue :: Maybe (UnitName NonMetric) -> (a, Maybe ExactPi) -> Dimensional (DQuantity s) d a dmap :: (a1 -> a2) -> Dimensional (DQuantity s) d a1 -> Dimensional (DQuantity s) d a2 Source # | |
Typeable m => KnownVariant (DUnit m) Source # | |
Defined in Numeric.Units.Dimensional.Internal extractValue :: Dimensional (DUnit m) d a -> (a, Maybe ExactPi) extractName :: Dimensional (DUnit m) d a -> Maybe (UnitName NonMetric) injectValue :: Maybe (UnitName NonMetric) -> (a, Maybe ExactPi) -> Dimensional (DUnit m) d a dmap :: (a1 -> a2) -> Dimensional (DUnit m) d a1 -> Dimensional (DUnit m) d a2 Source # |
changeRep :: forall v1 v2 d a b. (KnownVariant v1, KnownVariant v2, CompatibleVariants v1 v2, MinCtxt (ScaleFactor v1 / ScaleFactor v2) b, Real a, Fractional b) => Dimensional v1 d a -> Dimensional v2 d b Source #
Convenient conversion between numerical types while retaining dimensional information.
changeRepRound :: forall v1 v2 d a b. (KnownVariant v1, KnownVariant v2, CompatibleVariants v1 v2, MinCtxt (ScaleFactor v1 / ScaleFactor v2) a, RealFrac a, Integral b) => Dimensional v1 d a -> Dimensional v2 d b Source #
changeRepApproximate :: (KnownVariant v, Floating b) => Dimensional v d ExactPi -> Dimensional v d b Source #
Convenient conversion from exactly represented values while retaining dimensional information.
Dimension Synonyms
type DOne = Dim Zero Zero Zero Zero Zero Zero Zero Source #
The type-level dimension of dimensionless values.
Quantity Synonyms
type Dimensionless = Quantity DOne Source #
Constants
_0 :: Num a => SQuantity s d a Source #
The constant for zero is polymorphic, allowing
it to express zero Length
or Capacitance
or Velocity
etc, in addition
to the Dimensionless
value zero.
epsilon :: Integral a => SQuantity s d a Source #
The least positive representable value in a given fixed-point scaled quantity type.
Note that, other than _0
and epsilon
, these constants may not be exactly representable with certain scale factors.
tau :: (Integral a, KnownExactPi s) => SQuantity s DOne a Source #
Twice pi
.
For background on tau
see http://tauday.com/tau-manifesto (but also
feel free to review http://www.thepimanifesto.com).
Constructing Units
siUnit :: forall d a. (KnownDimension d, Num a) => Unit NonMetric d a Source #
A polymorphic Unit
which can be used in place of the coherent
SI base unit of any dimension. This allows polymorphic quantity
creation and destruction without exposing the Dimensional
constructor.
one :: Num a => Unit NonMetric DOne a Source #
The unit one
has dimension DOne
and is the base unit of dimensionless values.
As detailed in 7.10 "Values of quantities expressed simply as numbers:
the unit one, symbol 1" of [1] the unit one generally does not
appear in expressions. However, for us it is necessary to use one
as we would any other unit to perform the "boxing" of dimensionless values.
mkUnitR :: Floating a => UnitName m -> ExactPi -> Unit m1 d a -> Unit m d a Source #
Forms a new atomic Unit
by specifying its UnitName
and its definition as a multiple of another Unit
.
Use this variant when the scale factor of the resulting unit is irrational or Approximate
. See mkUnitQ
for when it is rational
and mkUnitZ
for when it is an integer.
Note that supplying zero as a definining quantity is invalid, as the library relies upon units forming a group under multiplication.
Supplying negative defining quantities is allowed and handled gracefully, but is discouraged on the grounds that it may be unexpected by other readers.
Unit Metadata
exactValue :: Unit m d a -> ExactPi Source #
weaken :: Unit m d a -> Unit NonMetric d a Source #
Discards potentially unwanted type level information about a Unit
.
Commonly Used Type Synonyms
These type synonyms for commonly used fixed-point types are provided for convenience.
type Q n a = SQuantity (QScale n) DOne a Source #
A dimensionless number with n
fractional bits, using a representation of type a
.
type Angle8 = SQuantity (Pi * QScale 7) DPlaneAngle Int8 Source #
A single-turn angle represented as a signed 8-bit integer.