{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Haspara.Quantity where
import Control.Applicative (liftA2)
import Control.Monad.Except (MonadError (throwError))
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Encoding as Aeson.Encoding
import Data.Either (fromRight)
import Data.Proxy (Proxy (..))
import Data.Scientific (FPFormat (Fixed), Scientific, formatScientific)
import GHC.Generics (Generic)
import GHC.TypeLits (KnownNat, Nat, natVal, type (+))
import qualified Language.Haskell.TH.Syntax as TH
import qualified Numeric.Decimal as D
import Refined (NonNegative, Refined, unrefine)
import Refined.Unsafe (unsafeRefine)
newtype Quantity (s :: Nat) = MkQuantity {forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity :: D.Decimal D.RoundHalfEven s Integer}
deriving (Quantity s -> Quantity s -> Bool
forall (s :: Nat). Quantity s -> Quantity s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Quantity s -> Quantity s -> Bool
$c/= :: forall (s :: Nat). Quantity s -> Quantity s -> Bool
== :: Quantity s -> Quantity s -> Bool
$c== :: forall (s :: Nat). Quantity s -> Quantity s -> Bool
Eq, Quantity s -> Quantity s -> Bool
Quantity s -> Quantity s -> Ordering
Quantity s -> Quantity s -> Quantity s
forall (s :: Nat). Eq (Quantity s)
forall (s :: Nat). Quantity s -> Quantity s -> Bool
forall (s :: Nat). Quantity s -> Quantity s -> Ordering
forall (s :: Nat). Quantity s -> Quantity s -> Quantity s
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Quantity s -> Quantity s -> Quantity s
$cmin :: forall (s :: Nat). Quantity s -> Quantity s -> Quantity s
max :: Quantity s -> Quantity s -> Quantity s
$cmax :: forall (s :: Nat). Quantity s -> Quantity s -> Quantity s
>= :: Quantity s -> Quantity s -> Bool
$c>= :: forall (s :: Nat). Quantity s -> Quantity s -> Bool
> :: Quantity s -> Quantity s -> Bool
$c> :: forall (s :: Nat). Quantity s -> Quantity s -> Bool
<= :: Quantity s -> Quantity s -> Bool
$c<= :: forall (s :: Nat). Quantity s -> Quantity s -> Bool
< :: Quantity s -> Quantity s -> Bool
$c< :: forall (s :: Nat). Quantity s -> Quantity s -> Bool
compare :: Quantity s -> Quantity s -> Ordering
$ccompare :: forall (s :: Nat). Quantity s -> Quantity s -> Ordering
Ord, forall (s :: Nat) x. Rep (Quantity s) x -> Quantity s
forall (s :: Nat) x. Quantity s -> Rep (Quantity s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (s :: Nat) x. Rep (Quantity s) x -> Quantity s
$cfrom :: forall (s :: Nat) x. Quantity s -> Rep (Quantity s) x
Generic, Integer -> Quantity s
Quantity s -> Quantity s
Quantity s -> Quantity s -> Quantity s
forall (s :: Nat). KnownNat s => Integer -> Quantity s
forall (s :: Nat). KnownNat s => Quantity s -> Quantity s
forall (s :: Nat).
KnownNat s =>
Quantity s -> Quantity s -> Quantity s
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Quantity s
$cfromInteger :: forall (s :: Nat). KnownNat s => Integer -> Quantity s
signum :: Quantity s -> Quantity s
$csignum :: forall (s :: Nat). KnownNat s => Quantity s -> Quantity s
abs :: Quantity s -> Quantity s
$cabs :: forall (s :: Nat). KnownNat s => Quantity s -> Quantity s
negate :: Quantity s -> Quantity s
$cnegate :: forall (s :: Nat). KnownNat s => Quantity s -> Quantity s
* :: Quantity s -> Quantity s -> Quantity s
$c* :: forall (s :: Nat).
KnownNat s =>
Quantity s -> Quantity s -> Quantity s
- :: Quantity s -> Quantity s -> Quantity s
$c- :: forall (s :: Nat).
KnownNat s =>
Quantity s -> Quantity s -> Quantity s
+ :: Quantity s -> Quantity s -> Quantity s
$c+ :: forall (s :: Nat).
KnownNat s =>
Quantity s -> Quantity s -> Quantity s
Num)
type UnsignedQuantity s = Refined NonNegative (Quantity s)
deriving instance TH.Lift (D.Decimal D.RoundHalfEven s Integer)
deriving instance TH.Lift (Quantity s)
instance (KnownNat s) => Aeson.FromJSON (Quantity s) where
parseJSON :: Value -> Parser (Quantity s)
parseJSON = forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
Aeson.withScientific String
"Quantity" (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (s :: Nat). KnownNat s => Scientific -> Quantity s
mkQuantity)
instance (KnownNat s) => Aeson.ToJSON (Quantity s) where
toJSON :: Quantity s -> Value
toJSON = Scientific -> Value
Aeson.Number forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall p (s :: Nat) r.
(Integral p, KnownNat s) =>
Decimal r s p -> Scientific
D.toScientificDecimal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity
toEncoding :: Quantity s -> Encoding
toEncoding = Scientific -> Encoding
Aeson.Encoding.scientific forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall p (s :: Nat) r.
(Integral p, KnownNat s) =>
Decimal r s p -> Scientific
D.toScientificDecimal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity
instance (KnownNat s) => Num (D.Arith (Quantity s)) where
+ :: Arith (Quantity s) -> Arith (Quantity s) -> Arith (Quantity s)
(+) = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(+)
(-) = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
* :: Arith (Quantity s) -> Arith (Quantity s) -> Arith (Quantity s)
(*) = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Num a => a -> a -> a
(*)
signum :: Arith (Quantity s) -> Arith (Quantity s)
signum = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
signum
abs :: Arith (Quantity s) -> Arith (Quantity s)
abs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Num a => a -> a
abs
fromInteger :: Integer -> Arith (Quantity s)
fromInteger = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r (s :: Nat). KnownNat s => Integer -> Decimal r s Integer
D.fromIntegerDecimal
instance (KnownNat s) => Fractional (D.Arith (Quantity s)) where
Arith (Quantity s)
a / :: Arith (Quantity s) -> Arith (Quantity s) -> Arith (Quantity s)
/ Arith (Quantity s)
b = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity Arith (Quantity s)
a forall a. Fractional a => a -> a -> a
/ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity Arith (Quantity s)
b
fromRational :: Rational -> Arith (Quantity s)
fromRational = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r (s :: Nat).
(MonadThrow m, KnownNat s) =>
Rational -> m (Decimal r s Integer)
D.fromRationalDecimalWithoutLoss
instance KnownNat s => Show (Quantity s) where
show :: Quantity s -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity
mkQuantity :: KnownNat s => Scientific -> Quantity s
mkQuantity :: forall (s :: Nat). KnownNat s => Scientific -> Quantity s
mkQuantity Scientific
s = case forall (s :: Nat) (m :: * -> *).
(KnownNat s, MonadError String m) =>
Scientific -> m (Quantity s)
mkQuantityLossless Scientific
s of
Left String
_ -> forall (s :: Nat). KnownNat s => Scientific -> Quantity s
mkQuantityAux Scientific
s
Right Quantity s
dv -> Quantity s
dv
mkQuantityLossless :: (KnownNat s, MonadError String m) => Scientific -> m (Quantity s)
mkQuantityLossless :: forall (s :: Nat) (m :: * -> *).
(KnownNat s, MonadError String m) =>
Scientific -> m (Quantity s)
mkQuantityLossless Scientific
s = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String
"Underflow while trying to create quantity: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Scientific
s)) (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r (s :: Nat).
(MonadThrow m, KnownNat s) =>
Scientific -> m (Decimal r s Integer)
D.fromScientificDecimal Scientific
s
roundQuantity :: KnownNat k => Quantity (n + k) -> Quantity n
roundQuantity :: forall (k :: Nat) (n :: Nat).
KnownNat k =>
Quantity (n + k) -> Quantity n
roundQuantity (MkQuantity Decimal RoundHalfEven (n + k) Integer
d) = forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity (forall r p (k :: Nat) (n :: Nat).
(Round r p, KnownNat k) =>
Decimal r (n + k) p -> Decimal r n p
D.roundDecimal Decimal RoundHalfEven (n + k) Integer
d)
times :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Quantity s
times :: forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity s
times Quantity s
q1 Quantity k
q2 = forall (k :: Nat) (n :: Nat).
KnownNat k =>
Quantity (n + k) -> Quantity n
roundQuantity (forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity (s + k)
timesLossless Quantity s
q1 Quantity k
q2)
timesLossless :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Quantity (s + k)
timesLossless :: forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity (s + k)
timesLossless (MkQuantity Decimal RoundHalfEven s Integer
d1) (MkQuantity Decimal RoundHalfEven k Integer
d2) = forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity (forall r (s1 :: Nat) (s2 :: Nat).
Decimal r s1 Integer
-> Decimal r s2 Integer -> Decimal r (s1 + s2) Integer
D.timesDecimal Decimal RoundHalfEven s Integer
d1 Decimal RoundHalfEven k Integer
d2)
divide :: (KnownNat s) => Quantity s -> Quantity s -> Maybe (Quantity s)
divide :: forall (s :: Nat).
KnownNat s =>
Quantity s -> Quantity s -> Maybe (Quantity s)
divide (MkQuantity Decimal RoundHalfEven s Integer
d1) (MkQuantity Decimal RoundHalfEven s Integer
d2) = forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (s :: Nat) r.
(MonadThrow m, KnownNat s, Round r Integer) =>
Decimal r s Integer
-> Decimal r s Integer -> m (Decimal r s Integer)
D.divideDecimalWithRounding Decimal RoundHalfEven s Integer
d1 Decimal RoundHalfEven s Integer
d2
divideL :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Maybe (Quantity s)
divideL :: forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Maybe (Quantity s)
divideL (MkQuantity Decimal RoundHalfEven s Integer
d1) Quantity k
d2 = forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (s :: Nat) r.
(MonadThrow m, KnownNat s, Round r Integer) =>
Decimal r s Integer
-> Decimal r s Integer -> m (Decimal r s Integer)
D.divideDecimalWithRounding Decimal RoundHalfEven s Integer
d1 (forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity forall a b. (a -> b) -> a -> b
$ Quantity s
1 forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity s
`times` Quantity k
d2)
divideR :: (KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Maybe (Quantity k)
divideR :: forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Maybe (Quantity k)
divideR Quantity s
d1 (MkQuantity Decimal RoundHalfEven k Integer
d2) = forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (s :: Nat) r.
(MonadThrow m, KnownNat s, Round r Integer) =>
Decimal r s Integer
-> Decimal r s Integer -> m (Decimal r s Integer)
D.divideDecimalWithRounding (forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity forall a b. (a -> b) -> a -> b
$ Quantity k
1 forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity s
`times` Quantity s
d1) Decimal RoundHalfEven k Integer
d2
divideD :: (KnownNat r, KnownNat s, KnownNat k) => Quantity s -> Quantity k -> Maybe (Quantity r)
divideD :: forall (r :: Nat) (s :: Nat) (k :: Nat).
(KnownNat r, KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Maybe (Quantity r)
divideD Quantity s
d1 Quantity k
d2 = forall (s :: Nat). Decimal RoundHalfEven s Integer -> Quantity s
MkQuantity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (s :: Nat) r.
(MonadThrow m, KnownNat s, Round r Integer) =>
Decimal r s Integer
-> Decimal r s Integer -> m (Decimal r s Integer)
D.divideDecimalWithRounding (forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity forall a b. (a -> b) -> a -> b
$ Quantity r
1 forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity s
`times` Quantity s
d1) (forall (s :: Nat). Quantity s -> Decimal RoundHalfEven s Integer
unQuantity forall a b. (a -> b) -> a -> b
$ Quantity r
1 forall (s :: Nat) (k :: Nat).
(KnownNat s, KnownNat k) =>
Quantity s -> Quantity k -> Quantity s
`times` Quantity k
d2)
sumUnsignedQuantity
:: KnownNat s
=> [UnsignedQuantity s]
-> UnsignedQuantity s
sumUnsignedQuantity :: forall (s :: Nat).
KnownNat s =>
[UnsignedQuantity s] -> UnsignedQuantity s
sumUnsignedQuantity = forall p x. Predicate p x => x -> Refined p x
unsafeRefine forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall p x. Refined p x -> x
unrefine
absQuantity
:: KnownNat s
=> Quantity s
-> UnsignedQuantity s
absQuantity :: forall (s :: Nat). KnownNat s => Quantity s -> UnsignedQuantity s
absQuantity = forall p x. Predicate p x => x -> Refined p x
unsafeRefine forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a
abs
mkQuantityAux :: forall s. KnownNat s => Scientific -> Quantity s
mkQuantityAux :: forall (s :: Nat). KnownNat s => Scientific -> Quantity s
mkQuantityAux Scientific
x = forall b a. b -> Either a b -> b
fromRight forall {a}. a
err forall a b. (a -> b) -> a -> b
$ forall (s :: Nat) (m :: * -> *).
(KnownNat s, MonadError String m) =>
Scientific -> m (Quantity s)
mkQuantityLossless (Int -> Scientific -> Scientific
roundScientific Int
nof Scientific
x)
where
nof :: Int
nof = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
err :: a
err = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"PROGRAMMING ERROR: Can not construct 'Quantity " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Int
nof forall a. Semigroup a => a -> a -> a
<> String
"' with '" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Scientific
x forall a. Semigroup a => a -> a -> a
<> String
"' in a lossy way."
roundScientific :: Int -> Scientific -> Scientific
roundScientific :: Int -> Scientific -> Scientific
roundScientific = (forall a. Read a => String -> a
read forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FPFormat -> Maybe Int -> Scientific -> String
formatScientific FPFormat
Fixed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just