]> Git — Sourcephile - comptalang.git/blob - lib/Hcompta/Journal.hs
Ajout : Hcompta.Chart.
[comptalang.git] / lib / Hcompta / Journal.hs
1 {-# LANGUAGE BangPatterns #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# OPTIONS_GHC -fno-warn-orphans #-}
5 module Hcompta.Journal where
6
7 import Data.Foldable (Foldable(..))
8 import Data.Functor (Functor(..))
9 import Data.Map.Strict (Map)
10 import qualified Data.Map.Strict as Data.Map
11 import Data.Monoid (Monoid(..))
12 import Prelude (($), Eq(..), Show(..), flip)
13
14 import Hcompta.Date (Date)
15 import Hcompta.Lib.Consable (Consable(..))
16
17 class Transaction t where
18 transaction_date :: t -> Date
19
20 newtype Journal t
21 = Journal (Map Date [t])
22 deriving (Eq, Show)
23
24 instance Functor Journal where
25 fmap f (Journal t) = Journal (fmap (fmap f) t)
26 instance Foldable Journal where
27 foldMap f (Journal t) = foldMap (foldMap f) t
28
29 instance Transaction t => Monoid (Journal t) where
30 mempty = Journal mempty
31 mappend (Journal x) (Journal y) =
32 Journal $ Data.Map.unionWith (flip mappend) x y
33
34 instance Transaction t
35 => Consable () (Journal) t where
36 mcons () = cons
37 instance Consable () [] transaction where
38 mcons () t !j = (:) t j
39
40 -- | Return the given 'Journal'
41 -- updated by the given 'Transaction'.
42 --
43 -- NOTE: to reduce memory consumption when 'cons'ing iteratively,
44 -- the given 'Journal' is matched strictly.
45 cons :: Transaction t => t -> Journal t -> Journal t
46 cons t (Journal !ts) =
47 Journal $
48 Data.Map.insertWith (flip mappend)
49 (transaction_date t) [t] ts
50
51 transactions :: Transaction t => Journal t -> Map Date [t]
52 transactions (Journal ts) = ts