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
11 -- import Control.Applicative (Const(..))
12 import Control.Exception (assert)
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)
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
35 -- * Requirements' interface
39 ( Data (Amount_Unit a)
41 , Show (Amount_Unit a)
42 , Typeable (Amount_Unit a)
45 amount_null :: a -> Bool
46 amount_add :: a -> a -> a
47 amount_negate :: a -> a
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
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
59 {- NOTE: not needed so far.
60 instance (Amount amount, unit ~ Amount_Unit amount)
61 => Posting (Account, Map unit amount)
63 type Posting_Amount (Account, Map unit amount) = amount
66 posting_set_amounts amounts (acct, _) = (acct, amounts)
69 instance (Amount amount)
70 => Posting (Account, Account_Sum amount)
72 type Posting_Amount (Account, Account_Sum amount) = amount
74 posting_amounts (_, Account_Sum x) = x
75 posting_set_amounts amounts (acct, _) = (acct, Account_Sum amounts)
79 -- | Sum by 'Account' and sum by 'unit' of some 'Posting's.
81 -- NOTE: to reduce memory consumption when 'cons'ing iteratively,
82 -- the fields are explicitely stricts.
86 { balance_by_account :: !(Balance_by_Account amount)
87 , balance_by_unit :: !(Balance_by_Unit amount)
89 deriving instance ( Amount amount
91 ) => Data (Balance amount)
92 deriving instance ( Amount amount
94 ) => Eq (Balance amount)
95 deriving instance ( Amount amount
97 ) => Show (Balance amount)
98 deriving instance Typeable1 Balance
99 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
101 instance Amount amount => Monoid (Balance amount) where
105 -- ** Type 'Balance_by_Account'
106 type Balance_by_Account amount
107 = TreeMap Account.Name
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
120 ) => Data (Account_Sum amount)
121 deriving instance ( Amount amount
123 ) => Eq (Account_Sum amount)
124 deriving instance ( Amount amount
126 ) => Show (Account_Sum amount)
127 deriving instance Typeable1 Account_Sum
128 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
130 instance Amount amount
131 => Monoid (Account_Sum amount) where
132 mempty = Account_Sum mempty
136 Account_Sum $ Data.Map.unionWith amount_add a0 a1
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
144 ) => Data (Balance_by_Unit amount)
145 deriving instance ( Amount amount
147 ) => Eq (Balance_by_Unit amount)
148 deriving instance ( Amount amount
150 ) => Show (Balance_by_Unit amount)
151 deriving instance Typeable1 Balance_by_Unit
152 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
154 instance Amount amount
155 => Monoid (Balance_by_Unit amount) where
156 mempty = Balance_by_Unit mempty
157 mappend = union_by_unit
159 -- *** Type 'Unit_Sum'
161 -- | A sum of 'amount's with their 'Account's involved,
162 -- concerning a single 'unit'.
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)
171 empty :: Amount amount => Balance amount
174 { balance_by_account = mempty
175 , balance_by_unit = mempty
178 -- | Return the given 'Balance'
179 -- updated by the given 'Posting'.
182 , balance ~ Balance (Posting_Amount posting) )
183 => posting -> balance -> balance
186 { balance_by_account = cons_by_account post (balance_by_account bal)
187 , balance_by_unit = cons_by_unit post (balance_by_unit bal)
190 -- | Return the given 'Balance'
191 -- updated by the given 'Posting's.
194 , balance ~ Balance (Posting_Amount posting)
195 , Foldable foldable )
196 => foldable posting -> balance -> balance
197 postings = flip (Data.Foldable.foldr cons)
199 -- | Return the first given 'Balance'
200 -- updated by the second given 'Balance'.
201 union :: Amount amount
202 => Balance amount -> Balance amount -> Balance amount
207 { balance_by_account = union_by_account b0a b1a
208 , balance_by_unit = union_by_unit b0u b1u
211 -- | Return the given 'Balance_by_Account'
212 -- updated by the given 'Posting'.
215 , amount ~ Posting_Amount posting
216 , unit ~ Amount_Unit amount
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)
226 -- | Return the given 'Balance_by_Unit'
227 -- updated by the given 'Posting'.
230 , amount ~ Posting_Amount posting
231 , unit ~ Amount_Unit amount )
233 -> Balance_by_Unit amount
234 -> Balance_by_Unit amount
240 { unit_sum_amount = amount
241 , unit_sum_accounts = Data.Map.singleton (posting_account post) ()
243 (posting_amounts post)
245 -- | Return a 'Balance_by_Unit'
246 -- derived from the given 'Balance_by_Account'.
247 by_unit_of_by_account ::
249 , unit ~ Amount_Unit amount
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
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
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
273 (Balance_by_Unit a1) =
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
282 (unit_sum_accounts old)
283 (unit_sum_accounts new)
287 -- * Type 'Deviation'
289 -- | The 'Balance_by_Unit' whose 'unit_sum_amount'
290 -- is not zero and possible 'Account' to 'infer_equilibrium'.
291 newtype Amount amount
293 = Deviation (Balance_by_Unit amount)
294 deriving instance ( Amount amount
296 ) => Data (Deviation amount)
297 deriving instance ( Amount amount
299 ) => Eq (Deviation amount)
300 deriving instance ( Amount amount
302 ) => Show (Deviation amount)
303 deriving instance Typeable1 Deviation
304 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
306 -- | Return the 'balance_by_unit' of the given 'Balance' with:
308 -- * 'unit's whose 'unit_sum_amount' verifying 'amount_is_zero' removed,
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').
318 { balance_by_account=ba
319 , balance_by_unit=Balance_by_Unit bu
321 let all_accounts = Lib.TreeMap.flatten (const ()) ba
322 let max_accounts = Data.Map.size all_accounts
324 Data.Map.foldlWithKey
325 (\(Balance_by_Unit m) unit Unit_Sum{unit_sum_amount, unit_sum_accounts} ->
327 if amount_null unit_sum_amount
330 case Data.Map.size unit_sum_accounts of
331 n | n == max_accounts ->
332 Data.Map.insert unit Unit_Sum
334 , unit_sum_accounts = Data.Map.empty
337 let diff = Data.Map.difference all_accounts unit_sum_accounts
338 Data.Map.insert unit Unit_Sum
340 , unit_sum_accounts = diff
346 -- ** The equilibrium
348 -- | Return the 'Balance' (adjusted by inferred 'Amount's)
349 -- of the given 'Posting's and either:
351 -- * 'Left': the 'Posting's that cannot be inferred.
352 -- * 'Right': the given 'Posting's with inferred 'Amount's inserted.
355 => Map Account [posting]
356 -> ( Balance (Posting_Amount posting)
357 , Either [Unit_Sum (Posting_Amount posting)] (Map Account [posting])
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})
366 case Data.Map.size unit_sum_accounts of
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
374 _ -> (bal, Left [unit_sum] : lr))
377 let (l, r) = Lib.Foldable.accumLeftsAndFoldrRights
378 (\(acct, unit, amt) ->
380 (\_new_ps -> insert_amount (unit, amt))
381 acct (assert False []))
384 [] -> (bal_adjusted, Right r)
385 _ -> (bal_adjusted, Left l)
389 => (Amount_Unit (Posting_Amount posting), Posting_Amount posting)
390 -> [posting] -> [posting]
391 insert_amount p@(unit, amt) ps =
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
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
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)) =
413 (\Unit_Sum{unit_sum_accounts} -> Data.Map.size unit_sum_accounts == 1)
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)) =
422 (\Unit_Sum{unit_sum_accounts} -> Data.Map.size unit_sum_accounts > 1)
427 -- | Descending propagation of 'Amount's accross 'Account's.
429 = TreeMap Account.Name (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'
435 deriving instance ( Amount amount
437 ) => Data (Account_Sum_Expanded amount)
438 deriving instance ( Amount amount
440 ) => Eq (Account_Sum_Expanded amount)
441 deriving instance ( Amount amount
443 ) => Show (Account_Sum_Expanded amount)
444 deriving instance Typeable1 Account_Sum_Expanded
445 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
447 instance Amount amount => Monoid (Account_Sum_Expanded amount) where
448 mempty = Account_Sum_Expanded mempty mempty
450 (Account_Sum_Expanded e0 i0)
451 (Account_Sum_Expanded e1 i1) =
456 -- | Return the given 'Balance_by_Account' with:
458 -- * all missing 'Account.ascending' 'Account's inserted,
460 -- * and every mapped 'Amount'
461 -- added with any 'Amount'
462 -- of the 'Account's for which it is 'Account.ascending'.
465 => Balance_by_Account amount
468 Lib.TreeMap.map_by_depth_first
469 (\descendants value ->
470 let exclusive = Strict.fromMaybe mempty value in
475 ( flip $ mappend . inclusive
476 . Strict.fromMaybe (assert False undefined)
477 . Lib.TreeMap.node_value)
479 Lib.TreeMap.nodes descendants
482 -- | Return a 'Balance_by_Unit'
483 -- derived from the given 'Expanded' balance.
485 -- NOTE: also correct if the 'Expanded' has been filtered.
486 by_unit_of_expanded ::
488 , unit ~ Amount_Unit amount
491 -> Balance_by_Unit amount
492 -> Balance_by_Unit amount
493 by_unit_of_expanded =
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 ->
500 Strict.Nothing -> go (k:p) node_descendants acc
502 let account = Lib.TreeMap.reverse $ Lib.TreeMap.path k p in
503 cons_by_unit (account, inclusive a) acc)