]> Git — Sourcephile - comptalang.git/blob - lib/Hcompta/Model/Transaction/Posting.hs
Ajout : Calc.Balance types and constructors.
[comptalang.git] / lib / Hcompta / Model / Transaction / Posting.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
3 module Hcompta.Model.Transaction.Posting where
4
5 import Data.Data
6 import qualified Data.Foldable
7 import qualified Data.List
8 import qualified Data.Map
9 import Data.Map (Map)
10 import Data.Typeable ()
11
12 import qualified Hcompta.Model.Account as Account
13 import Hcompta.Model.Account (Account)
14 import qualified Hcompta.Model.Amount as Amount
15 import Hcompta.Model.Amount (Amount)
16 import qualified Hcompta.Model.Date as Date
17 import Hcompta.Model.Date (Date)
18 import qualified Hcompta.Model.Transaction.Tag as Tag
19 import Hcompta.Model.Transaction.Tag (Tag)
20
21 -- * The 'Posting' type
22
23 data Posting
24 = Posting
25 { account :: Account
26 , amounts :: Amount.By_Unit
27 , comment :: String
28 , date :: Date
29 , date2 :: Maybe Date
30 , status :: Bool
31 , tags :: Tag.By_Name
32 , type_ :: Type
33 } deriving (Data, Eq, Read, Show, Typeable)
34
35 data Type
36 = Type_Regular
37 | Type_Virtual
38 | Type_Virtual_Balanced
39 deriving (Data, Eq, Read, Show, Typeable)
40
41 -- ** Convenient constructors
42
43 null :: Posting
44 null =
45 Posting
46 { account = []
47 , amounts = Data.Map.empty
48 , comment = ""
49 , date = Date.null
50 , date2 = Nothing
51 , status = False
52 , tags = Data.Map.empty
53 , type_ = Type_Regular
54 }
55
56 -- * The 'By_Account' mapping
57
58 type By_Account
59 = Map Account [Posting]
60
61 -- ** Convenient constructors
62
63 -- | Return a tuple associating the given posting with its account.
64 by_account :: Posting -> (Account, Posting)
65 by_account posting = (account posting, posting)
66
67 -- | Return a 'Data.Map.Map' associating the given 'Posting's with their respective 'Unit'.
68 from_List :: [Posting] -> By_Account
69 from_List postings =
70 Data.Map.fromListWith (++) $
71 Data.List.map
72 (\posting -> (account posting, [posting]))
73 postings
74
75 -- * Collectors
76
77 -- | Return the units in use within the given postings
78 units
79 :: Data.Foldable.Foldable m
80 => m [Posting]
81 -> [Amount.Unit]
82 units =
83 Data.Foldable.foldl
84 (\acc ->
85 Data.List.union acc .
86 Data.List.concatMap
87 (Data.Map.keys . amounts))
88 []