1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE DeriveFunctor #-}
3 {-# LANGUAGE StandaloneDeriving #-}
4 {-# LANGUAGE UndecidableInstances #-}
5 {-# OPTIONS_GHC -fno-warn-orphans #-}
6 module Hcompta.Quantity where
8 import Control.DeepSeq (NFData(..))
10 import Data.Data (Data)
11 import Data.Decimal (Decimal, DecimalRaw(..), roundTo)
12 import Data.Eq (Eq(..))
13 import Data.Function (const, flip)
14 import Data.Functor (Functor(..), (<$>))
15 import Data.Map.Strict (Map)
16 import Data.Maybe (Maybe(..))
17 import Data.Ord (Ord(..), Ordering(..))
18 import Data.Semigroup (Semigroup(..))
19 import Data.Sequence (Seq)
20 import Data.TreeMap.Strict (TreeMap)
21 import Data.Tuple (curry, uncurry)
22 import Data.Typeable (Typeable)
23 import Data.Word (Word8)
24 import Prelude (Integer, Integral, fromIntegral, seq)
25 import Text.Show (Show(..))
26 import qualified Data.Foldable as Foldable
27 import qualified Data.List as L
28 import qualified Data.Map.Strict as Map
29 import qualified Data.Sequence as Seq
30 import qualified Data.TreeMap.Strict as TM
31 import qualified Prelude
34 class Zeroable a where
37 instance Zeroable () where
39 instance Zeroable Integer where
41 instance Zeroable Decimal where
43 instance Zeroable (Seq a) where
45 instance Zeroable [a] where
47 instance Zeroable (Map k a) where
49 instance Zeroable (TreeMap k a) where
53 class Zeroable a => Nullable a where
55 default null :: Eq a => a -> Bool
58 instance Nullable Integer where
60 instance Nullable Decimal where
62 instance Nullable [a] where
64 instance Nullable (Seq a) where
66 instance Nullable a => Nullable (Map k a) where
67 null = Foldable.all null
68 instance Nullable (TreeMap k a) where
72 class Signable a where
74 default sign :: (Nullable a, Ord a) => a -> Ordering
81 instance Signable Integer
82 instance Signable Decimal
86 (+) :: a -> a -> a; infixl 6 +
87 instance Addable () where
89 instance Addable Integer where
91 instance Addable Decimal where
93 Decimal e (fromIntegral (nx Prelude.+ ny))
94 where (e, nx, ny) = roundMinDecimal x y
95 instance Addable [a] where
97 instance Addable (Seq a) where
99 instance (Ord k, Addable a) => Addable (Map k a) where
100 (+) = Map.unionWith (flip (+))
101 instance (Ord k, Addable a) => Addable (TreeMap k a) where
105 class Negable a where
107 instance Negable Integer where
109 instance Negable Decimal where
111 instance Negable a => Negable (Map k a) where
115 class Subable a where
116 (-) :: a -> a -> a; infixl 6 -
117 instance Subable Integer where
119 instance Subable Decimal where
121 instance (Ord k, Addable a, Negable a) => Subable (Map k a) where
122 (-) x y = Map.unionWith (flip (+)) x (neg y)
125 class Sumable s a where
126 (+=) :: s -> a -> s; infix 4 +=
128 default sum :: Zeroable s => a -> s
130 instance (Sumable s a, Zeroable s) => Sumable s [a] where
131 (+=) = Foldable.foldr (flip (+=))
133 instance (Ord k, Addable a) => Sumable (TreeMap k a) (TM.Path k, a) where
134 (+=) = flip (uncurry (TM.insert (flip (+))))
135 instance (Ord k, Addable a, Sumable (Map k b) (TM.Path k, a)) =>
136 Sumable (Map k b) (TreeMap k a) where
137 (+=) = TM.foldr_with_Path (curry (flip (+=)))
139 -- * Class 'Polarizable'
140 class Polarizable a where
141 negativeOf :: a -> Maybe a
142 positiveOf :: a -> Maybe a
143 instance Polarizable Integer where
150 _ | q <= 0 -> Nothing
152 instance Polarizable Decimal where
159 _ | q <= 0 -> Nothing
161 instance Polarizable (Polarized a) where
164 PolNegative _ -> Just qty
165 PolPositive _ -> Nothing
166 PolBoth n _ -> Just (PolNegative n)
169 PolNegative _ -> Nothing
170 PolPositive _ -> Just qty
171 PolBoth _ p -> Just (PolPositive p)
172 instance Polarizable a => Polarizable (Map k a) where
174 case Map.mapMaybe positiveOf q of
175 m | Map.null m -> Nothing
178 case Map.mapMaybe negativeOf q of
179 m | Map.null m -> Nothing
181 instance Polarizable a => Polarizable (k, a) where
182 positiveOf (u, q) = (u,) <$> positiveOf q
183 negativeOf (u, q) = (u,) <$> negativeOf q
185 -- ** Type 'Polarized'
186 -- | Polarize a quantity to distinctively keep track
187 -- of negative and positive ones.
192 deriving (Data, Eq, Functor, Ord, Show, Typeable)
193 instance NFData a => NFData (Polarized a) where
194 rnf (PolNegative n) = rnf n
195 rnf (PolPositive p) = rnf p
196 rnf (PolBoth n p) = rnf n `seq` rnf p
197 instance Zeroable a => Zeroable (Polarized a) where
198 zero = PolPositive zero
199 instance (Nullable a, Addable a) => Nullable (Polarized a) where
202 PolNegative n -> null n
203 PolPositive p -> null p
204 PolBoth n p -> null (n + p)
205 instance Addable a => Addable (Polarized a) where
206 PolNegative nx + PolNegative ny = PolNegative (nx + ny)
207 PolNegative n + PolPositive p = PolBoth n p
208 PolNegative nx + PolBoth ny p = PolBoth (nx + ny) p
210 PolPositive p + PolNegative n = PolBoth n p
211 PolPositive px + PolPositive py = PolPositive (px + py)
212 PolPositive p + PolBoth ny py = PolBoth ny (p + py)
214 PolBoth nx px + PolNegative n = PolBoth (nx + n) px
215 PolBoth nx px + PolPositive py = PolBoth nx (px + py)
216 PolBoth nx px + PolBoth ny py = PolBoth (nx + ny) (px + py)
217 instance Negable a => Negable (Polarized a) where
218 neg (PolNegative n) = PolPositive (neg n)
219 neg (PolPositive p) = PolNegative (neg p)
220 neg (PolBoth n p) = PolBoth (neg p) (neg n)
222 unNegative :: Polarized a -> Maybe a
225 PolNegative n -> Just n
226 PolPositive _ -> Nothing
227 PolBoth n _ -> Just n
229 unPositive :: Polarized a -> Maybe a
232 PolNegative _ -> Nothing
233 PolPositive p -> Just p
234 PolBoth _ p -> Just p
236 polarize :: Polarizable a => a -> Polarized a
238 case (negativeOf qty, positiveOf qty) of
239 (Just n, Nothing) -> PolNegative n
240 (Nothing, Just p) -> PolPositive p
241 (Just n, Just p) -> PolBoth n p
242 (Nothing, Nothing) -> PolBoth qty qty
243 depolarize :: Addable a => Polarized a -> a
253 deriving instance Data Decimal
255 -- | Round the two 'DecimalRaw' values to the smallest exponent.
256 roundMinDecimal :: Integral i => DecimalRaw i -> DecimalRaw i -> (Word8, i, i)
257 roundMinDecimal d1@(Decimal e1 _) d2@(Decimal e2 _) = (e, n1, n2)
260 Decimal _ n1 = roundTo e d1
261 Decimal _ n2 = roundTo e d2