]> Git — Sourcephile - comptalang.git/blob - lib/Hcompta/Model/Account.hs
WIP : Format.Ledger.Read : Model.Transaction.Posting
[comptalang.git] / lib / Hcompta / Model / Account.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 module Hcompta.Model.Account where
3
4 import Data.Data
5 import Data.Function (on)
6 import qualified Data.List
7 import qualified Data.Map
8 import Data.Map (Map)
9 import Data.Maybe (fromMaybe)
10 import Data.Typeable ()
11 -- import qualified Text.Parsec as P
12 -- import Text.Parsec (Stream, ParsecT, (<|>), (<?>))
13
14 -- import qualified Hcompta.Model.Account.Path as Path
15 import qualified Hcompta.Model.Amount as Amount
16 import Hcompta.Model.Amount (Amount)
17 import qualified Hcompta.Model.Transaction.Tag as Tag
18 import Hcompta.Model.Transaction.Tag (Tag)
19 import Hcompta.Lib.Regex (Regex)
20
21 -- * The 'Account' type
22
23 type Account = [Name]
24 type Name = String
25
26 nil :: Account
27 nil = []
28
29 -- | Return the given 'Account' without its last 'Name' is any.
30 ascending :: Account -> Account
31 ascending [] = []
32 ascending [a] = []
33 ascending (n:a) = n:ascending a
34
35 -- | Apply the given function to all the prefixes of the given 'Account'.
36 fold :: Account -> (Account -> a -> a) -> a -> a
37 fold = loop []
38 where
39 loop :: Account -> Account -> (Account -> a -> a) -> a -> a
40 loop _path [] _f acc = acc
41 loop path (name:account) f acc =
42 let next = (Hcompta.Model.Account.++) path [name] in
43 loop next account f (f next acc)
44
45
46 -- | Return the concatenation of the given 'Account'.
47 (++) :: Account -> Account -> Account
48 (++) = (Data.List.++)
49
50 -- * The 'Joker' type
51
52 type Joker
53 = [Joker_Name]
54 data Joker_Name
55 = Joker_Any
56 | Joker_Name Name
57 deriving (Data, Eq, Read, Show, Typeable)
58
59 -- * The 'Filter' type
60
61 data Pattern
62 = Pattern_Exact Account
63 | Pattern_Joker Joker
64 | Pattern_Regex Regex
65 deriving (Read, Show, Typeable)