]> Git — Sourcephile - comptalang.git/blob - lib/Hcompta/Balance.hs
Ajout : Hcompta.Chart.
[comptalang.git] / lib / Hcompta / Balance.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE NamedFieldPuns #-}
6 {-# LANGUAGE StandaloneDeriving #-}
7 {-# LANGUAGE TypeFamilies #-}
8 {-# OPTIONS_GHC -fno-warn-deprecations #-} -- FIXME: to be removed when dropping GHC-7.6 support
9 module Hcompta.Balance where
10
11 -- import Control.Applicative (Const(..))
12 import Control.Exception (assert)
13 import Data.Bool
14 import Data.Data
15 import Data.Either (Either(..))
16 import Data.Eq (Eq(..))
17 import Data.Ord (Ord(..))
18 import qualified Data.Foldable
19 import Data.Foldable (Foldable(..))
20 import qualified Data.Map.Strict as Data.Map
21 import Data.Map.Strict (Map)
22 import Data.Monoid (Monoid(..))
23 import qualified Data.Strict.Maybe as Strict
24 import Data.Typeable ()
25 import Text.Show (Show(..))
26 import Prelude (($), (.), const, curry, flip, fst, undefined)
27
28 import Hcompta.Account (Account)
29 import qualified Hcompta.Account as Account
30 -- import Hcompta.Lib.Consable (Consable(..))
31 import qualified Hcompta.Lib.Foldable as Lib.Foldable
32 import Hcompta.Lib.TreeMap (TreeMap)
33 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
34
35 -- * Requirements' interface
36
37 -- ** Class 'Amount'
38 class
39 ( Data (Amount_Unit a)
40 , Ord (Amount_Unit a)
41 , Show (Amount_Unit a)
42 , Typeable (Amount_Unit a)
43 ) => Amount a where
44 type Amount_Unit a
45 amount_null :: a -> Bool
46 amount_add :: a -> a -> a
47 amount_negate :: a -> a
48
49 -- ** Class 'Posting'
50
51 -- | A 'posting' used to produce a 'Balance'
52 -- must be an instance of this class.
53 class Amount (Posting_Amount p) => Posting p where
54 type Posting_Amount p
55 posting_account :: p -> Account
56 posting_amounts :: p -> Map (Amount_Unit (Posting_Amount p)) (Posting_Amount p)
57 posting_set_amounts :: Map (Amount_Unit (Posting_Amount p)) (Posting_Amount p) -> p -> p
58
59 {- NOTE: not needed so far.
60 instance (Amount amount, unit ~ Amount_Unit amount)
61 => Posting (Account, Map unit amount)
62 where
63 type Posting_Amount (Account, Map unit amount) = amount
64 posting_account = fst
65 posting_amounts = snd
66 posting_set_amounts amounts (acct, _) = (acct, amounts)
67 -}
68
69 instance (Amount amount)
70 => Posting (Account, Account_Sum amount)
71 where
72 type Posting_Amount (Account, Account_Sum amount) = amount
73 posting_account = fst
74 posting_amounts (_, Account_Sum x) = x
75 posting_set_amounts amounts (acct, _) = (acct, Account_Sum amounts)
76
77 -- * Type 'Balance'
78
79 -- | Sum by 'Account' and sum by 'unit' of some 'Posting's.
80 --
81 -- NOTE: to reduce memory consumption when 'cons'ing iteratively,
82 -- the fields are explicitely stricts.
83 data Amount amount
84 => Balance amount
85 = Balance
86 { balance_by_account :: !(Balance_by_Account amount)
87 , balance_by_unit :: !(Balance_by_Unit amount)
88 }
89 deriving instance ( Amount amount
90 , Data amount
91 ) => Data (Balance amount)
92 deriving instance ( Amount amount
93 , Eq amount
94 ) => Eq (Balance amount)
95 deriving instance ( Amount amount
96 , Show amount
97 ) => Show (Balance amount)
98 deriving instance Typeable1 Balance
99 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
100
101 instance Amount amount => Monoid (Balance amount) where
102 mempty = empty
103 mappend = union
104
105 -- ** Type 'Balance_by_Account'
106 type Balance_by_Account amount
107 = TreeMap Account.Account_Section
108 (Account_Sum amount)
109
110 -- *** Type 'Account_Sum'
111 -- | A sum of 'amount's,
112 -- concerning a single 'Account'.
113 newtype Amount amount
114 => Account_Sum amount
115 = Account_Sum (Map (Amount_Unit amount) amount)
116 get_Account_Sum :: Amount amount => Account_Sum amount -> Map (Amount_Unit amount) amount
117 get_Account_Sum (Account_Sum m) = m
118 deriving instance ( Amount amount
119 , Data amount
120 ) => Data (Account_Sum amount)
121 deriving instance ( Amount amount
122 , Eq amount
123 ) => Eq (Account_Sum amount)
124 deriving instance ( Amount amount
125 , Show amount
126 ) => Show (Account_Sum amount)
127 deriving instance Typeable1 Account_Sum
128 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
129
130 instance Amount amount
131 => Monoid (Account_Sum amount) where
132 mempty = Account_Sum mempty
133 mappend
134 (Account_Sum a0)
135 (Account_Sum a1) =
136 Account_Sum $ Data.Map.unionWith amount_add a0 a1
137
138 -- ** Type 'Balance_by_Unit'
139 newtype Amount amount
140 => Balance_by_Unit amount
141 = Balance_by_Unit (Map (Amount_Unit amount) (Unit_Sum amount))
142 deriving instance ( Amount amount
143 , Data amount
144 ) => Data (Balance_by_Unit amount)
145 deriving instance ( Amount amount
146 , Eq amount
147 ) => Eq (Balance_by_Unit amount)
148 deriving instance ( Amount amount
149 , Show amount
150 ) => Show (Balance_by_Unit amount)
151 deriving instance Typeable1 Balance_by_Unit
152 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
153
154 instance Amount amount
155 => Monoid (Balance_by_Unit amount) where
156 mempty = Balance_by_Unit mempty
157 mappend = union_by_unit
158
159 -- *** Type 'Unit_Sum'
160
161 -- | A sum of 'amount's with their 'Account's involved,
162 -- concerning a single 'unit'.
163 data Unit_Sum amount
164 = Unit_Sum
165 { unit_sum_amount :: !amount -- ^ The sum of 'amount's for a single 'unit'.
166 , unit_sum_accounts :: !(Map Account ()) -- ^ The 'Account's involved to build 'unit_sum_amount'.
167 } deriving (Data, Eq, Show, Typeable)
168
169 -- ** Constructors
170
171 empty :: Amount amount => Balance amount
172 empty =
173 Balance
174 { balance_by_account = mempty
175 , balance_by_unit = mempty
176 }
177
178 -- | Return the given 'Balance'
179 -- updated by the given 'Posting'.
180 cons ::
181 ( Posting posting
182 , balance ~ Balance (Posting_Amount posting) )
183 => posting -> balance -> balance
184 cons post bal =
185 bal
186 { balance_by_account = cons_by_account post (balance_by_account bal)
187 , balance_by_unit = cons_by_unit post (balance_by_unit bal)
188 }
189
190 -- | Return the given 'Balance'
191 -- updated by the given 'Posting's.
192 postings ::
193 ( Posting posting
194 , balance ~ Balance (Posting_Amount posting)
195 , Foldable foldable )
196 => foldable posting -> balance -> balance
197 postings = flip (Data.Foldable.foldr cons)
198
199 -- | Return the first given 'Balance'
200 -- updated by the second given 'Balance'.
201 union :: Amount amount
202 => Balance amount -> Balance amount -> Balance amount
203 union
204 (Balance b0a b0u)
205 (Balance b1a b1u) =
206 Balance
207 { balance_by_account = union_by_account b0a b1a
208 , balance_by_unit = union_by_unit b0u b1u
209 }
210
211 -- | Return the given 'Balance_by_Account'
212 -- updated by the given 'Posting'.
213 cons_by_account ::
214 ( Posting posting
215 , amount ~ Posting_Amount posting
216 , unit ~ Amount_Unit amount
217 )
218 => posting
219 -> Balance_by_Account amount
220 -> Balance_by_Account amount
221 cons_by_account post =
222 Lib.TreeMap.insert mappend
223 (posting_account post)
224 (Account_Sum $ posting_amounts post)
225
226 -- | Return the given 'Balance_by_Unit'
227 -- updated by the given 'Posting'.
228 cons_by_unit ::
229 ( Posting posting
230 , amount ~ Posting_Amount posting
231 , unit ~ Amount_Unit amount )
232 => posting
233 -> Balance_by_Unit amount
234 -> Balance_by_Unit amount
235 cons_by_unit post =
236 union_by_unit $
237 Balance_by_Unit $
238 Data.Map.map
239 (\amount -> Unit_Sum
240 { unit_sum_amount = amount
241 , unit_sum_accounts = Data.Map.singleton (posting_account post) ()
242 })
243 (posting_amounts post)
244
245 -- | Return a 'Balance_by_Unit'
246 -- derived from the given 'Balance_by_Account'.
247 by_unit_of_by_account ::
248 ( Amount amount
249 , unit ~ Amount_Unit amount
250 )
251 => Balance_by_Account amount
252 -> Balance_by_Unit amount
253 -> Balance_by_Unit amount
254 by_unit_of_by_account =
255 flip $ Lib.TreeMap.foldr_with_Path $ curry cons_by_unit
256
257 -- | Return the first given 'Balance_by_Account'
258 -- updated by the second given 'Balance_by_Account'.
259 union_by_account :: Amount amount
260 => Balance_by_Account amount
261 -> Balance_by_Account amount
262 -> Balance_by_Account amount
263 union_by_account = Lib.TreeMap.union mappend
264
265 -- | Return the first given 'Balance_by_Unit'
266 -- updated by the second given 'Balance_by_Unit'.
267 union_by_unit :: (Amount amount, unit ~ Amount_Unit amount)
268 => Balance_by_Unit amount
269 -> Balance_by_Unit amount
270 -> Balance_by_Unit amount
271 union_by_unit
272 (Balance_by_Unit a0)
273 (Balance_by_Unit a1) =
274 Balance_by_Unit $
275 Data.Map.unionWith
276 (\new old -> Unit_Sum
277 { unit_sum_amount = amount_add
278 (unit_sum_amount old)
279 (unit_sum_amount new)
280 , unit_sum_accounts = Data.Map.unionWith
281 (const::()->()->())
282 (unit_sum_accounts old)
283 (unit_sum_accounts new)
284 })
285 a0 a1
286
287 -- * Type 'Deviation'
288
289 -- | The 'Balance_by_Unit' whose 'unit_sum_amount'
290 -- is not zero and possible 'Account' to 'infer_equilibrium'.
291 newtype Amount amount
292 => Deviation amount
293 = Deviation (Balance_by_Unit amount)
294 deriving instance ( Amount amount
295 , Data amount
296 ) => Data (Deviation amount)
297 deriving instance ( Amount amount
298 , Eq amount
299 ) => Eq (Deviation amount)
300 deriving instance ( Amount amount
301 , Show amount
302 ) => Show (Deviation amount)
303 deriving instance Typeable1 Deviation
304 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
305
306 -- | Return the 'balance_by_unit' of the given 'Balance' with:
307 --
308 -- * 'unit's whose 'unit_sum_amount' verifying 'amount_is_zero' removed,
309 --
310 -- * and remaining 'unit's having their 'unit_sum_accounts'
311 -- complemented with the 'balance_by_account' of the given 'Balance'
312 -- (i.e. now mapping to 'Account's __not__ involved to build the 'Unit_Sum').
313 deviation
314 :: Amount amount
315 => Balance amount
316 -> Deviation amount
317 deviation Balance
318 { balance_by_account=ba
319 , balance_by_unit=Balance_by_Unit bu
320 } = do
321 let all_accounts = Lib.TreeMap.flatten (const ()) ba
322 let max_accounts = Data.Map.size all_accounts
323 Deviation $
324 Data.Map.foldlWithKey
325 (\(Balance_by_Unit m) unit Unit_Sum{unit_sum_amount, unit_sum_accounts} ->
326 Balance_by_Unit $
327 if amount_null unit_sum_amount
328 then m
329 else
330 case Data.Map.size unit_sum_accounts of
331 n | n == max_accounts ->
332 Data.Map.insert unit Unit_Sum
333 { unit_sum_amount
334 , unit_sum_accounts = Data.Map.empty
335 } m
336 _ -> do
337 let diff = Data.Map.difference all_accounts unit_sum_accounts
338 Data.Map.insert unit Unit_Sum
339 { unit_sum_amount
340 , unit_sum_accounts = diff
341 } m
342 )
343 mempty
344 bu
345
346 -- ** The equilibrium
347
348 -- | Return the 'Balance' (adjusted by inferred 'Amount's)
349 -- of the given 'Posting's and either:
350 --
351 -- * 'Left': the 'Posting's that cannot be inferred.
352 -- * 'Right': the given 'Posting's with inferred 'Amount's inserted.
353 infer_equilibrium ::
354 ( Posting posting )
355 => Map Account [posting]
356 -> ( Balance (Posting_Amount posting)
357 , Either [Unit_Sum (Posting_Amount posting)] (Map Account [posting])
358 )
359 infer_equilibrium posts = do
360 let bal_initial = Data.Foldable.foldr postings empty posts
361 let Deviation (Balance_by_Unit dev) = deviation bal_initial
362 let (bal_adjusted, eithers) =
363 Data.Map.foldrWithKey
364 (\unit unit_sum@(Unit_Sum{unit_sum_amount, unit_sum_accounts})
365 (bal, lr) ->
366 case Data.Map.size unit_sum_accounts of
367 1 ->
368 let acct = fst $ Data.Map.elemAt 0 unit_sum_accounts in
369 let amt = amount_negate unit_sum_amount in
370 let amts = Data.Map.singleton unit amt in
371 ( cons (acct, Account_Sum amts) bal
372 , Right (acct, unit, amt) : lr
373 )
374 _ -> (bal, Left [unit_sum] : lr))
375 (bal_initial, [])
376 dev
377 let (l, r) = Lib.Foldable.accumLeftsAndFoldrRights
378 (\(acct, unit, amt) ->
379 Data.Map.insertWith
380 (\_new_ps -> insert_amount (unit, amt))
381 acct (assert False []))
382 posts eithers
383 case l of
384 [] -> (bal_adjusted, Right r)
385 _ -> (bal_adjusted, Left l)
386 where
387 insert_amount
388 :: Posting posting
389 => (Amount_Unit (Posting_Amount posting), Posting_Amount posting)
390 -> [posting] -> [posting]
391 insert_amount p@(unit, amt) ps =
392 case ps of
393 [] -> assert False []
394 (x:xs) | Data.Map.null (posting_amounts x) ->
395 posting_set_amounts (Data.Map.singleton unit amt) x:xs
396 | Data.Map.notMember unit (posting_amounts x) ->
397 let amts = Data.Map.insertWith
398 (assert False undefined)
399 unit amt (posting_amounts x) in
400 posting_set_amounts amts x:xs
401 (x:xs) -> x:insert_amount p xs
402
403 -- | Return 'True' if and only if the given 'Deviation' maps no 'unit'.
404 is_at_equilibrium :: Amount amount => Deviation amount -> Bool
405 is_at_equilibrium (Deviation (Balance_by_Unit dev)) = Data.Map.null dev
406
407 -- | Return 'True' if and only if the given 'Deviation'
408 -- maps only to 'Unit_Sum's whose 'unit_sum_accounts'
409 -- maps exactly one 'Account'.
410 is_equilibrium_inferrable :: Amount amount => Deviation amount -> Bool
411 is_equilibrium_inferrable (Deviation (Balance_by_Unit dev)) =
412 Data.Foldable.all
413 (\Unit_Sum{unit_sum_accounts} -> Data.Map.size unit_sum_accounts == 1)
414 dev
415
416 -- | Return 'True' if and only if the given 'Deviation'
417 -- maps to at least one 'Unit_Sum' whose 'unit_sum_accounts'
418 -- maps more than one 'Account'.
419 is_equilibrium_non_inferrable :: Amount amount => Deviation amount -> Bool
420 is_equilibrium_non_inferrable (Deviation (Balance_by_Unit dev)) =
421 Data.Foldable.any
422 (\Unit_Sum{unit_sum_accounts} -> Data.Map.size unit_sum_accounts > 1)
423 dev
424
425 -- * Type 'Expanded'
426
427 -- | Descending propagation of 'Amount's accross 'Account's.
428 type Expanded amount
429 = TreeMap Account.Account_Section (Account_Sum_Expanded amount)
430 data Amount amount => Account_Sum_Expanded amount
431 = Account_Sum_Expanded
432 { exclusive :: !(Account_Sum amount)
433 , inclusive :: !(Account_Sum amount) -- ^ 'amount_add' folded over 'exclusive' and 'inclusive' of 'Lib.TreeMap.node_descendants'
434 }
435 deriving instance ( Amount amount
436 , Data amount
437 ) => Data (Account_Sum_Expanded amount)
438 deriving instance ( Amount amount
439 , Eq amount
440 ) => Eq (Account_Sum_Expanded amount)
441 deriving instance ( Amount amount
442 , Show amount
443 ) => Show (Account_Sum_Expanded amount)
444 deriving instance Typeable1 Account_Sum_Expanded
445 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
446
447 instance Amount amount => Monoid (Account_Sum_Expanded amount) where
448 mempty = Account_Sum_Expanded mempty mempty
449 mappend
450 (Account_Sum_Expanded e0 i0)
451 (Account_Sum_Expanded e1 i1) =
452 Account_Sum_Expanded
453 (mappend e0 e1)
454 (mappend i0 i1)
455
456 -- | Return the given 'Balance_by_Account' with:
457 --
458 -- * all missing 'Account.ascending' 'Account's inserted,
459 --
460 -- * and every mapped 'Amount'
461 -- added with any 'Amount'
462 -- of the 'Account's for which it is 'Account.ascending'.
463 expanded
464 :: Amount amount
465 => Balance_by_Account amount
466 -> Expanded amount
467 expanded =
468 Lib.TreeMap.map_by_depth_first
469 (\descendants value ->
470 let exclusive = Strict.fromMaybe mempty value in
471 Account_Sum_Expanded
472 { exclusive
473 , inclusive =
474 Data.Map.foldl'
475 ( flip $ mappend . inclusive
476 . Strict.fromMaybe (assert False undefined)
477 . Lib.TreeMap.node_value )
478 exclusive $
479 Lib.TreeMap.nodes descendants
480 })
481
482 -- | Return a 'Balance_by_Unit'
483 -- derived from the given 'Expanded' balance.
484 --
485 -- NOTE: also correct if the 'Expanded' has been filtered.
486 by_unit_of_expanded ::
487 ( Amount amount
488 , unit ~ Amount_Unit amount
489 )
490 => Expanded amount
491 -> Balance_by_Unit amount
492 -> Balance_by_Unit amount
493 by_unit_of_expanded =
494 go []
495 where
496 go p (Lib.TreeMap.TreeMap m) bal =
497 Data.Map.foldrWithKey
498 (\k Lib.TreeMap.Node{Lib.TreeMap.node_value, Lib.TreeMap.node_descendants} acc ->
499 case node_value of
500 Strict.Nothing -> go (k:p) node_descendants acc
501 Strict.Just a ->
502 let account = Lib.TreeMap.reverse $ Lib.TreeMap.path k p in
503 cons_by_unit (account, inclusive a) acc)
504 bal m