Ajout : Hcompta.CLI
[comptalang.git] / lib / Hcompta / Calc / Balance.hs
index 06f0d9ecc29226192c8f92c252bb57e3523bd0bf..f37cf1613034800859d28a031ca4df46431cae9e 100644 (file)
@@ -1,4 +1,5 @@
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 module Hcompta.Calc.Balance where
 
@@ -105,20 +106,21 @@ posting post balance =
         , by_unit =
                Data.Map.unionWith
                 (\x y -> Sum_by_Unit
-                        { amount = (GHC.Num.+) (amount x) (amount y)
+                        { amount   = (GHC.Num.+) (amount x) (amount y)
                         , accounts = Data.Map.union (accounts x) (accounts y)
                         })
                 (by_unit balance) $
                Data.Map.map
-                (\amt -> Sum_by_Unit
-                        { amount=amt
-                        , accounts=Data.Map.singleton (Posting.account post) ()
+                (\amount -> Sum_by_Unit
+                        { amount
+                        , accounts = Data.Map.singleton (Posting.account post) ()
                         })
                 (Posting.amounts post)
         }
 
 -- | Return the given 'Balance'
---   updated by the 'Transaction.postings' of the given 'Transaction'.
+--   updated by the 'Transaction.postings'
+--   of the given 'Transaction'.
 transaction :: Transaction -> Balance -> Balance
 transaction tran balance =
        Data.Map.foldr
@@ -127,7 +129,30 @@ transaction tran balance =
         (Transaction.postings tran)
 
 -- | Return the given 'Balance'
---   updated by the 'Journal.transactions' of the given 'Journal'.
+--   updated by the 'Transaction.postings'
+--   and 'Transaction.virtual_postings'
+--   and 'Transaction.balanced_virtual_postings'
+--   of the given 'Transaction'.
+transaction_with_virtual :: Transaction -> Balance -> Balance
+transaction_with_virtual tran balance =
+       Data.Map.foldr
+        (flip (Data.List.foldl (flip posting)))
+        balance
+        (Transaction.postings tran)
+
+-- | Return the given 'Balance'
+--   updated by the 'Transaction.balanced_virtual_postings' of the given 'Transaction'.
+transaction_balanced_virtual :: Transaction -> Balance -> Balance
+transaction_balanced_virtual tran balance =
+       Data.Map.foldr
+        (flip (Data.List.foldl (flip posting)))
+        balance
+        (Transaction.balanced_virtual_postings tran)
+
+-- | Return the given 'Balance'
+--   updated by the 'Journal.transactions'
+--   of the given 'Journal',
+--   through 'transactions'.
 journal :: Journal -> Balance -> Balance
 journal jour balance =
        Data.Map.foldl
@@ -135,6 +160,17 @@ journal jour balance =
         balance
         (Journal.transactions jour)
 
+-- | Return the given 'Balance'
+--   updated by the 'Journal.transactions'
+--   of the given 'Journal',
+--   through 'transactions'.
+journal_with_virtual :: Journal -> Balance -> Balance
+journal_with_virtual jour balance =
+       Data.Map.foldl
+        (Data.List.foldl (flip transaction_with_virtual))
+        balance
+        (Journal.transactions jour)
+
 -- | Return the first given 'Balance'
 --   updated by the second given 'Balance'.
 union :: Balance -> Balance -> Balance