1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE NamedFieldPuns #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE Rank2Types #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TupleSections #-}
9 {-# OPTIONS_GHC -fno-warn-orphans #-}
11 module Balance.Test where
12 import Control.Arrow ((***))
14 import Data.Either (Either(..), either, isRight)
15 import Data.Eq (Eq(..))
16 import Data.Function (($), (.), id, const, flip)
17 import Data.Functor ((<$>))
18 import Data.Maybe (Maybe(..))
19 import Data.Monoid (Monoid(..))
20 import Data.Ord (Ord(..))
21 import Data.String (String)
22 import Data.Text (Text)
23 import Data.Tuple (snd)
24 import Prelude (Integer, error)
26 import Test.Tasty.HUnit
27 import Text.Show (Show(..))
28 import qualified Data.List as List
29 import qualified Data.Map.Strict as Map
30 import qualified Data.NonNull as NonNull
31 import qualified Data.Text as Text
33 import qualified Data.TreeMap.Strict as TreeMap
34 import qualified Hcompta as H
35 import qualified Hcompta.Lib.Strict as Strict
37 elide :: String -> String
38 elide s | List.length s > 42 = List.take 42 s List.++ ['…']
42 type Quantity = Integer
43 amounts :: (H.Addable q, Ord u) => [(u, q)] -> Map.Map u q
44 amounts = Map.fromListWith H.quantity_add
45 pol :: H.Polarizable t => (forall q. q -> (Unit, q)) -> (t -> (Unit, H.Polarized t))
46 pol u = u . H.polarize
55 account :: Text -> H.Balance_Account Text
56 account txt = case go txt of
58 a:as -> NonNull.ncons a as
68 let (chunk, rest) = Text.break (== sep) t in
71 type Posting = (Account, [(Unit, Quantity)])
72 instance H.Get (H.Balance_Account a) (H.Balance_Account a) where get = id
75 tests = testGroup "Balance"
76 [ testGroup "balance_cons" $
77 let (==>) (input::[Posting])
78 ( byAccount::[(Account, [(Unit, H.Polarized Quantity)])]
79 , byUnit::[(Unit, (H.Polarized Quantity, [Account]))] ) =
80 testCase (elide $ show input) $
81 List.foldl (flip H.balance_cons) H.balance_empty
82 ((account *** Map.map H.polarize . amounts) <$> input) @?=
84 { H.balByAccount = TreeMap.from_List const $
85 (account *** H.SumByAccount . amounts) <$> byAccount
86 , H.balByUnit = H.BalByUnit $ Map.fromList $
87 (id *** (\(q, as) -> H.SumByUnit q $ Map.fromList $ ((,()) . account <$> as))) <$> byUnit
90 [ [ ("/A", [usd 1]) ] ==> (,)
91 [ ("/A", [pol usd 1]) ]
92 [ usd (H.polarize 1, ["/A"]) ]
94 , ("/A", [usd (-1)]) ] ==> (,)
95 [ ("/A", [usd $ H.Polarized_Both (-1) 1]) ]
96 [ usd (H.Polarized_Both (-1) 1, ["/A"]) ]
98 , ("/A", [eur (-1)]) ] ==> (,)
101 [ usd (H.polarize 1, ["/A"])
102 , eur (H.polarize (-1), ["/A"]) ]
104 , ("/B", [usd (-1)]) ] ==> (,)
105 [ ("/A", [pol usd 1])
106 , ("/B", [pol usd (-1)]) ]
107 [ usd (H.Polarized_Both (-1) 1, ["/A", "/B"]) ]
109 , ("/B", [eur (-1)]) ] ==> (,)
110 [ ("/A", [pol usd 1])
111 , ("/B", [pol eur (-1)]) ]
112 [ usd (H.polarize 1, ["/A"])
113 , eur (H.polarize (-1), ["/B"]) ]
115 , ("/B", [usd 1]) ] ==> (,)
116 [ ("/A", [pol usd 1])
117 , ("/B", [pol usd 1]) ]
118 [ usd (H.polarize 2, ["/A", "/B"]) ]
119 , [ ("/A", [usd 1, eur 2])
120 , ("/A", [usd (-1), eur (-2)]) ] ==> (,)
121 [ ("/A", [ usd $ H.Polarized_Both (-1) 1
122 , eur $ H.Polarized_Both (-2) 2 ]) ]
123 [ usd (H.Polarized_Both (-1) 1, ["/A"])
124 , eur (H.Polarized_Both (-2) 2, ["/A"]) ]
125 , [ ("/A", [usd 1, eur 2, gbp 3])
126 , ("/B", [usd (-1), eur (-2), gbp (-3)]) ] ==> (,)
130 , ("/B", [ pol usd (-1)
133 [ usd (H.Polarized_Both (-1) 1, ["/A", "/B"])
134 , eur (H.Polarized_Both (-2) 2, ["/A", "/B"])
135 , gbp (H.Polarized_Both (-3) 3, ["/A", "/B"]) ]
137 , testGroup "balance_union" $
140 [( [(Account, [(Unit, H.Polarized Quantity)])]
141 , [(Unit, (H.Polarized Quantity, [Account]))] )])
143 ( [(Account, [(Unit, H.Polarized Quantity)])]
144 , [(Unit, (H.Polarized Quantity, [Account]))] )) =
145 testCase (elide $ show input) $
146 List.foldl H.balance_union H.balance_empty (bal <$> input) @?= bal expected
148 bal (byAccount, byUnit) =
150 { H.balByAccount = TreeMap.from_List const $
151 (account *** H.SumByAccount . amounts) <$> byAccount
152 , H.balByUnit = H.BalByUnit $ Map.fromList $
153 (id *** (\(q, as) -> H.SumByUnit q $ Map.fromList $ ((,()) . account <$> as))) <$> byUnit
157 [ ("/A", [pol usd 1]) ]
158 [ usd (H.polarize 1, ["/A"]) ]
160 [ ("/A", [pol usd 1]) ]
161 [ usd (H.polarize 1, ["/A"]) ]
163 [ ("/A", [pol usd 2]) ]
164 [ usd (H.polarize 2, ["/A"]) ]
166 [ ("/A", [pol usd 1]) ]
167 [ usd (H.polarize 1, ["/A"]) ]
169 [ ("/B", [pol usd 1]) ]
170 [ usd (H.polarize 1, ["/B"]) ]
172 [ ("/A", [pol usd 1])
173 , ("/B", [pol usd 1]) ]
174 [ usd (H.polarize 2, ["/A", "/B"]) ]
176 [ ("/A", [pol usd 1]) ]
177 [ usd (H.polarize 1, ["/A"]) ]
179 [ ("/B", [pol eur 1]) ]
180 [ eur (H.polarize 1, ["/B"]) ]
182 [ ("/A", [pol usd 1])
183 , ("/B", [pol eur 1]) ]
184 [ usd (H.polarize 1, ["/A"])
185 , eur (H.polarize 1, ["/B"]) ]
187 [ ("/A", [pol usd 1, pol eur 2]) ]
188 [ usd (H.polarize 1, ["/A"])
189 , eur (H.polarize 2, ["/A"]) ]
191 [ ("/B", [pol usd (-1), pol eur (-2)]) ]
192 [ usd (H.polarize (-1), ["/B"])
193 , eur (H.polarize (-2), ["/B"]) ]
195 [ ("/A", [pol usd 1 , pol eur 2])
196 , ("/B", [pol usd (-1), pol eur (-2)]) ]
197 [ usd (H.Polarized_Both (-1) 1, ["/A", "/B"])
198 , eur (H.Polarized_Both (-2) 2, ["/A", "/B"]) ]
200 [ ("/A", [pol usd 1, pol eur 2]) ]
201 [ usd (H.polarize 1, ["/A"])
202 , eur (H.polarize 2, ["/A"]) ]
204 [ ("/B", [pol usd (-1), pol eur (-2)]) ]
205 [ usd (H.polarize (-1), ["/B"])
206 , eur (H.polarize (-2), ["/B"]) ]
208 [ ("/C", [pol gbp 3]) ]
209 [ gbp (H.polarize 3, ["/C"]) ]
211 [ ("/A", [pol usd 1 , pol eur 2])
212 , ("/B", [pol usd (-1), pol eur (-2)])
213 , ("/C", [pol gbp 3]) ]
214 [ usd (H.Polarized_Both (-1) 1, ["/A", "/B"])
215 , eur (H.Polarized_Both (-2) 2, ["/A", "/B"])
216 , gbp (H.polarize 3, ["/C"]) ]
218 , testGroup "clusiveBalByAccount" $
220 (input::[(Account, [(Unit, H.Polarized Quantity)])])
221 (expected::[(Account, ( [(Unit, H.Polarized Quantity)]
222 , [(Unit, H.Polarized Quantity)] ))]) =
223 testCase (elide $ show input) $
224 H.clusiveBalByAccount (bal input) @?= exbal expected
227 TreeMap.from_List const $
228 (account *** H.SumByAccount . amounts) <$> byAccount
230 TreeMap.from_List const $
231 (account *** (\(e, i) -> Strict.Clusive
232 (H.SumByAccount (amounts e))
233 (H.SumByAccount (amounts i)) )) <$> byAccount
236 , [ ("/A", [pol usd 1]) ] ==>
237 [ ("/A", (,) [pol usd 1] [pol usd 1]) ]
238 , [ ("/A/A", [pol usd 1]) ] ==>
239 [ ("/A", (,) [] [pol usd 1])
240 , ("/A/A", (,) [pol usd 1] [pol usd 1]) ]
241 , [ ("/A/B", [pol usd 1]) ] ==>
242 [ ("/A", (,) [] [pol usd 1])
243 , ("/A/B", (,) [pol usd 1] [pol usd 1]) ]
244 , [ ("/A/B/C", [pol usd 1]) ] ==>
245 [ ("/A", (,) [] [pol usd 1])
246 , ("/A/B", (,) [] [pol usd 1])
247 , ("/A/B/C", (,) [pol usd 1] [pol usd 1]) ]
248 , [ ("/A/B", [pol usd (-1)])
249 , ("/A/B/C", [pol usd 1])
251 [ ("/A", (,) [] [usd $ H.Polarized_Both (-1) 1])
252 , ("/A/B", (,) [pol usd (-1)] [usd $ H.Polarized_Both (-1) 1])
253 , ("/A/B/C", (,) [pol usd 1] [pol usd 1]) ]
254 , [ ("/A/B", [pol usd 1])
255 , ("/A/B/C", [pol usd 1])
256 , ("/A/B/D", [pol usd 1])
258 [ ("/A", (,) [] [pol usd 3])
259 , ("/A/B", (,) [pol usd 1] [pol usd 3])
260 , ("/A/B/C", (,) [pol usd 1] [pol usd 1])
261 , ("/A/B/D", (,) [pol usd 1] [pol usd 1]) ]
262 , [ ("/A/B", [pol usd 1])
263 , ("/A/C", [pol usd 1])
264 , ("/D/B", [pol usd 1])
266 [ ("/A", (,) [] [pol usd 2])
267 , ("/A/B", (,) [pol usd 1] [pol usd 1])
268 , ("/A/C", (,) [pol usd 1] [pol usd 1])
269 , ("/D", (,) [] [pol usd 1])
270 , ("/D/B", (,) [pol usd 1] [pol usd 1]) ]
272 , testGroup "deviationByUnit" $
273 let (==>) (input::[Posting])
274 (expected::[(Unit, (H.Polarized Quantity, [Account]))]) =
275 testCase (elide $ show input) $
281 H.DeviationByUnit balDev
284 TreeMap.from_List const $
285 (account *** H.SumByAccount . (H.polarize <$>) . amounts) <$> input
286 balByUnit = H.balByUnit_of_BalByAccount balByAccount mempty
288 H.BalByUnit $ Map.fromList $
290 H.SumByUnit q $ Map.fromList $
291 ((,()) . account <$> as))
295 , [ ("/A", [usd 1]) ] ==>
296 [usd (H.polarize 1, [])]
299 [usd (H.polarize 1, ["/B"])]
302 [usd (H.polarize 1, ["/A/B"])]
304 , ("/A/B", [usd (-1)]) ] ==>
307 , ("/A/B", [eur (-1)]) ] ==>
308 [ usd (H.polarize 1, ["/A/B"])
309 , eur (H.polarize (-1), ["/A"])
312 , ("/B", [usd 1]) ] ==>
313 [usd (H.polarize 2, [])]
315 , ("/B", [eur 2]) ] ==>
316 [ usd (H.polarize 1, ["/B"])
317 , eur (H.polarize 2, ["/A"])
319 , [ ("/A", [usd 1, eur 2])
320 , ("/B", [usd (-1), eur 2]) ] ==>
321 [ eur (H.polarize 4, []) ]
322 , [ ("/A", [usd 1, eur 2])
323 , ("/B", [usd (-1), eur 2])
324 , ("/C", [gbp 3]) ] ==>
325 [ eur (H.polarize 4, ["/C"])
326 , gbp (H.polarize 3, ["/A", "/B"]) ]
328 , testGroup "equilibrium" $
329 let (==>) (input::[Posting])
330 (expected::Either [(Unit, (H.Polarized Quantity, [Account]))] [Posting]) =
331 testCase (elide $ show input) $
332 let o = snd (H.equilibrium $ postings input) in
333 let e = either (Left . units) (Right . postings) expected in
334 let is = H.is_equilibrium_inferrable $
340 (isRight o, o) @?= (is, e)
344 -> Map.Map (H.Balance_Account Text)
345 [( H.Balance_Account Text
346 , Map.Map Unit (H.Polarized Quantity) )]
350 let a = account acct in (a,)
351 [(a, H.polarize <$> amounts amts)] ) <$>)
353 :: [(Unit, (H.Polarized Quantity, [Account]))]
354 -> [(Unit, H.SumByUnit (H.Balance_Account Text) (H.Polarized Quantity))]
356 ((id *** (\(q, as) ->
357 H.SumByUnit q $ Map.fromList $
358 ((,()) . account <$> as))) <$>)
360 TreeMap.from_List const $
361 (account *** H.SumByAccount . (H.polarize <$>) . amounts) <$> input
362 balByUnit = H.balByUnit_of_BalByAccount balByAccount mempty
365 , [ ("/A", [usd 1]) ] ==> Left
366 [ usd (H.polarize 1, []) ]
368 , ("/B", []) ] ==> Right
370 , ("/B", [usd (-1)]) ]
372 , ("/A/B", []) ] ==> Right
374 , ("/A/B", [usd (-1)]) ]
376 , ("/A/B", [usd (-1)]) ] ==> Right
378 , ("/A/B", [usd (-1)]) ]
380 , ("/A/B", [eur (-1)]) ] ==> Right
381 [ ("/A", [usd 1, eur 1])
382 , ("/A/B", [usd (-1), eur (-1)]) ]
384 , ("/B", [usd 1]) ] ==> Left
385 [ usd (H.polarize 2, []) ]
387 , ("/B", [eur 2]) ] ==> Right
388 [ ("/A", [usd 1, eur (-2)])
389 , ("/B", [usd (-1), eur 2]) ]
390 , [ ("/A", [usd 1, eur 2])
391 , ("/B", [usd (-1), eur 2]) ] ==> Left
392 [ eur (H.polarize 4, []) ]
393 , [ ("/A", [usd 1, eur 2])
394 , ("/B", [usd (-1), eur 2])
395 , ("/C", [gbp 3]) ] ==> Left
396 [ gbp (H.polarize 3, ["/A", "/B"]) ]