1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE NamedFieldPuns #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 module Hcompta.Calc.Balance where
7 import qualified Data.Foldable
8 import qualified Data.List
9 import qualified Data.Map.Strict as Data.Map
10 import Data.Map.Strict (Map)
12 import Data.Typeable ()
13 import Data.Maybe (fromMaybe)
14 import qualified GHC.Num
16 import qualified Hcompta.Model as Model ()
17 import qualified Hcompta.Model.Account as Account
18 import qualified Hcompta.Lib.Foldable as Lib.Foldable
19 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
20 import Hcompta.Model.Account (Account)
21 import qualified Hcompta.Model.Amount as Amount
22 import Hcompta.Model.Amount (Amount, Unit)
23 import qualified Hcompta.Model.Transaction as Transaction
24 import Hcompta.Model.Transaction (Transaction, Posting)
25 import qualified Hcompta.Model.Transaction.Posting as Posting
26 import qualified Hcompta.Model.Journal as Journal
27 import Hcompta.Model.Journal (Journal)
29 -- * The 'Balance' type
31 -- | Sum by 'Account' and sum by 'Unit' of some 'Posting's.
34 { by_account :: By_Account
36 } deriving (Data, Eq, Read, Show, Typeable)
39 = Lib.TreeMap.TreeMap Account.Name Account_Sum
40 -- | A sum of 'Amount's,
41 -- concerning a single 'Account'.
46 = Map Amount.Unit Unit_Sum
47 -- | A sum of 'Amount's with their 'Account's involved,
48 -- concerning a single 'Unit'.
51 { amount :: Amount -- ^ The sum of 'Amount's for a single 'Unit'.
52 , accounts :: Map Account () -- ^ The 'Account's involved to build 'amount'.
53 } deriving (Data, Eq, Read, Show, Typeable)
60 { by_account = Lib.TreeMap.empty
61 , by_unit = Data.Map.empty
64 nil_By_Account :: By_Account
68 nil_By_Unit :: By_Unit
72 nil_Account_Sum :: Account_Sum
76 nil_Unit_Sum :: Unit_Sum
79 { accounts = Data.Map.empty
83 -- | Return a tuple associating the given 'Unit_Sum' with its 'Unit'.
84 assoc_unit_sum :: Unit_Sum -> (Unit, Unit_Sum)
85 assoc_unit_sum s = (Amount.unit $ amount s, s)
87 -- | Return a 'Map' associating the given 'Unit_Sum' with their respective 'Unit'.
88 by_Unit_from_List :: [Unit_Sum] -> By_Unit
89 by_Unit_from_List balances =
92 { amount=(GHC.Num.+) (amount x) (amount y)
93 , accounts=Data.Map.union (accounts x) (accounts y)
95 Data.List.map assoc_unit_sum balances
97 -- ** Incremental constructors
99 -- | Return the given 'Balance'
100 -- updated by the given 'Posting'.
101 posting :: Posting -> Balance -> Balance
102 posting post balance =
106 (Data.Map.unionWith (GHC.Num.+))
107 (Posting.account post)
108 (Posting.amounts post)
113 { amount = (GHC.Num.+) (amount x) (amount y)
114 , accounts = Data.Map.union (accounts x) (accounts y)
120 , accounts = Data.Map.singleton (Posting.account post) ()
122 (Posting.amounts post)
125 -- | Return the given 'Balance'
126 -- updated by the given 'Posting's.
127 postings :: (Foldable to, Foldable ti) => to (ti Posting) -> Balance -> Balance
128 postings = flip $ Data.Foldable.foldr (flip (Data.Foldable.foldr posting))
130 -- | Return the given 'Balance'
131 -- updated by the 'Transaction.postings'
132 -- of the given 'Transaction'.
133 transaction :: Transaction -> Balance -> Balance
134 transaction = postings . Transaction.postings
136 -- | Return the given 'Balance'
137 -- updated by the 'Transaction.postings'
138 -- and 'Transaction.virtual_postings'
139 -- and 'Transaction.balanced_virtual_postings'
140 -- of the given 'Transaction'.
141 transaction_with_virtual :: Transaction -> Balance -> Balance
142 transaction_with_virtual tr =
143 postings (Transaction.balanced_virtual_postings tr) .
144 postings (Transaction.virtual_postings tr) .
145 postings (Transaction.postings tr)
147 -- | Return the given 'Balance'
148 -- updated by the 'Transaction.balanced_virtual_postings' of the given 'Transaction'.
149 transaction_balanced_virtual :: Transaction -> Balance -> Balance
150 transaction_balanced_virtual =
151 postings . Transaction.balanced_virtual_postings
153 -- | Return the given 'Balance'
154 -- updated by the 'Journal.transactions'
155 -- of the given 'Journal',
156 -- through 'transaction'.
157 journal :: Journal -> Balance -> Balance
158 journal jour balance =
160 (Data.List.foldl (flip transaction))
162 (Journal.transactions jour)
164 -- | Return the given 'Balance'
165 -- updated by the 'Journal.transactions'
166 -- of the given 'Journal',
167 -- through 'transaction'.
168 journal_with_virtual :: Journal -> Balance -> Balance
169 journal_with_virtual jour balance =
171 (Data.List.foldl (flip transaction_with_virtual))
173 (Journal.transactions jour)
175 -- | Return the first given 'Balance'
176 -- updated by the second given 'Balance'.
177 union :: Balance -> Balance -> Balance
182 (Data.Map.unionWith (GHC.Num.+))
188 { amount = (GHC.Num.+) (amount x) (amount y)
189 , accounts = Data.Map.union (accounts x) (accounts y)
195 -- * The 'Deviation' type
197 -- | The 'By_Unit' whose 'Unit_Sum'sā 'amount'
198 -- is not zero and possible 'Account' to 'infer_equilibrium'.
201 deriving (Data, Eq, Read, Show, Typeable)
203 -- | Return the 'by_unit' of the given 'Balance' with:
205 -- * 'Unit's whose 'Unit_Sum' 'amount' verifying 'Amount.is_zero' removed,
207 -- * and remaining 'Unit's having their 'Unit_Sum' 'accounts'
208 -- complemented with the 'by_account' of the given 'Balance'
209 -- (i.e. now mapping to accounts __not__ involved to build the 'Unit_Sum').
210 deviation :: Balance -> Deviation
211 deviation balance = do
212 let all_accounts = Lib.TreeMap.flatten (const ()) (by_account balance)
213 let max_accounts = Data.Map.size all_accounts
215 Data.Map.foldlWithKey
216 (\m unit Unit_Sum{amount, accounts} ->
217 if Amount.is_zero amount
220 case Data.Map.size accounts of
221 n | n == max_accounts ->
222 Data.Map.insert unit Unit_Sum{amount, accounts=Data.Map.empty} m
224 let diff = Data.Map.difference all_accounts accounts
225 Data.Map.insert unit Unit_Sum{amount, accounts=diff} m
230 -- | Return the 'Balance' of the given 'Posting's and either:
232 -- * 'Left': the 'Posting's that cannot be inferred.
233 -- * 'Right': the given 'Posting's with inferred 'Amount's inserted.
235 :: Posting.By_Account
236 -> (Balance, Either [Unit_Sum] Posting.By_Account)
237 infer_equilibrium ps = do
238 let bal = postings ps nil
239 let Deviation dev = deviation bal
240 (\(l, r) -> (bal, case l of { [] -> Right r; _ -> Left l })) $ do
241 Lib.Foldable.accumLeftsAndFoldrRights
242 (\p -> Data.Map.insertWith
243 (\pn -> (++) pn . Data.List.filter (not . Data.Map.null . Posting.amounts))
244 (Posting.account p) [p])
247 (\unit_sum@(Unit_Sum{ amount=amt, accounts }) acc ->
248 case Data.Map.size accounts of
249 1 -> (Right $ (Posting.nil $ fst $ Data.Map.elemAt 0 accounts)
250 { Posting.amounts = Amount.from_List [negate amt] }):acc
251 _ -> Left [unit_sum]:acc)
257 -- | Return 'True' if and only if the given 'Deviation' maps no 'Unit'.
258 is_at_equilibrium :: Deviation -> Bool
259 is_at_equilibrium (Deviation dev) = Data.Map.null dev
261 -- | Return 'True' if and only if the given 'Deviation'
262 -- maps only to 'Unit_Sum's whose 'accounts'
263 -- maps exactly one 'Account'.
264 is_equilibrium_inferrable :: Deviation -> Bool
265 is_equilibrium_inferrable (Deviation dev) =
267 (\Unit_Sum{accounts} -> Data.Map.size accounts == 1)
270 -- | Return 'True' if and only if the given 'Deviation'
271 -- maps to at least one 'Unit_Sum's whose 'accounts'
272 -- maps more than one 'Account'.
273 is_equilibrium_non_inferrable :: Deviation -> Bool
274 is_equilibrium_non_inferrable (Deviation dev) =
276 (\Unit_Sum{accounts} -> Data.Map.size accounts > 1)
279 -- * The 'Expanded' type
281 -- | Descending propagation of 'Amount's accross 'Account's.
282 type Expanded = Lib.TreeMap.TreeMap Account.Name Account_Sum_Expanded
283 data Account_Sum_Expanded
284 = Account_Sum_Expanded
285 { inclusive :: Amount.By_Unit
286 , exclusive :: Amount.By_Unit
288 deriving (Data, Eq, Read, Show, Typeable)
290 -- | Return the given 'By_Account' with:
292 -- * all missing 'Account.ascending' 'Account's inserted,
294 -- * and every mapped Amount.'Amount.By_Unit'
295 -- added with any Amount.'Amount.By_Unit'
296 -- of the 'Account'sā for which it is 'Account.ascending'.
297 expanded :: By_Account -> Expanded
299 Lib.TreeMap.map_by_depth_first
300 (\descendants value ->
301 let exc = fromMaybe Data.Map.empty value in
306 ( Data.Map.unionWith (GHC.Num.+)
308 . fromMaybe (error "Oops, should not happen in: Hcompta.Calc.Balance.expanded")
309 . Lib.TreeMap.node_value) )
310 exc $ Lib.TreeMap.nodes $ descendants