]> Git — Sourcephile - comptalang.git/blob - lib/Test/Main.hs
Modification : sépare hcompta-ledger de hcompta-lib.
[comptalang.git] / lib / Test / Main.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TupleSections #-}
5
6 import Prelude
7 import Test.HUnit hiding ((~?))
8 import Test.Framework.Providers.HUnit (hUnitTestToTests)
9 import Test.Framework.Runners.Console (defaultMain)
10
11 -- import Control.Applicative (Const(..))
12 import Control.Arrow ((***))
13 import Data.Data ()
14 import qualified Data.Either
15 import Data.Function (on)
16 -- import Data.Functor.Compose (Compose(..))
17 import qualified Data.List as List
18 import Data.List.NonEmpty (NonEmpty(..))
19 import qualified Data.Map.Strict as Map
20 import Data.Maybe (fromJust)
21 import qualified Data.Strict.Maybe as Strict
22 import Data.Text (Text)
23 import qualified Text.Parsec as P hiding (char, space, spaces, string)
24
25 import qualified Hcompta.Account as Account
26 import qualified Hcompta.Balance as Balance
27 import qualified Hcompta.Filter as Filter
28 import qualified Hcompta.Filter.Read as Filter.Read
29 import qualified Hcompta.Lib.Foldable as Lib.Foldable
30 import qualified Hcompta.Lib.Interval as Lib.Interval
31 import qualified Hcompta.Lib.Interval.Sieve as Lib.Interval.Sieve
32 import qualified Hcompta.Lib.Parsec as P
33 import qualified Hcompta.Lib.TreeMap as TreeMap
34 import qualified Hcompta.Polarize as Polarize
35 import qualified Hcompta.Quantity as Quantity
36 import qualified Hcompta.Tag as Tag
37
38 main :: IO ()
39 main = defaultMain $ hUnitTestToTests test_Hcompta
40
41 (~?) :: String -> Bool -> Test
42 (~?) s b = s ~: (b ~?= True)
43
44 amounts :: (Quantity.Addable q, Ord u) => [(u, q)] -> Map.Map u q
45 amounts = Map.fromListWith Quantity.quantity_add
46 amount_usd = (("$"::Text),)
47 amount_eur = (("€"::Text),)
48 amount_gbp = (("£"::Text),)
49
50 test_Hcompta :: Test
51 test_Hcompta =
52 TestList
53 [ "Lib" ~: TestList
54 [ "TreeMap" ~: TestList
55 [ "insert" ~: TestList
56 [ "[] 0" ~:
57 (TreeMap.insert const ((0::Int):|[]) () TreeMap.empty)
58 ~?=
59 (TreeMap.TreeMap $
60 Map.fromList
61 [ ((0::Int), TreeMap.leaf ())
62 ])
63 , "[] 0/1" ~:
64 (TreeMap.insert const ((0::Int):|1:[]) () TreeMap.empty)
65 ~?=
66 (TreeMap.TreeMap $
67 Map.fromList
68 [ ((0::Int), TreeMap.Node
69 { TreeMap.node_value = Strict.Nothing
70 , TreeMap.node_size = 1
71 , TreeMap.node_descendants =
72 TreeMap.singleton ((1::Int):|[]) ()
73 })
74 ])
75 ]
76 , "union" ~: TestList
77 [
78 ]
79 , "map_by_depth_first" ~: TestList
80 [ "[0, 0/1, 0/1/2, 1, 1/2/3]" ~:
81 (TreeMap.map_by_depth_first
82 (\descendants value ->
83 Map.foldl'
84 (\acc v -> (++) acc $
85 Strict.fromMaybe undefined $
86 TreeMap.node_value v
87 )
88 (Strict.fromMaybe [] value)
89 (TreeMap.nodes descendants)
90 ) $
91 TreeMap.from_List const
92 [ (((0::Integer):|[]), [0])
93 , ((0:|1:[]), [0,1])
94 , ((0:|1:2:[]), [0,1,2])
95 , ((1:|[]), [1])
96 , ((1:|2:3:[]), [1,2,3])
97 ]
98 )
99 ~?=
100 (TreeMap.from_List const
101 [ ((0:|[]), [0,0,1,0,1,2])
102 , ((0:|1:[]), [0,1,0,1,2])
103 , ((0:|1:2:[]), [0,1,2])
104 , ((1:|[]), [1,1,2,3])
105 , ((1:|2:[]), [1,2,3])
106 , ((1:|2:3:[]), [1,2,3])
107 ])
108 , "[0/0]" ~:
109 (TreeMap.map_by_depth_first
110 (\descendants value ->
111 Map.foldl'
112 (\acc v -> (++) acc $
113 Strict.fromMaybe undefined $
114 TreeMap.node_value v
115 )
116 (Strict.fromMaybe [] value)
117 (TreeMap.nodes descendants)
118 ) $
119 TreeMap.from_List const
120 [ (((0::Integer):|0:[]), [0,0])
121 ]
122 )
123 ~?=
124 (TreeMap.from_List const
125 [ ((0:|[]), [0,0])
126 , ((0:|0:[]), [0,0])
127 ])
128 ]
129 , "flatten" ~: TestList
130 [ "[0, 0/1, 0/1/2]" ~:
131 (TreeMap.flatten id $
132 TreeMap.from_List const
133 [ (((0::Integer):|[]), ())
134 , ((0:|1:[]), ())
135 , ((0:|1:2:[]), ())
136 ]
137 )
138 ~?=
139 (Map.fromList
140 [ ((0:|[]), ())
141 , ((0:|1:[]), ())
142 , ((0:|1:2:[]), ())
143 ])
144 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
145 (TreeMap.flatten id $
146 TreeMap.from_List const
147 [ ((1:|[]), ())
148 , ((1:|2:[]), ())
149 , ((1:|22:[]), ())
150 , ((1:|2:3:[]), ())
151 , ((1:|2:33:[]), ())
152 , ((11:|[]), ())
153 , ((11:|2:[]), ())
154 , ((11:|2:3:[]), ())
155 , ((11:|2:33:[]), ())
156 ]
157 )
158 ~?=
159 (Map.fromList
160 [ (((1::Integer):|[]), ())
161 , ((1:|2:[]), ())
162 , ((1:|22:[]), ())
163 , ((1:|2:3:[]), ())
164 , ((1:|2:33:[]), ())
165 , ((11:|[]), ())
166 , ((11:|2:[]), ())
167 , ((11:|2:3:[]), ())
168 , ((11:|2:33:[]), ())
169 ])
170 ]
171 , "find_along" ~: TestList
172 [ "0/1/2/3 [0, 0/1, 0/1/2, 0/1/2/3]" ~:
173 (TreeMap.find_along
174 (0:|[1,2,3]) $
175 TreeMap.from_List const
176 [ (((0::Integer):|[]), [0])
177 , ((0:|1:[]), [0,1])
178 , ((0:|1:2:[]), [0,1,2])
179 , ((0:|1:2:3:[]), [0,1,2,3])
180 ]
181 )
182 ~?=
183 [ [0]
184 , [0,1]
185 , [0,1,2]
186 , [0,1,2,3]
187 ]
188 , "0/1/2/3 [0, 0/1]" ~:
189 (TreeMap.find_along
190 (0:|[1,2,3]) $
191 TreeMap.from_List const
192 [ (((0::Integer):|[]), [0])
193 , ((0:|1:[]), [0,1])
194 ]
195 )
196 ~?=
197 [ [0]
198 , [0,1]
199 ]
200 ]
201 ]
202 , "Foldable" ~: TestList
203 [ "accumLeftsAndFoldrRights" ~: TestList
204 [ "Left" ~:
205 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
206 [Left [0]])
207 ~?=
208 (([(0::Integer)], [(""::String)]))
209 , "repeat Left" ~:
210 ((take 1 *** take 0) $
211 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
212 ( repeat (Left [0]) ))
213 ~?=
214 ([(0::Integer)], ([]::[String]))
215 , "Right:Left:Right:Left" ~:
216 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
217 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
218 ~?=
219 (([1, 0]::[Integer]), (["2", "1", "0"]::[String]))
220 , "Right:Left:Right:repeat Left" ~:
221 ((take 1 *** take 2) $
222 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
223 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
224 ~?=
225 (([1]::[Integer]), (["2", "1"]::[String]))
226 ]
227 ]
228 , "Interval" ~: TestList
229 [ "position" ~: TestList $
230 concatMap
231 (\(mi, mj, p) ->
232 let i = fromJust mi in
233 let j = fromJust mj in
234 let (le, ge) =
235 case p of
236 Lib.Interval.Equal -> (EQ, EQ)
237 _ -> (LT, GT) in
238 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.position i j ~?= (p, le)
239 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.position j i ~?= (p, ge)
240 ]
241 )
242 [ ( (Lib.Interval.<..<) 0 (4::Integer)
243 , (Lib.Interval.<..<) 5 9
244 , Lib.Interval.Away )
245 , ( (Lib.Interval.<..<) 0 4
246 , (Lib.Interval.<=..<) 4 9
247 , Lib.Interval.Adjacent )
248 , ( (Lib.Interval.<..<) 0 5
249 , (Lib.Interval.<..<) 4 9
250 , Lib.Interval.Overlap )
251 , ( (Lib.Interval.<..<) 0 5
252 , (Lib.Interval.<..<) 0 9
253 , Lib.Interval.Prefix )
254 , ( (Lib.Interval.<..<) 0 9
255 , (Lib.Interval.<..<) 1 8
256 , Lib.Interval.Include )
257 , ( (Lib.Interval.<..<) 0 9
258 , (Lib.Interval.<..<) 5 9
259 , Lib.Interval.Suffixed )
260 , ( (Lib.Interval.<..<) 0 9
261 , (Lib.Interval.<..<) 0 9
262 , Lib.Interval.Equal )
263 , ( (Lib.Interval.<..<) 0 9
264 , (Lib.Interval.<..<=) 0 9
265 , Lib.Interval.Prefix )
266 , ( (Lib.Interval.<=..<) 0 9
267 , (Lib.Interval.<..<) 0 9
268 , Lib.Interval.Suffixed )
269 , ( (Lib.Interval.<=..<=) 0 9
270 , (Lib.Interval.<..<) 0 9
271 , Lib.Interval.Include )
272 ]
273 , "intersection" ~: TestList $
274 concatMap
275 (\(mi, mj, e) ->
276 let i = fromJust mi in
277 let j = fromJust mj in
278 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.intersection i j ~?= e
279 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.intersection j i ~?= e
280 ]
281 )
282 [ ( (Lib.Interval.<..<) 0 (4::Integer)
283 , (Lib.Interval.<..<) 5 9
284 , Nothing )
285 , ( (Lib.Interval.<..<=) 0 5
286 , (Lib.Interval.<=..<) 5 9
287 , (Lib.Interval.<=..<=) 5 5 )
288 , ( (Lib.Interval.<..<) 0 6
289 , (Lib.Interval.<..<) 4 9
290 , (Lib.Interval.<..<) 4 6 )
291 , ( (Lib.Interval.<..<=) 0 6
292 , (Lib.Interval.<=..<) 4 9
293 , (Lib.Interval.<=..<=) 4 6 )
294 , ( (Lib.Interval.<..<) 0 6
295 , (Lib.Interval.<=..<) 4 9
296 , (Lib.Interval.<=..<) 4 6 )
297 , ( (Lib.Interval.<..<=) 0 6
298 , (Lib.Interval.<..<) 4 9
299 , (Lib.Interval.<..<=) 4 6 )
300 , ( (Lib.Interval.<..<) 0 9
301 , (Lib.Interval.<..<) 0 9
302 , (Lib.Interval.<..<) 0 9 )
303 , ( (Lib.Interval.<=..<) 0 9
304 , (Lib.Interval.<..<=) 0 9
305 , (Lib.Interval.<..<) 0 9 )
306 , ( (Lib.Interval.<..<=) 0 9
307 , (Lib.Interval.<=..<) 0 9
308 , (Lib.Interval.<..<) 0 9 )
309 , ( (Lib.Interval.<=..<=) 0 9
310 , (Lib.Interval.<=..<=) 0 9
311 , (Lib.Interval.<=..<=) 0 9 )
312 ]
313 , "union" ~: TestList $
314 concatMap
315 (\(mi, mj, e) ->
316 let i = fromJust mi in
317 let j = fromJust mj in
318 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.union i j ~?= e
319 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.union j i ~?= e
320 ]
321 )
322 [ ( (Lib.Interval.<..<) 0 (4::Integer)
323 , (Lib.Interval.<..<) 5 9
324 , Nothing )
325 , ( (Lib.Interval.<..<=) 0 5
326 , (Lib.Interval.<..<) 5 9
327 , (Lib.Interval.<..<) 0 9 )
328 , ( (Lib.Interval.<..<) 0 5
329 , (Lib.Interval.<=..<) 5 9
330 , (Lib.Interval.<..<) 0 9 )
331 , ( (Lib.Interval.<..<=) 0 5
332 , (Lib.Interval.<=..<) 5 9
333 , (Lib.Interval.<..<) 0 9 )
334 , ( (Lib.Interval.<..<) 0 6
335 , (Lib.Interval.<..<) 4 9
336 , (Lib.Interval.<..<) 0 9 )
337 , ( (Lib.Interval.<..<) 0 9
338 , (Lib.Interval.<..<) 0 9
339 , (Lib.Interval.<..<) 0 9 )
340 , ( (Lib.Interval.<=..<) 0 9
341 , (Lib.Interval.<..<=) 0 9
342 , (Lib.Interval.<=..<=) 0 9 )
343 , ( (Lib.Interval.<..<=) 0 9
344 , (Lib.Interval.<=..<) 0 9
345 , (Lib.Interval.<=..<=) 0 9 )
346 , ( (Lib.Interval.<=..<=) 0 9
347 , (Lib.Interval.<=..<=) 0 9
348 , (Lib.Interval.<=..<=) 0 9 )
349 ]
350 , "Sieve" ~: TestList $
351 [ "union" ~: TestList $
352 List.concatMap
353 (\(mis, me) ->
354 let is = map (fromJust) mis in
355 let e = map (fromJust) me in
356 let sil = foldl
357 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
358 Lib.Interval.Sieve.empty is in
359 let sir = foldr
360 (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)
361 Lib.Interval.Sieve.empty is in
362 [ (List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ~:
363 Lib.Interval.Sieve.intervals sil ~?= e
364 , (List.intercalate " " $ map (show . Lib.Interval.Pretty) $ reverse is) ~:
365 Lib.Interval.Sieve.intervals sir ~?= e
366 ]
367 )
368 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer)
369 , (Lib.Interval.<=..<=) 5 9
370 ]
371 , [ (Lib.Interval.<=..<=) 0 9 ]
372 )
373 , ( [ (Lib.Interval.<=..<=) 0 5
374 , (Lib.Interval.<=..<=) 0 9
375 ]
376 , [ (Lib.Interval.<=..<=) 0 9 ]
377 )
378 , ( [ (Lib.Interval.<=..<=) 0 4
379 , (Lib.Interval.<=..<=) 5 9
380 , (Lib.Interval.<=..<=) 3 6
381 ]
382 , [ (Lib.Interval.<=..<=) 0 9 ]
383 )
384 , ( [ (Lib.Interval.<=..<=) 1 4
385 , (Lib.Interval.<=..<=) 5 8
386 ]
387 , [ (Lib.Interval.<=..<=) 1 4
388 , (Lib.Interval.<=..<=) 5 8
389 ]
390 )
391 , ( [ (Lib.Interval.<=..<=) 1 8
392 , (Lib.Interval.<=..<=) 0 9
393 ]
394 , [ (Lib.Interval.<=..<=) 0 9 ]
395 )
396 , ( [ (Lib.Interval.<=..<=) 1 4
397 , (Lib.Interval.<=..<=) 5 8
398 , (Lib.Interval.<=..<=) 0 9
399 ]
400 , [ (Lib.Interval.<=..<=) 0 9 ]
401 )
402 ]
403 ++ List.concatMap
404 (\(mis, mjs, me) ->
405 let is = map fromJust mis in
406 let js = map fromJust mjs in
407 let e = map fromJust me in
408 let iu = foldl
409 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
410 Lib.Interval.Sieve.empty is in
411 let ju = foldl
412 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
413 Lib.Interval.Sieve.empty js in
414 [ ((List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " u " ++
415 (List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
416 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union iu ju) ~?= e
417 , ((List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " u " ++
418 (List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
419 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union ju iu) ~?= e
420 ]
421 )
422 [ ( [ (Lib.Interval.<=..<=) 0 (1::Integer)
423 , (Lib.Interval.<=..<=) 2 4
424 ]
425 , [ (Lib.Interval.<=..<=) 0 3
426 ]
427 , [ (Lib.Interval.<=..<=) 0 4
428 ]
429 )
430 , ( [ (Lib.Interval.<=..<=) 0 1
431 , (Lib.Interval.<=..<=) 2 3
432 , (Lib.Interval.<=..<=) 4 5
433 , (Lib.Interval.<=..<=) 6 7
434 ]
435 , [ (Lib.Interval.<=..<=) 1 2
436 , (Lib.Interval.<=..<=) 3 4
437 , (Lib.Interval.<=..<=) 5 6
438 ]
439 , [ (Lib.Interval.<=..<=) 0 7
440 ]
441 )
442 , ( [ (Lib.Interval.<=..<=) 0 1
443 , (Lib.Interval.<=..<=) 2 3
444 ]
445 , [ (Lib.Interval.<=..<=) 4 5
446 ]
447 , [ (Lib.Interval.<=..<=) 0 1
448 , (Lib.Interval.<=..<=) 2 3
449 , (Lib.Interval.<=..<=) 4 5
450 ]
451 )
452 , ( [ (Lib.Interval.<=..<=) 0 1
453 , (Lib.Interval.<=..<=) 4 5
454 ]
455 , [ (Lib.Interval.<=..<=) 2 3
456 ]
457 , [ (Lib.Interval.<=..<=) 0 1
458 , (Lib.Interval.<=..<=) 2 3
459 , (Lib.Interval.<=..<=) 4 5
460 ]
461 )
462 ]
463 , "intersection" ~: TestList $
464 List.concatMap
465 (\(mis, mjs, me) ->
466 let is = map (fromJust) mis in
467 let js = map (fromJust) mjs in
468 let e = map (fromJust) me in
469 let iu = foldl
470 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
471 Lib.Interval.Sieve.empty is in
472 let ju = foldl
473 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
474 Lib.Interval.Sieve.empty js in
475 [ ((List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " n " ++
476 (List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
477 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection iu ju) ~?= e
478 , ((List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " n " ++
479 (List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
480 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection ju iu) ~?= e
481 ]
482 )
483 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) ]
484 , [ (Lib.Interval.<=..<=) 5 9 ]
485 , [ ]
486 )
487 , ( [ (Lib.Interval.<=..<=) 0 5 ]
488 , [ (Lib.Interval.<=..<=) 5 9 ]
489 , [ (Lib.Interval.<=..<=) 5 5 ]
490 )
491 , ( [ (Lib.Interval.<=..<=) 0 5 ]
492 , [ (Lib.Interval.<=..<=) 0 9 ]
493 , [ (Lib.Interval.<=..<=) 0 5 ]
494 )
495 , ( [ (Lib.Interval.<=..<=) 0 4
496 , (Lib.Interval.<=..<=) 5 9
497 ]
498 , [ (Lib.Interval.<=..<=) 3 6 ]
499 , [ (Lib.Interval.<=..<=) 3 4
500 , (Lib.Interval.<=..<=) 5 6
501 ]
502 )
503 , ( [ (Lib.Interval.<=..<=) 1 4
504 , (Lib.Interval.<=..<=) 6 8
505 ]
506 , [ (Lib.Interval.<=..<=) 2 3
507 , (Lib.Interval.<=..<=) 5 7
508 ]
509 , [ (Lib.Interval.<=..<=) 2 3
510 , (Lib.Interval.<=..<=) 6 7
511 ]
512 )
513 ]
514 , "complement" ~: TestList $
515 List.concatMap
516 (\(mis, me) ->
517 let is = map fromJust mis in
518 let e = map fromJust me in
519 let iu = foldl
520 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
521 Lib.Interval.Sieve.empty is in
522 [ show (Lib.Interval.Pretty $
523 Lib.Interval.Sieve.fmap_interval
524 (Lib.Interval.fmap_unsafe $ Lib.Interval.Pretty) iu) ~:
525 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement iu) ~?= e
526 ]
527 )
528 [ ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 (5::Integer)
529 , ((Lib.Interval.<=..<=) `on` Lib.Interval.Limited) 5 9
530 ]
531 , [ Just $ (Lib.Interval...<) 0
532 , Just $ (Lib.Interval.<..) 9
533 ]
534 )
535 , ( [ Just $ Lib.Interval.unlimited ]
536 , [ ]
537 )
538 , ( [ ]
539 , [ Just $ Lib.Interval.unlimited ]
540 )
541 , ( [ Just $ (Lib.Interval...<) 0
542 , Just $ (Lib.Interval.<..) 0
543 ]
544 , [ Just $ Lib.Interval.point $ Lib.Interval.Limited 0
545 ]
546 )
547 , ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 1
548 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 2 3
549 , ((Lib.Interval.<..<=) `on` Lib.Interval.Limited) 3 4
550 ]
551 , [ Just $ (Lib.Interval...<) 0
552 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 1 2
553 , Just $ Lib.Interval.point $ Lib.Interval.Limited 3
554 , Just $ (Lib.Interval.<..) 4
555 ]
556 )
557 ]
558 , "complement_with" ~: TestList $
559 List.concatMap
560 (\(mib, mis, me) ->
561 let ib = fromJust mib in
562 let is = map fromJust mis in
563 let e = map fromJust me in
564 let iu = foldl
565 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
566 Lib.Interval.Sieve.empty is in
567 [ show (Lib.Interval.Pretty iu) ~:
568 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement_with ib iu) ~?= e
569 ]
570 )
571 [ ( (Lib.Interval.<=..<=) (-10) (10::Integer)
572 , [ (Lib.Interval.<=..<) 0 5
573 , (Lib.Interval.<=..<=) 5 9
574 ]
575 , [ (Lib.Interval.<=..<) (-10) 0
576 , (Lib.Interval.<..<=) 9 10
577 ]
578 )
579 , ( (Lib.Interval.<=..<=) (-10) 10
580 , [ (Lib.Interval.<=..<=) (-10) 10 ]
581 , [ ]
582 )
583 , ( (Lib.Interval.<=..<=) (-10) 10
584 , [ ]
585 , [ (Lib.Interval.<=..<=) (-10) 10 ]
586 )
587 , ( (Lib.Interval.<=..<=) (-10) 10
588 , [ (Lib.Interval.<=..<) (-10) 0
589 , (Lib.Interval.<..<=) 0 10
590 ]
591 , [ Just $ Lib.Interval.point 0
592 ]
593 )
594 , ( (Lib.Interval.<=..<=) (-10) 10
595 , [ Just $ Lib.Interval.point 0
596 ]
597 , [ (Lib.Interval.<=..<) (-10) 0
598 , (Lib.Interval.<..<=) 0 10
599 ]
600 )
601 , ( (Lib.Interval.<=..<=) 0 10
602 , [ (Lib.Interval.<..<=) 0 10
603 ]
604 , [ Just $ Lib.Interval.point 0
605 ]
606 )
607 , ( (Lib.Interval.<=..<=) 0 10
608 , [ (Lib.Interval.<=..<) 0 10
609 ]
610 , [ Just $ Lib.Interval.point 10
611 ]
612 )
613 , ( Just $ Lib.Interval.point 0
614 , [
615 ]
616 , [ Just $ Lib.Interval.point 0
617 ]
618 )
619 , ( Just $ Lib.Interval.point 0
620 , [ Just $ Lib.Interval.point 0
621 ]
622 , [
623 ]
624 )
625 ]
626 ]
627 ]
628 ]
629 , "Account" ~: TestList
630 [ "foldr" ~: TestList
631 [ "[A]" ~:
632 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
633 , "[A, B]" ~:
634 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
635 , "[A, B, C]" ~:
636 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
637 ]
638 , "ascending" ~: TestList
639 [ "[A]" ~:
640 Account.ascending ("A":|[]) ~?= Nothing
641 , "[A, B]" ~:
642 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
643 , "[A, B, C]" ~:
644 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
645 ]
646 ]
647 , "Filter" ~: TestList
648 [ "test" ~: TestList
649 [ "Filter_Path" ~: TestList
650 [ "A A" ~?
651 Filter.test
652 (Filter.Filter_Path Filter.Eq
653 [ Filter.Filter_Path_Section_Text
654 (Filter.Filter_Text_Exact "A")
655 ])
656 ((("A"::Text):|[]))
657 , "* A" ~?
658 Filter.test
659 (Filter.Filter_Path Filter.Eq
660 [ Filter.Filter_Path_Section_Any
661 ])
662 ((("A"::Text):|[]))
663 , ": A" ~?
664 Filter.test
665 (Filter.Filter_Path Filter.Eq
666 [ Filter.Filter_Path_Section_Many
667 ])
668 ((("A"::Text):|[]))
669 , ":A A" ~?
670 Filter.test
671 (Filter.Filter_Path Filter.Eq
672 [ Filter.Filter_Path_Section_Many
673 , Filter.Filter_Path_Section_Text
674 (Filter.Filter_Text_Exact "A")
675 ])
676 ((("A"::Text):|[]))
677 , "A: A" ~?
678 Filter.test
679 (Filter.Filter_Path Filter.Eq
680 [ Filter.Filter_Path_Section_Text
681 (Filter.Filter_Text_Exact "A")
682 , Filter.Filter_Path_Section_Many
683 ])
684 ((("A"::Text):|[]))
685 , "A: A:B" ~?
686 Filter.test
687 (Filter.Filter_Path Filter.Eq
688 [ Filter.Filter_Path_Section_Text
689 (Filter.Filter_Text_Exact "A")
690 , Filter.Filter_Path_Section_Many
691 ])
692 ((("A"::Text):|"B":[]))
693 , "A:B A:B" ~?
694 Filter.test
695 (Filter.Filter_Path Filter.Eq
696 [ Filter.Filter_Path_Section_Text
697 (Filter.Filter_Text_Exact "A")
698 , Filter.Filter_Path_Section_Text
699 (Filter.Filter_Text_Exact "B")
700 ])
701 ((("A"::Text):|"B":[]))
702 , "A::B A:B" ~?
703 Filter.test
704 (Filter.Filter_Path Filter.Eq
705 [ Filter.Filter_Path_Section_Text
706 (Filter.Filter_Text_Exact "A")
707 , Filter.Filter_Path_Section_Many
708 , Filter.Filter_Path_Section_Many
709 , Filter.Filter_Path_Section_Text
710 (Filter.Filter_Text_Exact "B")
711 ])
712 ((("A"::Text):|"B":[]))
713 , ":B: A:B:C" ~?
714 Filter.test
715 (Filter.Filter_Path Filter.Eq
716 [ Filter.Filter_Path_Section_Many
717 , Filter.Filter_Path_Section_Text
718 (Filter.Filter_Text_Exact "B")
719 , Filter.Filter_Path_Section_Many
720 ])
721 ((("A"::Text):|"B":"C":[]))
722 , ":C A:B:C" ~?
723 Filter.test
724 (Filter.Filter_Path Filter.Eq
725 [ Filter.Filter_Path_Section_Many
726 , Filter.Filter_Path_Section_Text
727 (Filter.Filter_Text_Exact "C")
728 ])
729 ((("A"::Text):|"B":"C":[]))
730 , "<A:B:C::D A:B" ~?
731 Filter.test
732 (Filter.Filter_Path Filter.Lt
733 [ Filter.Filter_Path_Section_Text
734 (Filter.Filter_Text_Exact "A")
735 , Filter.Filter_Path_Section_Text
736 (Filter.Filter_Text_Exact "B")
737 , Filter.Filter_Path_Section_Text
738 (Filter.Filter_Text_Exact "C")
739 , Filter.Filter_Path_Section_Many
740 , Filter.Filter_Path_Section_Text
741 (Filter.Filter_Text_Exact "D")
742 ])
743 ((("A"::Text):|"B":[]))
744 , ">A:B:C::D A:B:C:CC:CCC:D:E" ~?
745 Filter.test
746 (Filter.Filter_Path Filter.Gt
747 [ Filter.Filter_Path_Section_Text
748 (Filter.Filter_Text_Exact "A")
749 , Filter.Filter_Path_Section_Text
750 (Filter.Filter_Text_Exact "B")
751 , Filter.Filter_Path_Section_Text
752 (Filter.Filter_Text_Exact "C")
753 , Filter.Filter_Path_Section_Many
754 , Filter.Filter_Path_Section_Text
755 (Filter.Filter_Text_Exact "D")
756 ])
757 ((("A"::Text):|"B":"C":"CC":"CCC":"D":"E":[]))
758 ]
759 , "Filter_Bool" ~: TestList
760 [ "Any A" ~?
761 Filter.test
762 (Filter.Any::Filter.Filter_Bool (Filter.Filter_Account (Tag.Tags, NonEmpty Text)))
763 (mempty, ("A":|[]))
764 ]
765 , "Filter_Ord" ~: TestList
766 [ "0 < (1, 2)" ~?
767 Filter.test
768 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer))
769 (fromJust $ (Lib.Interval.<=..<=) 1 2)
770 , "(-2, -1) < 0" ~?
771 Filter.test
772 (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer))
773 (fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
774 , "not (1 < (0, 2))" ~?
775 (not $ Filter.test
776 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer))
777 (fromJust $ (Lib.Interval.<=..<=) 0 2))
778 ]
779 ]
780 , "Read" ~: TestList
781 [ "filter_account" ~: TestList
782 [ "*" ~:
783 (Data.Either.rights $
784 [P.runParser
785 (Filter.Read.filter_account_path <* P.eof)
786 () "" ("*"::Text)])
787 ~?=
788 [ Filter.Filter_Path Filter.Eq
789 [ Filter.Filter_Path_Section_Any ]
790 ]
791 , "A" ~:
792 (Data.Either.rights $
793 [P.runParser
794 (Filter.Read.filter_account_path <* P.eof)
795 () "" ("A"::Text)])
796 ~?=
797 [ Filter.Filter_Path Filter.Eq
798 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A") ]
799 ]
800 , "AA" ~:
801 (Data.Either.rights $
802 [P.runParser
803 (Filter.Read.filter_account_path <* P.eof)
804 () "" ("AA"::Text)])
805 ~?=
806 [ Filter.Filter_Path Filter.Eq
807 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "AA") ]
808 ]
809 , "::A" ~:
810 (Data.Either.rights $
811 [P.runParser
812 (Filter.Read.filter_account_path <* P.eof)
813 () "" ("::A"::Text)])
814 ~?=
815 [ Filter.Filter_Path Filter.Eq
816 [ Filter.Filter_Path_Section_Many
817 , Filter.Filter_Path_Section_Many
818 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
819 ]
820 ]
821 , ":A" ~:
822 (Data.Either.rights $
823 [P.runParser
824 (Filter.Read.filter_account_path <* P.eof)
825 () "" (":A"::Text)])
826 ~?=
827 [ Filter.Filter_Path Filter.Eq
828 [ Filter.Filter_Path_Section_Many
829 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
830 ]
831 ]
832 , "A:" ~:
833 (Data.Either.rights $
834 [P.runParser
835 (Filter.Read.filter_account_path <* P.eof)
836 () "" ("A:"::Text)])
837 ~?=
838 [ Filter.Filter_Path Filter.Eq
839 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
840 , Filter.Filter_Path_Section_Many
841 ]
842 ]
843 , "A::" ~:
844 (Data.Either.rights $
845 [P.runParser
846 (Filter.Read.filter_account_path <* P.eof)
847 () "" ("A::"::Text)])
848 ~?=
849 [ Filter.Filter_Path Filter.Eq
850 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
851 , Filter.Filter_Path_Section_Many
852 , Filter.Filter_Path_Section_Many
853 ]
854 ]
855 , "A:B" ~:
856 (Data.Either.rights $
857 [P.runParser
858 (Filter.Read.filter_account_path <* P.eof)
859 () "" ("A:B"::Text)])
860 ~?=
861 [ Filter.Filter_Path Filter.Eq
862 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
863 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
864 ]
865 ]
866 , "A::B" ~:
867 (Data.Either.rights $
868 [P.runParser
869 (Filter.Read.filter_account_path <* P.eof)
870 () "" ("A::B"::Text)])
871 ~?=
872 [ Filter.Filter_Path Filter.Eq
873 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
874 , Filter.Filter_Path_Section_Many
875 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
876 ]
877 ]
878 , "A:::B" ~:
879 (Data.Either.rights $
880 [P.runParser
881 (Filter.Read.filter_account_path <* P.eof)
882 () "" ("A:::B"::Text)])
883 ~?=
884 [ Filter.Filter_Path Filter.Eq
885 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
886 , Filter.Filter_Path_Section_Many
887 , Filter.Filter_Path_Section_Many
888 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
889 ]
890 ]
891 , "A: " ~:
892 (Data.Either.rights $
893 [P.runParser
894 (Filter.Read.filter_account_path <* P.char ' ' <* P.eof)
895 () "" ("A: "::Text)])
896 ~?=
897 [ Filter.Filter_Path Filter.Eq
898 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
899 , Filter.Filter_Path_Section_Many
900 ]
901 ]
902 , "<=A:B" ~:
903 (Data.Either.rights $
904 [P.runParser
905 (Filter.Read.filter_account_path <* P.eof)
906 () "" ("<=A:B"::Text)])
907 ~?=
908 [ Filter.Filter_Path Filter.Le
909 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
910 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
911 ]
912 ]
913 , ">=A:B" ~:
914 (Data.Either.rights $
915 [P.runParser
916 (Filter.Read.filter_account_path <* P.eof)
917 () "" (">=A:B"::Text)])
918 ~?=
919 [ Filter.Filter_Path Filter.Ge
920 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
921 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
922 ]
923 ]
924 , "<A:B" ~:
925 (Data.Either.rights $
926 [P.runParser
927 (Filter.Read.filter_account_path <* P.eof)
928 () "" ("<A:B"::Text)])
929 ~?=
930 [ Filter.Filter_Path Filter.Lt
931 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
932 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
933 ]
934 ]
935 , ">A:B" ~:
936 (Data.Either.rights $
937 [P.runParser
938 (Filter.Read.filter_account_path <* P.eof)
939 () "" (">A:B"::Text)])
940 ~?=
941 [ Filter.Filter_Path Filter.Gt
942 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
943 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
944 ]
945 ]
946 ]
947 , "filter_bool" ~: TestList
948 [ "( E )" ~:
949 (Data.Either.rights $
950 [P.runParser
951 (Filter.Read.filter_bool
952 [ P.char 'E' >> return (return $ Filter.Bool True) ]
953 <* P.eof)
954 () "" ("( E )"::Text)])
955 ~?=
956 [ Filter.And (Filter.Bool True) Filter.Any
957 ]
958 , "( ( E ) )" ~:
959 (Data.Either.rights $
960 [P.runParser
961 (Filter.Read.filter_bool
962 [ P.char 'E' >> return (return $ Filter.Bool True) ]
963 <* P.eof)
964 () "" ("( ( E ) )"::Text)])
965 ~?=
966 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
967 ]
968 , "( E ) & ( E )" ~:
969 (Data.Either.rights $
970 [P.runParser
971 (Filter.Read.filter_bool
972 [ P.char 'E' >> return (return $ Filter.Bool True) ]
973 <* P.eof)
974 () "" ("( E ) & ( E )"::Text)])
975 ~?=
976 [ Filter.And
977 (Filter.And (Filter.Bool True) Filter.Any)
978 (Filter.And (Filter.Bool True) Filter.Any)
979 ]
980 , "( E ) + ( E )" ~:
981 (Data.Either.rights $
982 [P.runParser
983 (Filter.Read.filter_bool
984 [ P.char 'E' >> return (return $ Filter.Bool True) ]
985 <* P.eof)
986 () "" ("( E ) + ( E )"::Text)])
987 ~?=
988 [ Filter.Or
989 (Filter.And (Filter.Bool True) Filter.Any)
990 (Filter.And (Filter.Bool True) Filter.Any)
991 ]
992 , "( E ) - ( E )" ~:
993 (Data.Either.rights $
994 [P.runParser
995 (Filter.Read.filter_bool
996 [ P.char 'E' >> return (return $ Filter.Bool True) ]
997 <* P.eof)
998 () "" ("( E ) - ( E )"::Text)])
999 ~?=
1000 [ Filter.And
1001 (Filter.And (Filter.Bool True) Filter.Any)
1002 (Filter.Not (Filter.And (Filter.Bool True) Filter.Any))
1003 ]
1004 , "(- E )" ~:
1005 (Data.Either.rights $
1006 [P.runParser
1007 (Filter.Read.filter_bool
1008 [ P.char 'E' >> return (return $ Filter.Bool True) ]
1009 <* P.eof)
1010 () "" ("(- E )"::Text)])
1011 ~?=
1012 [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any
1013 ]
1014 ]
1015 ]
1016 ]
1017 , "Balance" ~: TestList
1018 [ "balance" ~:
1019 TestList
1020 [ "[A+$1] = A+$1 & $+1" ~:
1021 (Balance.cons
1022 ( (("A"::Text):|[])
1023 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1024 )
1025 Balance.empty)
1026 ~?=
1027 (Balance.Balance
1028 { Balance.balance_by_account =
1029 TreeMap.from_List const $
1030 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1031 [ ("A":|[], amounts [ amount_usd $ 1 ]) ]
1032 , Balance.balance_by_unit =
1033 Balance.Balance_by_Unit $
1034 Map.fromList $
1035 [ amount_usd $ Balance.Unit_Sum
1036 { Balance.unit_sum_quantity = Polarize.polarize $ 1
1037 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1038 ["A":|[]]
1039 }
1040 ]
1041 }
1042 )
1043 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
1044 (List.foldl (flip Balance.cons)
1045 Balance.empty
1046 [ ( (("A"::Text):|[])
1047 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1048 )
1049 , ( ("A":|[])
1050 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1 ]
1051 )
1052 ])
1053 ~?=
1054 Balance.Balance
1055 { Balance.balance_by_account =
1056 TreeMap.from_List const $
1057 [ ( "A":|[]
1058 , Balance.Account_Sum $
1059 Map.fromListWith const $
1060 [ amount_usd $ Polarize.Polarized_Both (-1) ( 1)
1061 ]
1062 ) ]
1063 , Balance.balance_by_unit =
1064 Balance.Balance_by_Unit $ Map.fromList $
1065 [ amount_usd $ Balance.Unit_Sum
1066 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) ( 1)
1067 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1068 ["A":|[]]
1069 }
1070 ]
1071 }
1072 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
1073 (List.foldl (flip Balance.cons)
1074 Balance.empty
1075 [ ( (("A"::Text):|[])
1076 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1077 )
1078 , ( ("A":|[])
1079 , Map.map Polarize.polarize $ amounts [ amount_eur $ -1 ]
1080 )
1081 ])
1082 ~?=
1083 Balance.Balance
1084 { Balance.balance_by_account =
1085 TreeMap.from_List const $
1086 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1087 [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ -1 ]) ]
1088 , Balance.balance_by_unit =
1089 Balance.Balance_by_Unit $ Map.fromList $
1090 [ amount_usd $ Balance.Unit_Sum
1091 { Balance.unit_sum_quantity = Polarize.Polarized_Positive 1
1092 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1093 ["A":|[]]
1094 }
1095 , amount_eur $ Balance.Unit_Sum
1096 { Balance.unit_sum_quantity = Polarize.Polarized_Negative (-1)
1097 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1098 ["A":|[]]
1099 }
1100 ]
1101 }
1102 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
1103 (List.foldl (flip Balance.cons)
1104 Balance.empty
1105 [ ( (("A"::Text):|[])
1106 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1107 )
1108 , ( ("B":|[])
1109 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1 ]
1110 )
1111 ])
1112 ~?=
1113 Balance.Balance
1114 { Balance.balance_by_account =
1115 TreeMap.from_List const $
1116 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1117 [ ("A":|[], amounts [ amount_usd $ 1 ])
1118 , ("B":|[], amounts [ amount_usd $ -1 ])
1119 ]
1120 , Balance.balance_by_unit =
1121 Balance.Balance_by_Unit $ Map.fromList $
1122 [ amount_usd $ Balance.Unit_Sum
1123 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) 1
1124 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1125 ["A":|[], "B":|[]]
1126 }
1127 ]
1128 }
1129 , "[A+$1, B+$1]" ~:
1130 (List.foldl (flip Balance.cons)
1131 Balance.empty
1132 [ ( (("A"::Text):|[])
1133 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1134 )
1135 , ( ("B":|[])
1136 , Map.map Polarize.polarize $ amounts [ amount_usd $ 1 ]
1137 )
1138 ])
1139 ~?=
1140 Balance.Balance
1141 { Balance.balance_by_account =
1142 TreeMap.from_List const $
1143 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1144 [ ("A":|[], amounts [ amount_usd $ 1 ])
1145 , ("B":|[], amounts [ amount_usd $ 1 ])
1146 ]
1147 , Balance.balance_by_unit =
1148 Balance.Balance_by_Unit $ Map.fromList $
1149 [ amount_usd $ Balance.Unit_Sum
1150 { Balance.unit_sum_quantity = Polarize.polarize 2
1151 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1152 ["A":|[], "B":|[]]
1153 }
1154 ]
1155 }
1156 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
1157 (List.foldl (flip Balance.cons)
1158 Balance.empty
1159 [ ( (("A"::Text):|[])
1160 , Map.map Polarize.polarize $ amounts [ amount_usd $ 1, amount_eur $ (2::Integer) ]
1161 )
1162 , ( ("A":|[])
1163 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1, amount_eur $ -2 ]
1164 )
1165 ])
1166 ~?=
1167 Balance.Balance
1168 { Balance.balance_by_account =
1169 TreeMap.from_List const $
1170 [ ("A":|[]
1171 , Balance.Account_Sum $
1172 Map.fromListWith const $
1173 [ amount_usd $ Polarize.Polarized_Both (-1) 1
1174 , amount_eur $ Polarize.Polarized_Both (-2) 2
1175 ]
1176 )
1177 ]
1178 , Balance.balance_by_unit =
1179 Balance.Balance_by_Unit $ Map.fromList $
1180 [ amount_usd $ Balance.Unit_Sum
1181 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) 1
1182 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1183 ["A":|[]]
1184 }
1185 , amount_eur $ Balance.Unit_Sum
1186 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-2) 2
1187 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1188 ["A":|[]]
1189 }
1190 ]
1191 }
1192 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
1193 (List.foldl (flip Balance.cons)
1194 Balance.empty
1195 [ ( (("A"::Text):|[])
1196 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer), amount_eur $ 2, amount_gbp $ 3 ]
1197 )
1198 , ( ("B":|[])
1199 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ]
1200 )
1201 ])
1202 ~?=
1203 Balance.Balance
1204 { Balance.balance_by_account =
1205 TreeMap.from_List const $
1206 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1207 [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ 2, amount_gbp $ 3 ])
1208 , ("B":|[], amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ])
1209 ]
1210 , Balance.balance_by_unit =
1211 Balance.Balance_by_Unit $
1212 Map.fromList $
1213 [ amount_usd $ Balance.Unit_Sum
1214 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) 1
1215 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1216 ["A":|[], "B":|[]]
1217 }
1218 , amount_eur $ Balance.Unit_Sum
1219 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-2) 2
1220 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1221 ["A":|[], "B":|[]]
1222 }
1223 , amount_gbp $ Balance.Unit_Sum
1224 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-3) 3
1225 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1226 ["A":|[], "B":|[]]
1227 }
1228 ]
1229 }
1230 ]
1231 , "union" ~: TestList
1232 [ "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
1233 Balance.union
1234 (Balance.Balance
1235 { Balance.balance_by_account =
1236 TreeMap.from_List const $
1237 [ ( "A":|[]
1238 , Balance.Account_Sum $
1239 Map.fromListWith const $
1240 [ amount_usd $ Polarize.polarize 1 ]
1241 )
1242 ]
1243 , Balance.balance_by_unit =
1244 Balance.Balance_by_Unit $ Map.fromList $
1245 [ amount_usd $ Balance.Unit_Sum
1246 { Balance.unit_sum_quantity = Polarize.polarize 1
1247 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1248 ["A":|[]]
1249 }
1250 ]
1251 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1252 (Balance.Balance
1253 { Balance.balance_by_account =
1254 TreeMap.from_List const $
1255 [ ( "A":|[]
1256 , Balance.Account_Sum $
1257 Map.fromListWith const $
1258 [ amount_usd $ Polarize.polarize 1 ]
1259 )
1260 ]
1261 , Balance.balance_by_unit =
1262 Balance.Balance_by_Unit $ Map.fromList $
1263 [ amount_usd $ Balance.Unit_Sum
1264 { Balance.unit_sum_quantity = Polarize.polarize 1
1265 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1266 ["A":|[]]
1267 }
1268 ]
1269 })
1270 ~?=
1271 Balance.Balance
1272 { Balance.balance_by_account =
1273 TreeMap.from_List const $
1274 [ ( ("A":|[])
1275 , Balance.Account_Sum $
1276 Map.fromListWith const $
1277 [ amount_usd $ Polarize.polarize 2 ]
1278 )
1279 ]
1280 , Balance.balance_by_unit =
1281 Balance.Balance_by_Unit $ Map.fromList $
1282 [ amount_usd $ Balance.Unit_Sum
1283 { Balance.unit_sum_quantity = Polarize.polarize 2
1284 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1285 ["A":|[]]
1286 }
1287 ]
1288 }
1289 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
1290 Balance.union
1291 (Balance.Balance
1292 { Balance.balance_by_account =
1293 TreeMap.from_List const $
1294 [ ( ("A":|[])
1295 , Balance.Account_Sum $
1296 Map.fromListWith const $
1297 [ amount_usd $ Polarize.polarize 1 ]
1298 )
1299 ]
1300 , Balance.balance_by_unit =
1301 Balance.Balance_by_Unit $ Map.fromList $
1302 [ amount_usd $ Balance.Unit_Sum
1303 { Balance.unit_sum_quantity = Polarize.polarize 1
1304 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1305 ["A":|[]]
1306 }
1307 ]
1308 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1309 (Balance.Balance
1310 { Balance.balance_by_account =
1311 TreeMap.from_List const $
1312 [ ( ("B":|[])
1313 , Balance.Account_Sum $
1314 Map.fromListWith const $
1315 [ amount_usd $ Polarize.polarize 1 ]
1316 )
1317 ]
1318 , Balance.balance_by_unit =
1319 Balance.Balance_by_Unit $ Map.fromList $
1320 [ amount_usd $ Balance.Unit_Sum
1321 { Balance.unit_sum_quantity = Polarize.polarize 1
1322 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1323 ["B":|[]]
1324 }
1325 ]
1326 })
1327 ~?=
1328 Balance.Balance
1329 { Balance.balance_by_account =
1330 TreeMap.from_List const $
1331 [ ( ("A":|[])
1332 , Balance.Account_Sum $
1333 Map.fromListWith const $
1334 [ amount_usd $ Polarize.polarize 1 ]
1335 )
1336 , ( ("B":|[])
1337 , Balance.Account_Sum $
1338 Map.fromListWith const $
1339 [ amount_usd $ Polarize.polarize 1 ]
1340 )
1341 ]
1342 , Balance.balance_by_unit =
1343 Balance.Balance_by_Unit $ Map.fromList $
1344 [ amount_usd $ Balance.Unit_Sum
1345 { Balance.unit_sum_quantity = Polarize.polarize 2
1346 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1347 ["A":|[], "B":|[]]
1348 }
1349 ]
1350 }
1351 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
1352 Balance.union
1353 (Balance.Balance
1354 { Balance.balance_by_account =
1355 TreeMap.from_List const $
1356 [ ( ("A":|[])
1357 , Balance.Account_Sum $
1358 Map.fromListWith const $
1359 [ amount_usd $ Polarize.polarize 1 ]
1360 )
1361 ]
1362 , Balance.balance_by_unit =
1363 Balance.Balance_by_Unit $ Map.fromList $
1364 [ amount_usd $ Balance.Unit_Sum
1365 { Balance.unit_sum_quantity = Polarize.polarize 1
1366 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1367 ["A":|[]]
1368 }
1369 ]
1370 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1371 (Balance.Balance
1372 { Balance.balance_by_account =
1373 TreeMap.from_List const $
1374 [ ( ("B":|[])
1375 , Balance.Account_Sum $
1376 Map.fromListWith const $
1377 [ amount_eur $ Polarize.polarize 1 ]
1378 )
1379 ]
1380 , Balance.balance_by_unit =
1381 Balance.Balance_by_Unit $ Map.fromList $
1382 [ amount_eur $ Balance.Unit_Sum
1383 { Balance.unit_sum_quantity = Polarize.polarize 1
1384 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1385 ["B":|[]]
1386 }
1387 ]
1388 })
1389 ~?=
1390 Balance.Balance
1391 { Balance.balance_by_account =
1392 TreeMap.from_List const $
1393 [ ( ("A":|[])
1394 , Balance.Account_Sum $
1395 Map.fromListWith const $
1396 [ amount_usd $ Polarize.polarize 1 ]
1397 )
1398 , ( ("B":|[])
1399 , Balance.Account_Sum $
1400 Map.fromListWith const $
1401 [ amount_eur $ Polarize.polarize 1 ]
1402 )
1403 ]
1404 , Balance.balance_by_unit =
1405 Balance.Balance_by_Unit $ Map.fromList $
1406 [ amount_usd $ Balance.Unit_Sum
1407 { Balance.unit_sum_quantity = Polarize.polarize 1
1408 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1409 ["A":|[]]
1410 }
1411 , amount_eur $ Balance.Unit_Sum
1412 { Balance.unit_sum_quantity = Polarize.polarize 1
1413 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1414 ["B":|[]]
1415 }
1416 ]
1417 }
1418 ]
1419 , "expanded" ~: TestList
1420 [ "mempty" ~:
1421 Balance.expanded TreeMap.empty
1422 ~?=
1423 (TreeMap.empty::Balance.Expanded (NonEmpty Text) Text Integer)
1424 , "A+$1 = A+$1" ~:
1425 Balance.expanded
1426 (TreeMap.from_List const $
1427 [ ( ("A":|[])
1428 , Balance.Account_Sum $
1429 Map.fromListWith const $
1430 [ amount_usd $ Polarize.polarize 1 ]
1431 )
1432 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1433 ~?=
1434 (TreeMap.from_List const $
1435 [ ("A":|[], Balance.Account_Sum_Expanded
1436 { Balance.inclusive =
1437 Balance.Account_Sum $
1438 Map.map Polarize.polarize $
1439 amounts [ amount_usd $ 1 ]
1440 , Balance.exclusive =
1441 Balance.Account_Sum $
1442 Map.map Polarize.polarize $
1443 amounts [ amount_usd $ 1 ]
1444 })
1445 ])
1446 , "A/A+$1 = A+$1 A/A+$1" ~:
1447 Balance.expanded
1448 (TreeMap.from_List const $
1449 [ ( ("A":|["A"])
1450 , Balance.Account_Sum $
1451 Map.fromListWith const $
1452 [ amount_usd $ Polarize.polarize 1 ]
1453 )
1454 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1455 ~?=
1456 (TreeMap.from_List const
1457 [ ("A":|[], Balance.Account_Sum_Expanded
1458 { Balance.inclusive =
1459 Balance.Account_Sum $
1460 Map.map Polarize.polarize $
1461 amounts [ amount_usd $ 1 ]
1462 , Balance.exclusive =
1463 Balance.Account_Sum $
1464 Map.map Polarize.polarize $
1465 amounts []
1466 })
1467 , ("A":|["A"], Balance.Account_Sum_Expanded
1468 { Balance.inclusive =
1469 Balance.Account_Sum $
1470 Map.map Polarize.polarize $
1471 amounts [ amount_usd $ 1 ]
1472 , Balance.exclusive =
1473 Balance.Account_Sum $
1474 Map.map Polarize.polarize $
1475 amounts [ amount_usd $ 1 ]
1476 })
1477 ])
1478 , "A/B+$1 = A+$1 A/B+$1" ~:
1479 Balance.expanded
1480 (TreeMap.from_List const $
1481 [ ( ("A":|["B"])
1482 , Balance.Account_Sum $
1483 Map.fromListWith const $
1484 [ amount_usd $ Polarize.polarize 1 ]
1485 )
1486 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1487 ~?=
1488 (TreeMap.from_List const
1489 [ ("A":|[], Balance.Account_Sum_Expanded
1490 { Balance.inclusive =
1491 Balance.Account_Sum $
1492 Map.map Polarize.polarize $
1493 amounts [ amount_usd $ 1 ]
1494 , Balance.exclusive =
1495 Balance.Account_Sum $
1496 Map.map Polarize.polarize $
1497 amounts []
1498 })
1499 , ("A":|["B"], Balance.Account_Sum_Expanded
1500 { Balance.inclusive =
1501 Balance.Account_Sum $
1502 Map.map Polarize.polarize $
1503 amounts [ amount_usd $ 1 ]
1504 , Balance.exclusive =
1505 Balance.Account_Sum $
1506 Map.map Polarize.polarize $
1507 amounts [ amount_usd $ 1 ]
1508 })
1509 ])
1510 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
1511 Balance.expanded
1512 (TreeMap.from_List const $
1513 [ ( ("A":|["B", "C"])
1514 , Balance.Account_Sum $
1515 Map.fromListWith const $
1516 [ amount_usd $ Polarize.polarize 1 ]
1517 )
1518 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1519 ~?=
1520 (TreeMap.from_List const $
1521 [ ("A":|[], Balance.Account_Sum_Expanded
1522 { Balance.inclusive =
1523 Balance.Account_Sum $
1524 Map.map Polarize.polarize $
1525 amounts [ amount_usd $ 1 ]
1526 , Balance.exclusive =
1527 Balance.Account_Sum $
1528 Map.map Polarize.polarize $
1529 amounts []
1530 })
1531 , ("A":|["B"], Balance.Account_Sum_Expanded
1532 { Balance.inclusive =
1533 Balance.Account_Sum $
1534 Map.map Polarize.polarize $
1535 amounts [ amount_usd $ 1 ]
1536 , Balance.exclusive =
1537 Balance.Account_Sum $
1538 Map.map Polarize.polarize $
1539 amounts []
1540 })
1541 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
1542 { Balance.inclusive =
1543 Balance.Account_Sum $
1544 Map.map Polarize.polarize $
1545 amounts [ amount_usd $ 1 ]
1546 , Balance.exclusive =
1547 Balance.Account_Sum $
1548 Map.map Polarize.polarize $
1549 amounts [ amount_usd $ 1 ]
1550 })
1551 ])
1552 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
1553 Balance.expanded
1554 (TreeMap.from_List const $
1555 [ ( ("A":|[])
1556 , Balance.Account_Sum $
1557 Map.fromListWith const $
1558 [ amount_usd $ Polarize.polarize 1 ]
1559 )
1560 , ( ("A":|["B"])
1561 , Balance.Account_Sum $
1562 Map.fromListWith const $
1563 [ amount_usd $ Polarize.polarize 1 ]
1564 )
1565 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1566 ~?=
1567 (TreeMap.from_List const
1568 [ ("A":|[], Balance.Account_Sum_Expanded
1569 { Balance.inclusive =
1570 Balance.Account_Sum $
1571 Map.map Polarize.polarize $
1572 amounts [ amount_usd $ 2 ]
1573 , Balance.exclusive =
1574 Balance.Account_Sum $
1575 Map.map Polarize.polarize $
1576 amounts [ amount_usd $ 1 ]
1577 })
1578 , ("A":|["B"], Balance.Account_Sum_Expanded
1579 { Balance.inclusive =
1580 Balance.Account_Sum $
1581 Map.map Polarize.polarize $
1582 amounts [ amount_usd $ 1 ]
1583 , Balance.exclusive =
1584 Balance.Account_Sum $
1585 Map.map Polarize.polarize $
1586 amounts [ amount_usd $ 1 ]
1587 })
1588 ])
1589 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
1590 Balance.expanded
1591 (TreeMap.from_List const $
1592 [ ( ("A":|[])
1593 , Balance.Account_Sum $
1594 Map.fromListWith const $
1595 [ amount_usd $ Polarize.polarize 1 ]
1596 )
1597 , ( ("A":|["B"])
1598 , Balance.Account_Sum $
1599 Map.fromListWith const $
1600 [ amount_usd $ Polarize.polarize 1 ]
1601 )
1602 , ( ("A":|["B", "C"])
1603 , Balance.Account_Sum $
1604 Map.fromListWith const $
1605 [ amount_usd $ Polarize.polarize 1 ]
1606 )
1607 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1608 ~?=
1609 (TreeMap.from_List const
1610 [ ("A":|[], Balance.Account_Sum_Expanded
1611 { Balance.inclusive =
1612 Balance.Account_Sum $
1613 Map.map Polarize.polarize $
1614 amounts [ amount_usd $ 3 ]
1615 , Balance.exclusive =
1616 Balance.Account_Sum $
1617 Map.map Polarize.polarize $
1618 amounts [ amount_usd $ 1 ]
1619 })
1620 , ("A":|["B"], Balance.Account_Sum_Expanded
1621 { Balance.inclusive =
1622 Balance.Account_Sum $
1623 Map.map Polarize.polarize $
1624 amounts [ amount_usd $ 2 ]
1625 , Balance.exclusive =
1626 Balance.Account_Sum $
1627 Map.map Polarize.polarize $
1628 amounts [ amount_usd $ 1 ]
1629 })
1630 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
1631 { Balance.inclusive =
1632 Balance.Account_Sum $
1633 Map.map Polarize.polarize $
1634 amounts [ amount_usd $ 1 ]
1635 , Balance.exclusive =
1636 Balance.Account_Sum $
1637 Map.map Polarize.polarize $
1638 amounts [ amount_usd $ 1 ]
1639 })
1640 ])
1641 , "A+$1 A/B+$1 A/B/C+$1 A/B/C/D+$1 = A+$4 A/B+$3 A/B/C+$2 A/B/C/D+$1" ~:
1642 Balance.expanded
1643 (TreeMap.from_List const $
1644 [ ( ("A":|[])
1645 , Balance.Account_Sum $
1646 Map.fromListWith const $
1647 [ amount_usd $ Polarize.polarize 1 ]
1648 )
1649 , ( ("A":|["B"])
1650 , Balance.Account_Sum $
1651 Map.fromListWith const $
1652 [ amount_usd $ Polarize.polarize 1 ]
1653 )
1654 , ( ("A":|["B", "C"])
1655 , Balance.Account_Sum $
1656 Map.fromListWith const $
1657 [ amount_usd $ Polarize.polarize 1 ]
1658 )
1659 , ( ("A":|["B", "C", "D"])
1660 , Balance.Account_Sum $
1661 Map.fromListWith const $
1662 [ amount_usd $ Polarize.polarize 1 ]
1663 )
1664 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1665 ~?=
1666 (TreeMap.from_List const
1667 [ ("A":|[], Balance.Account_Sum_Expanded
1668 { Balance.inclusive =
1669 Balance.Account_Sum $
1670 Map.map Polarize.polarize $
1671 amounts [ amount_usd $ 4 ]
1672 , Balance.exclusive =
1673 Balance.Account_Sum $
1674 Map.map Polarize.polarize $
1675 amounts [ amount_usd $ 1 ]
1676 })
1677 , ("A":|["B"], Balance.Account_Sum_Expanded
1678 { Balance.inclusive =
1679 Balance.Account_Sum $
1680 Map.map Polarize.polarize $
1681 amounts [ amount_usd $ 3 ]
1682 , Balance.exclusive =
1683 Balance.Account_Sum $
1684 Map.map Polarize.polarize $
1685 amounts [ amount_usd $ 1 ]
1686 })
1687 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
1688 { Balance.inclusive =
1689 Balance.Account_Sum $
1690 Map.map Polarize.polarize $
1691 amounts [ amount_usd $ 2 ]
1692 , Balance.exclusive =
1693 Balance.Account_Sum $
1694 Map.map Polarize.polarize $
1695 amounts [ amount_usd $ 1 ]
1696 })
1697 , ("A":|["B", "C", "D"], Balance.Account_Sum_Expanded
1698 { Balance.inclusive =
1699 Balance.Account_Sum $
1700 Map.map Polarize.polarize $
1701 amounts [ amount_usd $ 1 ]
1702 , Balance.exclusive =
1703 Balance.Account_Sum $
1704 Map.map Polarize.polarize $
1705 amounts [ amount_usd $ 1 ]
1706 })
1707 ])
1708 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
1709 Balance.expanded
1710 (TreeMap.from_List const $
1711 [ ( ("A":|[])
1712 , Balance.Account_Sum $
1713 Map.fromListWith const $
1714 [ amount_usd $ Polarize.polarize 1 ]
1715 )
1716 , ( ("A":|["B"])
1717 , Balance.Account_Sum $
1718 Map.fromListWith const $
1719 [ amount_usd $ Polarize.polarize 1 ]
1720 )
1721 , ( ("A":|["BB"])
1722 , Balance.Account_Sum $
1723 Map.fromListWith const $
1724 [ amount_usd $ Polarize.polarize 1 ]
1725 )
1726 , ( ("AA":|["B"])
1727 , Balance.Account_Sum $
1728 Map.fromListWith const $
1729 [ amount_usd $ Polarize.polarize 1 ]
1730 )
1731 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1732 ~?=
1733 (TreeMap.from_List const
1734 [ ("A":|[], Balance.Account_Sum_Expanded
1735 { Balance.inclusive =
1736 Balance.Account_Sum $
1737 Map.map Polarize.polarize $
1738 amounts [ amount_usd $ 3 ]
1739 , Balance.exclusive =
1740 Balance.Account_Sum $
1741 Map.map Polarize.polarize $
1742 amounts [ amount_usd $ 1 ]
1743 })
1744 , ("A":|["B"], Balance.Account_Sum_Expanded
1745 { Balance.inclusive =
1746 Balance.Account_Sum $
1747 Map.map Polarize.polarize $
1748 amounts [ amount_usd $ 1 ]
1749 , Balance.exclusive =
1750 Balance.Account_Sum $
1751 Map.map Polarize.polarize $
1752 amounts [ amount_usd $ 1 ]
1753 })
1754 , ("A":|["BB"], Balance.Account_Sum_Expanded
1755 { Balance.inclusive =
1756 Balance.Account_Sum $
1757 Map.map Polarize.polarize $
1758 amounts [ amount_usd $ 1 ]
1759 , Balance.exclusive =
1760 Balance.Account_Sum $
1761 Map.map Polarize.polarize $
1762 amounts [ amount_usd $ 1 ]
1763 })
1764 , ("AA":|[], Balance.Account_Sum_Expanded
1765 { Balance.inclusive =
1766 Balance.Account_Sum $
1767 Map.map Polarize.polarize $
1768 amounts [ amount_usd $ 1 ]
1769 , Balance.exclusive =
1770 Balance.Account_Sum $
1771 Map.map Polarize.polarize $
1772 amounts []
1773 })
1774 , ("AA":|["B"], Balance.Account_Sum_Expanded
1775 { Balance.inclusive =
1776 Balance.Account_Sum $
1777 Map.map Polarize.polarize $
1778 amounts [ amount_usd $ 1 ]
1779 , Balance.exclusive =
1780 Balance.Account_Sum $
1781 Map.map Polarize.polarize $
1782 amounts [ amount_usd $ 1 ]
1783 })
1784 ])
1785 ]
1786 , "deviation" ~: TestList
1787 [ "{A+$1, $1}" ~:
1788 (Balance.deviation $
1789 Balance.Balance
1790 { Balance.balance_by_account =
1791 TreeMap.from_List const $
1792 [ ( ("A":|[])
1793 , Balance.Account_Sum $
1794 Map.fromListWith const $
1795 [ amount_usd $ Polarize.polarize 1 ]
1796 )
1797 , ( ("B":|[])
1798 , Balance.Account_Sum $
1799 Map.fromListWith const $
1800 [ ]
1801 )
1802 ]
1803 , Balance.balance_by_unit =
1804 Balance.Balance_by_Unit $ Map.fromList $
1805 [ amount_usd $ Balance.Unit_Sum
1806 { Balance.unit_sum_quantity = Polarize.polarize 1
1807 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1808 ["A":|[]]
1809 }
1810 ]
1811 }::Balance.Deviation (NonEmpty Text) Text (Polarize.Polarized Integer))
1812 ~?=
1813 (Balance.Deviation $
1814 Balance.Balance_by_Unit $ Map.fromList $
1815 [ amount_usd $ Balance.Unit_Sum
1816 { Balance.unit_sum_quantity = Polarize.polarize 1
1817 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1818 ["B":|[]]
1819 }
1820 ])
1821 , "{A+$1 B+$1, $2}" ~:
1822 (Balance.deviation $
1823 Balance.Balance
1824 { Balance.balance_by_account =
1825 TreeMap.from_List const $
1826 [ ( ("A":|[])
1827 , Balance.Account_Sum $
1828 Map.fromListWith const $
1829 [ amount_usd $ Polarize.polarize 1 ]
1830 )
1831 , ( ("B":|[])
1832 , Balance.Account_Sum $
1833 Map.fromListWith const $
1834 [ amount_usd $ Polarize.polarize 1 ]
1835 )
1836 ]
1837 , Balance.balance_by_unit =
1838 Balance.Balance_by_Unit $ Map.fromList $
1839 [ amount_usd $ Balance.Unit_Sum
1840 { Balance.unit_sum_quantity = Polarize.polarize 2
1841 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1842 [ "A":|[]
1843 , "B":|[]
1844 ]
1845 }
1846 ]
1847 }::Balance.Deviation (NonEmpty Text) Text (Polarize.Polarized Integer))
1848 ~?=
1849 (Balance.Deviation $
1850 Balance.Balance_by_Unit $ Map.fromList $
1851 [ amount_usd $ Balance.Unit_Sum
1852 { Balance.unit_sum_quantity = Polarize.polarize 2
1853 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1854 [
1855 ]
1856 }
1857 ])
1858 ]
1859 , "is_equilibrium_inferrable" ~: TestList
1860 [ "empty" ~: TestCase $
1861 (@=?) True $
1862 Balance.is_equilibrium_inferrable $
1863 Balance.deviation $
1864 (Balance.empty::Balance.Balance (NonEmpty Text) Text Integer)
1865 , "{A+$0, $+0}" ~: TestCase $
1866 (@=?) True $
1867 Balance.is_equilibrium_inferrable $
1868 Balance.deviation $
1869 (Balance.Balance
1870 { Balance.balance_by_account =
1871 TreeMap.from_List const $
1872 [ ( ("A":|[])
1873 , Balance.Account_Sum $
1874 Map.fromListWith const $
1875 [ amount_usd $ Polarize.polarize 0 ]
1876 )
1877 ]
1878 , Balance.balance_by_unit =
1879 Balance.Balance_by_Unit $ Map.fromList $
1880 [ amount_usd $ Balance.Unit_Sum
1881 { Balance.unit_sum_quantity = Polarize.polarize 0
1882 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1883 ["A":|[]]
1884 }
1885 ]
1886 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1887 , "{A+$1, $+1}" ~: TestCase $
1888 (@=?) False $
1889 Balance.is_equilibrium_inferrable $
1890 Balance.deviation $
1891 (Balance.Balance
1892 { Balance.balance_by_account =
1893 TreeMap.from_List const $
1894 [ ( ("A":|[])
1895 , Balance.Account_Sum $
1896 Map.fromListWith const $
1897 [ amount_usd $ Polarize.polarize 1 ]
1898 )
1899 ]
1900 , Balance.balance_by_unit =
1901 Balance.Balance_by_Unit $ Map.fromList $
1902 [ amount_usd $ Balance.Unit_Sum
1903 { Balance.unit_sum_quantity = Polarize.polarize 1
1904 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1905 ["A":|[]]
1906 }
1907 ]
1908 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1909 , "{A+$0+€0, $0 €+0}" ~: TestCase $
1910 (@=?) True $
1911 Balance.is_equilibrium_inferrable $
1912 Balance.deviation $
1913 (Balance.Balance
1914 { Balance.balance_by_account =
1915 TreeMap.from_List const $
1916 [ ( ("A":|[])
1917 , Balance.Account_Sum $
1918 Map.fromListWith const $
1919 [ amount_usd $ Polarize.polarize 0
1920 , amount_eur $ Polarize.polarize 0
1921 ]
1922 )
1923 ]
1924 , Balance.balance_by_unit =
1925 Balance.Balance_by_Unit $ Map.fromList $
1926 [ amount_usd $ Balance.Unit_Sum
1927 { Balance.unit_sum_quantity = Polarize.polarize 0
1928 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1929 ["A":|[]]
1930 }
1931 , amount_eur $ Balance.Unit_Sum
1932 { Balance.unit_sum_quantity = Polarize.polarize 0
1933 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1934 ["A":|[]]
1935 }
1936 ]
1937 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1938 , "{A+$1, B-$1, $+0}" ~: TestCase $
1939 (@=?) True $
1940 Balance.is_equilibrium_inferrable $
1941 Balance.deviation $
1942 (Balance.Balance
1943 { Balance.balance_by_account =
1944 TreeMap.from_List const $
1945 [ ( ("A":|[])
1946 , Balance.Account_Sum $
1947 Map.fromListWith const $
1948 [ amount_usd $ Polarize.polarize 1 ]
1949 )
1950 , ( ("B":|[])
1951 , Balance.Account_Sum $
1952 Map.fromListWith const $
1953 [ amount_usd $ Polarize.polarize (-1) ]
1954 )
1955 ]
1956 , Balance.balance_by_unit =
1957 Balance.Balance_by_Unit $ Map.fromList $
1958 [ amount_usd $ Balance.Unit_Sum
1959 { Balance.unit_sum_quantity = Polarize.polarize 0
1960 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1961 ["A":|[], "B":|[]]
1962 }
1963 ]
1964 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1965 , "{A+$1 B, $+1}" ~: TestCase $
1966 (@=?) True $
1967 Balance.is_equilibrium_inferrable $
1968 Balance.deviation $
1969 (Balance.Balance
1970 { Balance.balance_by_account =
1971 TreeMap.from_List const $
1972 [ ( ("A":|[])
1973 , Balance.Account_Sum $
1974 Map.fromListWith const $
1975 [ amount_usd $ Polarize.polarize 1 ]
1976 )
1977 , ( ("B":|[])
1978 , Balance.Account_Sum $
1979 Map.fromListWith const $
1980 [ ]
1981 )
1982 ]
1983 , Balance.balance_by_unit =
1984 Balance.Balance_by_Unit $ Map.fromList $
1985 [ amount_usd $ Balance.Unit_Sum
1986 { Balance.unit_sum_quantity = Polarize.polarize 1
1987 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1988 ["A":|[]]
1989 }
1990 ]
1991 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1992 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
1993 (@=?) True $
1994 Balance.is_equilibrium_inferrable $
1995 Balance.deviation $
1996 (Balance.Balance
1997 { Balance.balance_by_account =
1998 TreeMap.from_List const $
1999 [ ( ("A":|[])
2000 , Balance.Account_Sum $
2001 Map.fromListWith const $
2002 [ amount_usd $ Polarize.polarize 1 ]
2003 )
2004 , ( ("B":|[])
2005 , Balance.Account_Sum $
2006 Map.fromListWith const $
2007 [ amount_eur $ Polarize.polarize 1 ]
2008 )
2009 ]
2010 , Balance.balance_by_unit =
2011 Balance.Balance_by_Unit $ Map.fromList $
2012 [ amount_usd $ Balance.Unit_Sum
2013 { Balance.unit_sum_quantity = Polarize.polarize 1
2014 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2015 ["A":|[]]
2016 }
2017 , amount_eur $ Balance.Unit_Sum
2018 { Balance.unit_sum_quantity = Polarize.polarize 1
2019 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2020 ["B":|[]]
2021 }
2022 ]
2023 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
2024 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
2025 (@=?) True $
2026 Balance.is_equilibrium_inferrable $
2027 Balance.deviation $
2028 (Balance.Balance
2029 { Balance.balance_by_account =
2030 TreeMap.from_List const $
2031 [ ( ("A":|[])
2032 , Balance.Account_Sum $
2033 Map.fromListWith const $
2034 [ amount_usd $ Polarize.polarize 1 ]
2035 )
2036 , ( ("B":|[])
2037 , Balance.Account_Sum $
2038 Map.fromListWith const $
2039 [ amount_usd $ Polarize.polarize (-1)
2040 , amount_eur $ Polarize.polarize 1
2041 ]
2042 )
2043 ]
2044 , Balance.balance_by_unit =
2045 Balance.Balance_by_Unit $ Map.fromList $
2046 [ amount_usd $ Balance.Unit_Sum
2047 { Balance.unit_sum_quantity = Polarize.polarize 0
2048 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2049 ["A":|[], "B":|[]]
2050 }
2051 , amount_eur $ Balance.Unit_Sum
2052 { Balance.unit_sum_quantity = Polarize.polarize 1
2053 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2054 ["B":|[]]
2055 }
2056 ]
2057 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
2058 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
2059 (@=?) True $
2060 Balance.is_equilibrium_inferrable $
2061 Balance.deviation $
2062 (Balance.Balance
2063 { Balance.balance_by_account =
2064 TreeMap.from_List const $
2065 [ ( ("A":|[])
2066 , Balance.Account_Sum $
2067 Map.fromListWith const $
2068 [ amount_usd $ Polarize.polarize 1
2069 , amount_eur $ Polarize.polarize 2
2070 , amount_gbp $ Polarize.polarize 3
2071 ]
2072 )
2073 , ( ("B":|[])
2074 , Balance.Account_Sum $
2075 Map.fromListWith const $
2076 [ amount_usd $ Polarize.polarize (-1)
2077 , amount_eur $ Polarize.polarize (-2)
2078 , amount_gbp $ Polarize.polarize (-3)
2079 ]
2080 )
2081 ]
2082 , Balance.balance_by_unit =
2083 Balance.Balance_by_Unit $ Map.fromList $
2084 [ amount_usd $ Balance.Unit_Sum
2085 { Balance.unit_sum_quantity = Polarize.polarize 0
2086 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2087 ["A":|[], "B":|[]]
2088 }
2089 , amount_eur $ Balance.Unit_Sum
2090 { Balance.unit_sum_quantity = Polarize.polarize 0
2091 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2092 ["A":|[], "B":|[]]
2093 }
2094 , amount_gbp $ Balance.Unit_Sum
2095 { Balance.unit_sum_quantity = Polarize.polarize 0
2096 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2097 ["A":|[], "B":|[]]
2098 }
2099 ]
2100 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
2101 ]
2102 , "infer_equilibrium" ~: TestList
2103 [ "{A+$1 B}" ~:
2104 (snd $ Balance.infer_equilibrium $
2105 Map.fromList $
2106 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2107 [ ( ("A"::Text):|[]
2108 , amounts [ amount_usd $ (1::Integer) ] )
2109 , ( "B":|[]
2110 , amounts [] )
2111 ])
2112 ~?=
2113 (Right $
2114 Map.fromList $
2115 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2116 [ ( "A":|[]
2117 , amounts [ amount_usd $ 1 ] )
2118 , ( "B":|[]
2119 , amounts [ amount_usd $ -1 ] )
2120 ])
2121 , "{A+$1 B-1€}" ~:
2122 (snd $ Balance.infer_equilibrium $
2123 Map.fromList $
2124 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2125 [ ( ("A"::Text):|[]
2126 , amounts [ amount_usd $ (1::Integer) ] )
2127 , ( "B":|[]
2128 , amounts [ amount_eur $ -1 ] )
2129 ])
2130 ~?=
2131 (Right $
2132 Map.fromList $
2133 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2134 [ ( ("A"::Text):|[]
2135 , amounts [ amount_usd $ 1, amount_eur $ (1::Integer)] )
2136 , ( "B":|[]
2137 , amounts [ amount_eur $ -1, amount_usd $ -1 ] )
2138 ])
2139 , "{A+$1 B+$1}" ~:
2140 (snd $ Balance.infer_equilibrium $
2141 Map.fromList $
2142 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2143 [ ( ("A"::Text):|[]
2144 , amounts [ amount_usd $ (1::Integer) ] )
2145 , ( "B":|[]
2146 , amounts [ amount_usd $ 1 ] )
2147 ])
2148 ~?=
2149 (Left
2150 [ amount_usd $ Balance.Unit_Sum
2151 { Balance.unit_sum_quantity = 2
2152 , Balance.unit_sum_accounts = Map.fromList []}
2153 ])
2154 , "{A+$1 B-$1 B-1€}" ~:
2155 (snd $ Balance.infer_equilibrium $
2156 Map.fromList $
2157 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2158 [ ( ("A"::Text):|[]
2159 , amounts [ amount_usd $ (1::Integer) ] )
2160 , ( "B":|[]
2161 , amounts [ amount_usd $ -1, amount_eur $ -1 ] )
2162 ])
2163 ~?=
2164 (Right $
2165 Map.fromList $
2166 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2167 [ ( "A":|[]
2168 , amounts [ amount_usd $ 1, amount_eur $ 1 ] )
2169 , ( "B":|[]
2170 , amounts [ amount_usd $ -1, amount_eur $ -1 ] )
2171 ])
2172 ]
2173 ]
2174 ]