Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Quantity (s :: Nat) = MkQuantity {}
- quantity :: KnownNat s => Scientific -> Quantity s
- quantityAux :: forall s. KnownNat s => Scientific -> Quantity s
- quantityLossless :: (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)
- roundScientific :: Int -> Scientific -> Scientific
Documentation
>>>
:set -XDataKinds
newtype Quantity (s :: Nat) Source #
Type encoding for common quantity values with 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>>>
quantity 0.415 :: Quantity 2
0.42>>>
quantity 0.425 :: Quantity 2
0.42>>>
quantityLossless 0.42 :: Either String (Quantity 2)
Right 0.42>>>
quantityLossless 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.Internal.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.Internal.Quantity | |
Ord (Quantity s) Source # | |
KnownNat s => Show (Quantity s) Source # |
|
Generic (Quantity s) Source # | |
KnownNat s => ToJSON (Quantity s) Source # |
|
Defined in Haspara.Internal.Quantity | |
KnownNat s => FromJSON (Quantity s) Source # |
|
type Rep (Quantity s) Source # | |
Defined in Haspara.Internal.Quantity type Rep (Quantity s) = D1 ('MetaData "Quantity" "Haspara.Internal.Quantity" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" 'True) (C1 ('MetaCons "MkQuantity" 'PrefixI 'True) (S1 ('MetaSel ('Just "unQuantity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Decimal RoundHalfEven s Integer)))) |
quantity :: KnownNat s => Scientific -> Quantity s Source #
Constructs Quantity
values from Scientific
values in a lossy way.
This function uses quantityAux
in case that the lossless attempt fails. We
could have used quantityAux
directly. However, quantityAux
is doing too
much (see roundScientific
). Therefore, we are first attempting a lossless
construction (see quantityLossless
) and we fallback to quantityAux
in
case the lossless construction fails.
>>>
quantity 0 :: Quantity 0
0>>>
quantity 0 :: Quantity 1
0.0>>>
quantity 0 :: Quantity 2
0.00>>>
quantity 0.04 :: Quantity 1
0.0>>>
quantity 0.05 :: Quantity 1
0.0>>>
quantity 0.06 :: Quantity 1
0.1>>>
quantity 0.14 :: Quantity 1
0.1>>>
quantity 0.15 :: Quantity 1
0.2>>>
quantity 0.16 :: Quantity 1
0.2>>>
quantity 0.04 :: Quantity 2
0.04>>>
quantity 0.05 :: Quantity 2
0.05>>>
quantity 0.06 :: Quantity 2
0.06>>>
quantity 0.14 :: Quantity 2
0.14>>>
quantity 0.15 :: Quantity 2
0.15>>>
quantity 0.16 :: Quantity 2
0.16>>>
quantity 0.04 :: Quantity 3
0.040>>>
quantity 0.05 :: Quantity 3
0.050>>>
quantity 0.06 :: Quantity 3
0.060>>>
quantity 0.14 :: Quantity 3
0.140>>>
quantity 0.15 :: Quantity 3
0.150>>>
quantity 0.16 :: Quantity 3
0.160
quantityAux :: forall s. KnownNat s => Scientific -> Quantity s Source #
quantityLossless :: (KnownNat s, MonadError String m) => Scientific -> m (Quantity s) Source #
Constructs Quantity
values from Scientific
values in a lossy way.
>>>
quantityLossless 0 :: Either String (Quantity 0)
Right 0>>>
quantityLossless 0 :: Either String (Quantity 1)
Right 0.0>>>
quantityLossless 0 :: Either String (Quantity 2)
Right 0.00>>>
quantityLossless 0.04 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 4.0e-2">>>
quantityLossless 0.05 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 5.0e-2">>>
quantityLossless 0.06 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 6.0e-2">>>
quantityLossless 0.14 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 0.14">>>
quantityLossless 0.15 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 0.15">>>
quantityLossless 0.16 :: Either String (Quantity 1)
Left "Underflow while trying to create quantity: 0.16">>>
quantityLossless 0.04 :: Either String (Quantity 2)
Right 0.04>>>
quantityLossless 0.05 :: Either String (Quantity 2)
Right 0.05>>>
quantityLossless 0.06 :: Either String (Quantity 2)
Right 0.06>>>
quantityLossless 0.14 :: Either String (Quantity 2)
Right 0.14>>>
quantityLossless 0.15 :: Either String (Quantity 2)
Right 0.15>>>
quantityLossless 0.16 :: Either String (Quantity 2)
Right 0.16>>>
quantityLossless 0.04 :: Either String (Quantity 3)
Right 0.040>>>
quantityLossless 0.05 :: Either String (Quantity 3)
Right 0.050>>>
quantityLossless 0.06 :: Either String (Quantity 3)
Right 0.060>>>
quantityLossless 0.14 :: Either String (Quantity 3)
Right 0.140>>>
quantityLossless 0.15 :: Either String (Quantity 3)
Right 0.150>>>
quantityLossless 0.16 :: Either String (Quantity 3)
Right 0.160
roundQuantity :: KnownNat k => Quantity (n + k) -> Quantity n Source #
Rounds given quantity by k
digits.
>>>
roundQuantity (quantity 0.415 :: Quantity 3) :: Quantity 2
0.42>>>
roundQuantity (quantity 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 (quantity 0.42 :: Quantity 2) (quantity 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 (quantity 0.42 :: Quantity 2) (quantity 0.42 :: Quantity 2)
0.1764
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.