1 {-# LANGUAGE BangPatterns #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE FlexibleInstances #-}
5 {-# LANGUAGE MultiParamTypeClasses #-}
6 {-# LANGUAGE NamedFieldPuns #-}
7 {-# LANGUAGE StandaloneDeriving #-}
8 {-# LANGUAGE TypeFamilies #-}
9 {-# OPTIONS_GHC -fno-warn-deprecations #-} -- FIXME: to be removed when dropping GHC-7.6 support
11 module Hcompta.GL where
13 -- import Control.Applicative (Const(..))
14 import Control.DeepSeq (NFData(..))
15 import Control.Exception (assert)
18 import Data.Eq (Eq(..))
19 import qualified Data.Foldable
20 import Data.Foldable (Foldable(..))
21 import Data.Function (id)
22 import Data.Functor (Functor(..))
23 import Data.Functor.Compose (Compose(..))
24 import Data.List (filter)
25 import Data.Map.Strict (Map)
26 import qualified Data.Map.Strict as Map
27 import Data.Maybe (Maybe(..))
28 import Data.Monoid (Monoid(..))
29 import qualified Data.Sequence as Seq
30 import Data.Sequence (Seq, (><), (|>), ViewR(..))
31 import qualified Data.Strict.Maybe as Strict
32 import qualified Data.Traversable
33 import Data.Tuple (fst, snd)
34 import Data.Typeable ()
35 import Prelude (($), (.), flip, seq, undefined)
36 import Text.Show (Show(..))
38 import Hcompta.Quantity (Addable(..))
39 import Hcompta.Account (Account(..))
40 import Hcompta.Date (Date)
41 import qualified Hcompta.Lib.TreeMap as TreeMap
42 import Hcompta.Lib.TreeMap (TreeMap)
44 -- * Requirements' interface
49 ( Account (Posting_Account p)
50 , Addable (Posting_Quantity p)
51 , Data (Posting_Quantity p)
52 , NFData (Posting_Quantity p)
53 , Show (Posting_Quantity p)
55 type Posting_Account p
56 type Posting_Quantity p
57 posting_account :: p -> Posting_Account p
58 posting_quantity :: p -> Posting_Quantity p
64 => Posting (account, quantity)
66 type Posting_Account (account, quantity) = account
67 type Posting_Quantity (account, quantity) = quantity
68 posting_account (x, _) = x
69 posting_quantity (_, x) = x
71 -- ** Class 'Transaction'
74 ( Data (Transaction_Line t)
75 , Show (Transaction_Line t)
76 , NFData (Transaction_Line t)
77 , Data (Transaction_Posting t)
78 , Posting (Transaction_Posting t)
79 , NFData (Transaction_Posting t)
80 , Show (Transaction_Posting t)
81 , Foldable (Transaction_Postings t)
82 ) => Transaction t where
83 type Transaction_Line t
84 type Transaction_Posting t
85 type Transaction_Postings t :: * -> *
86 transaction_line :: t -> Transaction_Line t
87 transaction_date :: t -> Date
88 transaction_postings :: t -> Transaction_Postings t (Transaction_Posting t)
89 transaction_postings_filter :: (Transaction_Posting t -> Bool) -> t -> t
91 {- NOTE: not needed so far.
97 , account ~ Posting_Account posting
98 ) => Transaction (Date, Map account ([] posting))
100 type Transaction_Posting (Date, Map account ([] posting)) = posting
101 type Transaction_Postings (Date, Map account ([] posting)) = Compose (Map account) []
102 transaction_date = fst
103 transaction_postings = Compose . snd
104 transaction_postings_filter f =
107 (\p -> case filter f p of
118 ) => Transaction (Date, [posting])
120 type Transaction_Line (Date, [posting]) = (Date, [posting])
121 type Transaction_Posting (Date, [posting]) = posting
122 type Transaction_Postings (Date, [posting]) = []
123 transaction_line = id
124 transaction_date = fst
125 transaction_postings = snd
126 transaction_postings_filter = fmap . filter
130 newtype Transaction transaction
132 = GL (TreeMap (Account_Section (Posting_Account (Transaction_Posting transaction)))
134 (Seq (GL_Line transaction))))
135 deriving instance ( Transaction transaction
137 ) => Data (GL transaction)
138 deriving instance ( Transaction transaction
140 ) => Show (GL transaction)
141 deriving instance Typeable1 GL
142 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
143 instance Transaction transaction
144 => Monoid (GL transaction) where
150 ) => NFData (GL t) where
154 Transaction transaction
155 => GL_Line transaction
157 { gl_line_transaction :: Transaction_Line transaction
158 , gl_line_posting :: Transaction_Posting transaction
159 , gl_line_sum :: Posting_Quantity (Transaction_Posting transaction)
161 deriving instance ( Transaction transaction
163 , Typeable transaction
165 ) => Data (GL_Line transaction)
166 deriving instance ( Transaction transaction
167 ) => Show (GL_Line transaction)
168 deriving instance Typeable1 GL_Line
169 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
173 ) => NFData (GL_Line t) where
174 rnf (GL_Line x y z) = rnf x `seq` rnf y `seq` rnf z
179 :: Transaction transaction
183 -- | Return the given 'GL'
184 -- updated by the given 'Transaction'.
186 -- NOTE: to reduce memory consumption when 'cons'ing iteratively,
187 -- the given 'GL' is matched strictly.
189 :: Transaction transaction
199 { gl_line_transaction = transaction_line t
200 , gl_line_posting = p
201 , gl_line_sum = posting_quantity p
204 Map.singleton (transaction_date t) $
205 Seq.singleton first_line in
208 let (nlt, leq, neq, ngt) =
209 case Map.splitLookup (transaction_date t) old of
210 (olt, Nothing, ogt) | Map.null olt ->
211 (olt, first_line, Seq.singleton first_line, ogt)
212 (olt, Nothing, ogt) ->
214 case Seq.viewr $ snd $ Map.findMax olt of
215 (_:>GL_Line{gl_line_sum = s}) ->
216 first_line{gl_line_sum = quantity_add s $ posting_quantity p}
218 in (olt, line, Seq.singleton line, ogt)
219 (olt, Just oeq, ogt) ->
220 case Seq.viewr oeq of
221 (_:>GL_Line{gl_line_sum = s}) ->
222 let line = first_line{gl_line_sum = quantity_add s $ posting_quantity p} in
223 (olt, line, oeq |> line, ogt)
224 _ -> (olt, first_line, Seq.singleton first_line, ogt)
227 Map.insert (transaction_date t) neq $
229 (fmap (\l -> l{gl_line_sum =
230 quantity_add (gl_line_sum leq) $ gl_line_sum l}))
233 (account_path $ posting_account p)
237 (transaction_postings t)
240 :: Transaction transaction
244 union (GL gl0) (GL gl1) =
247 (Map.unionWith mappend)
252 -- | Descending propagation of 'Amount's accross 'Account's.
253 newtype Transaction transaction
254 => Expanded transaction
255 = Expanded (TreeMap (Account_Section (Posting_Account (Transaction_Posting transaction)))
256 (GL_Line_Expanded transaction))
257 data Transaction transaction
258 => GL_Line_Expanded transaction
260 { exclusive :: !(Map Date (Seq (GL_Line transaction)))
261 , inclusive :: !(Map Date (Seq (GL_Line transaction))) -- ^ 'quantity_add' folded over 'exclusive' and 'inclusive' of 'Lib.TreeMap.node_descendants'
263 deriving instance ( Transaction transaction
265 ) => Data (GL_Line_Expanded transaction)
266 deriving instance ( Transaction transaction
268 ) => Show (GL_Line_Expanded transaction)
269 deriving instance Typeable1 GL_Line_Expanded
270 -- FIXME: use 'Typeable' when dropping GHC-7.6 support
272 -- | Return the given 'GL' with:
274 -- * all missing 'Account.ascending' 'Account's inserted,
276 -- * and every mapped 'GL_Line'
277 -- added with any 'GL_Line'
278 -- of the 'Account's for which it is 'Account.ascending'.
280 :: Transaction transaction
282 -> Expanded transaction
284 let from_value = Strict.fromMaybe (assert False undefined) . TreeMap.node_value in
286 TreeMap.map_by_depth_first
287 (\(TreeMap.TreeMap nodes) value ->
288 let exclusive = Strict.fromMaybe Map.empty value in
294 Data.Traversable.mapAccumL -- NOTE: recalc 'gl_line_sum's
296 let qty = posting_quantity $ gl_line_posting line in
298 Nothing -> (Just qty, line)
300 let new_sum = quantity_add last_sum qty in
302 , line{gl_line_sum=new_sum} )
306 (Map.unionWith (flip (><)) . inclusive . from_value)