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