Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides definitions for modeling and working with quantities with fixed decimal points.
Synopsis
- newtype Quantity (s :: Nat) = MkQuantity {}
- type UnsignedQuantity s = Refined NonNegative (Quantity s)
- mkQuantity :: KnownNat s => Scientific -> Quantity s
- mkQuantityLossless :: (KnownNat s, MonadError String m) => Scientific -> m (Quantity s)
- roundQuantity :: KnownNat k => Quantity (n + k) -> Quantity n
- times :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Quantity s
- timesLossless :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Quantity (s + k)
- sumUnsignedQuantity :: KnownNat s => [UnsignedQuantity s] -> UnsignedQuantity s
- absQuantity :: KnownNat s => Quantity s -> UnsignedQuantity s
- mkQuantityAux :: forall s. KnownNat s => Scientific -> Quantity s
- roundScientific :: Int -> Scientific -> Scientific
Data Definition
newtype Quantity (s :: Nat) Source #
Type encoding for quantity values with a given scaling (digits after the decimal point).
>>>
42 :: Quantity 0
42>>>
42 :: Quantity 1
42.0>>>
42 :: Quantity 2
42.00>>>
41 + 1 :: Quantity 2
42.00>>>
43 - 1 :: Quantity 2
42.00>>>
2 * 3 * 7 :: Quantity 2
42.00>>>
negate (-42) :: Quantity 2
42.00>>>
abs (-42) :: Quantity 2
42.00>>>
signum (-42) :: Quantity 2
-1.00>>>
fromInteger 42 :: Quantity 2
42.00>>>
mkQuantity 0.415 :: Quantity 2
0.42>>>
mkQuantity 0.425 :: Quantity 2
0.42>>>
mkQuantityLossless 0.42 :: Either String (Quantity 2)
Right 0.42>>>
mkQuantityLossless 0.415 :: Either String (Quantity 2)
Left "Underflow while trying to create quantity: 0.415"
Instances
Lift (Quantity s :: Type) Source # | |
Eq (Quantity s) Source # | |
KnownNat s => Fractional (Arith (Quantity s)) Source # | Fractional arithmetic over
|
KnownNat s => Num (Arith (Quantity s)) Source # | Numeric arithmetic over
|
Defined in Haspara.Quantity (+) :: Arith (Quantity s) -> Arith (Quantity s) -> Arith (Quantity s) # (-) :: Arith (Quantity s) -> Arith (Quantity s) -> Arith (Quantity s) # (*) :: Arith (Quantity s) -> Arith (Quantity s) -> Arith (Quantity s) # negate :: Arith (Quantity s) -> Arith (Quantity s) # abs :: Arith (Quantity s) -> Arith (Quantity s) # signum :: Arith (Quantity s) -> Arith (Quantity s) # fromInteger :: Integer -> Arith (Quantity s) # | |
KnownNat s => Num (Quantity s) Source # | |
Defined in Haspara.Quantity | |
Ord (Quantity s) Source # | |
KnownNat s => Show (Quantity s) Source # |
|
Generic (Quantity s) Source # | |
KnownNat s => ToJSON (Quantity s) Source # |
|
Defined in Haspara.Quantity | |
KnownNat s => FromJSON (Quantity s) Source # |
|
type Rep (Quantity s) Source # | |
Defined in Haspara.Quantity type Rep (Quantity s) = D1 ('MetaData "Quantity" "Haspara.Quantity" "haspara-0.0.0.4-91kyQ1gsJrx6JOOKY5ajCi" 'True) (C1 ('MetaCons "MkQuantity" 'PrefixI 'True) (S1 ('MetaSel ('Just "unQuantity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Decimal RoundHalfEven s Integer)))) |
type UnsignedQuantity s = Refined NonNegative (Quantity s) Source #
Type definition for unsigned Quantity
values.
Smart Constructors
mkQuantity :: KnownNat s => Scientific -> Quantity s Source #
Constructs Quantity
values from Scientific
values in a lossy way.
This function uses mkQuantityAux
in case that the lossless attempt fails.
We could have used mkQuantityAux
directly. However, mkQuantityAux
is
doing too much (see roundScientific
). Therefore, we are first attempting a
lossless construction (see mkQuantityLossless
) and we fallback to
mkQuantityAux
in case the lossless construction fails.
>>>
mkQuantity 0 :: Quantity 0
0>>>
mkQuantity 0 :: Quantity 1
0.0>>>
mkQuantity 0 :: Quantity 2
0.00>>>
mkQuantity 0.04 :: Quantity 1
0.0>>>
mkQuantity 0.05 :: Quantity 1
0.0>>>
mkQuantity 0.06 :: Quantity 1
0.1>>>
mkQuantity 0.14 :: Quantity 1
0.1>>>
mkQuantity 0.15 :: Quantity 1
0.2>>>
mkQuantity 0.16 :: Quantity 1
0.2>>>
mkQuantity 0.04 :: Quantity 2
0.04>>>
mkQuantity 0.05 :: Quantity 2
0.05>>>
mkQuantity 0.06 :: Quantity 2
0.06>>>
mkQuantity 0.14 :: Quantity 2
0.14>>>
mkQuantity 0.15 :: Quantity 2
0.15>>>
mkQuantity 0.16 :: Quantity 2
0.16>>>
mkQuantity 0.04 :: Quantity 3
0.040>>>
mkQuantity 0.05 :: Quantity 3
0.050>>>
mkQuantity 0.06 :: Quantity 3
0.060>>>
mkQuantity 0.14 :: Quantity 3
0.140>>>
mkQuantity 0.15 :: Quantity 3
0.150>>>
mkQuantity 0.16 :: Quantity 3
0.160
mkQuantityLossless :: (KnownNat s, MonadError String m) => Scientific -> m (Quantity s) Source #
Constructs Quantity
values from Scientific
values in a lossy way.
>>>
mkQuantityLossless 0 :: Either String (Quantity 0)
Right 0>>>
mkQuantityLossless 0 :: Either String (Quantity 1)
Right 0.0>>>
mkQuantityLossless 0 :: Either String (Quantity 2)
Right 0.00>>>
mkQuantityLossless 0.04 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 4.0e-2">>>
mkQuantityLossless 0.05 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 5.0e-2">>>
mkQuantityLossless 0.06 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 6.0e-2">>>
mkQuantityLossless 0.14 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 0.14">>>
mkQuantityLossless 0.15 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 0.15">>>
mkQuantityLossless 0.16 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 0.16">>>
mkQuantityLossless 0.04 :: Either String (Quantity 2)
Right 0.04>>>
mkQuantityLossless 0.05 :: Either String (Quantity 2)
Right 0.05>>>
mkQuantityLossless 0.06 :: Either String (Quantity 2)
Right 0.06>>>
mkQuantityLossless 0.14 :: Either String (Quantity 2)
Right 0.14>>>
mkQuantityLossless 0.15 :: Either String (Quantity 2)
Right 0.15>>>
mkQuantityLossless 0.16 :: Either String (Quantity 2)
Right 0.16>>>
mkQuantityLossless 0.04 :: Either String (Quantity 3)
Right 0.040>>>
mkQuantityLossless 0.05 :: Either String (Quantity 3)
Right 0.050>>>
mkQuantityLossless 0.06 :: Either String (Quantity 3)
Right 0.060>>>
mkQuantityLossless 0.14 :: Either String (Quantity 3)
Right 0.140>>>
mkQuantityLossless 0.15 :: Either String (Quantity 3)
Right 0.150>>>
mkQuantityLossless 0.16 :: Either String (Quantity 3)
Right 0.160
Utilities
roundQuantity :: KnownNat k => Quantity (n + k) -> Quantity n Source #
Rounds given quantity by k
digits.
>>>
roundQuantity (mkQuantity 0.415 :: Quantity 3) :: Quantity 2
0.42>>>
roundQuantity (mkQuantity 0.425 :: Quantity 3) :: Quantity 2
0.42
times :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Quantity s Source #
Multiplies two quantities with different scales and rounds back to the scale of the frst operand.
>>>
times (mkQuantity 0.42 :: Quantity 2) (mkQuantity 0.42 :: Quantity 2)
0.18
timesLossless :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Quantity (s + k) Source #
Multiplies two quantities with different scales.
>>>
timesLossless (mkQuantity 0.42 :: Quantity 2) (mkQuantity 0.42 :: Quantity 2)
0.1764
sumUnsignedQuantity :: KnownNat s => [UnsignedQuantity s] -> UnsignedQuantity s Source #
Returns the total of a list of unsigned quantities.
>>>
sumUnsignedQuantity [] :: UnsignedQuantity 2
Refined 0.00
absQuantity :: KnownNat s => Quantity s -> UnsignedQuantity s Source #
Returns the absolute value of the Quantity
as UnsignedQuantity
.
>>>
abs (mkQuantity 0.42 :: Quantity 2)
0.42>>>
abs (mkQuantity 0 :: Quantity 2)
0.00>>>
abs (mkQuantity (-0.42) :: Quantity 2)
0.42
Internal
mkQuantityAux :: forall s. KnownNat s => Scientific -> Quantity s Source #
Auxiliary function for constructing Quantity
values.
See mkQuantity
why we need this function and why we haven't used it as the
direct implementation of mkQuantity
.
Call-sites should avoid using this function directly due to its performance characteristics.
roundScientific :: Int -> Scientific -> Scientific Source #
Rounds a given scientific into a new scientific with given max digits after decimal point.
This uses half-even rounding method.
>>>
roundScientific 0 0.4
0.0>>>
roundScientific 0 0.5
0.0>>>
roundScientific 0 0.6
1.0>>>
roundScientific 0 1.4
1.0>>>
roundScientific 0 1.5
2.0>>>
roundScientific 0 1.6
2.0>>>
roundScientific 1 0.04
0.0>>>
roundScientific 1 0.05
0.0>>>
roundScientific 1 0.06
0.1>>>
roundScientific 1 0.14
0.1>>>
roundScientific 1 0.15
0.2>>>
roundScientific 1 0.16
0.2>>>
roundScientific 1 3.650
3.6>>>
roundScientific 1 3.740
3.7>>>
roundScientific 1 3.749
3.7>>>
roundScientific 1 3.750
3.8>>>
roundScientific 1 3.751
3.8>>>
roundScientific 1 3.760
3.8>>>
roundScientific 1 (-3.650)
-3.6>>>
roundScientific 1 (-3.740)
-3.7>>>
roundScientific 1 (-3.749)
-3.7>>>
roundScientific 1 (-3.750)
-3.8>>>
roundScientific 1 (-3.751)
-3.8>>>
roundScientific 1 (-3.760)
-3.8
TODO: Refactor to improve the performance of this function.