1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
3 {-# LANGUAGE TupleSections #-}
5 module Balance.Test where
6 import Control.Arrow ((***))
9 import Data.Either (Either(..))
10 import Data.Function (($), (.), id, const, flip)
11 import qualified Data.List as List
12 import Data.List.NonEmpty (NonEmpty(..))
13 import qualified Data.Map.Strict as Map
14 import Data.Ord (Ord(..))
15 import Data.Text (Text)
16 import Data.Tuple (snd)
17 import Prelude (Integer)
19 import Test.Tasty.HUnit
21 import qualified Data.TreeMap.Strict as TreeMap
22 import Hcompta.Balance
23 import qualified Hcompta.Lib.Strict as Strict
24 import Hcompta.Polarize
25 import Hcompta.Quantity
26 -- {-# ANN module "HLint: ignore Use second" #-}
27 -- {-# ANN module "HLint: ignore Redundant bracket" #-}
28 -- {-# ANN module "HLint: ignore Redundant $" #-}
30 amounts :: (Addable q, Ord u) => [(u, q)] -> Map.Map u q
31 amounts = Map.fromListWith quantity_add
32 amount_usd :: t -> (Text, t)
34 amount_eur :: t -> (Text, t)
36 amount_gbp :: t -> (Text, t)
40 tests = testGroup "Balance"
41 [ testGroup "balance_cons"
42 [ testCase "[A+$1] = {A+$1, $+1}" $
45 , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ]
50 { balance_by_account =
51 TreeMap.from_List const $
52 List.map (id *** Balance_by_Account_Sum . Map.map polarize) $
53 [ ("A":|[], amounts [ amount_usd $ 1 ]) ]
57 [ amount_usd $ Balance_by_Unit_Sum
58 { balance_by_unit_sum_quantity = polarize $ 1
59 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
65 , testCase "[A+$1, A-$1] = {A+$0, $+0}" $
66 List.foldl (flip balance_cons)
69 , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ]
72 , Map.map polarize $ amounts [ amount_usd $ -1 ]
77 { balance_by_account =
78 TreeMap.from_List const $
80 , Balance_by_Account_Sum $
81 Map.fromListWith const $
82 [ amount_usd $ Polarized_Both (-1) ( 1)
86 Balance_by_Unit $ Map.fromList $
87 [ amount_usd $ Balance_by_Unit_Sum
88 { balance_by_unit_sum_quantity = Polarized_Both (-1) ( 1)
89 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
94 , testCase "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" $
95 List.foldl (flip balance_cons)
98 , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ]
101 , Map.map polarize $ amounts [ amount_eur $ -1 ]
106 { balance_by_account =
107 TreeMap.from_List const $
108 List.map (id *** Balance_by_Account_Sum . Map.map polarize) $
109 [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ -1 ]) ]
111 Balance_by_Unit $ Map.fromList $
112 [ amount_usd $ Balance_by_Unit_Sum
113 { balance_by_unit_sum_quantity = Polarized_Positive 1
114 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
117 , amount_eur $ Balance_by_Unit_Sum
118 { balance_by_unit_sum_quantity = Polarized_Negative (-1)
119 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
124 , testCase "[A+$1, B-$1] = {A+$1 B-$1, $+0}" $
125 List.foldl (flip balance_cons)
127 [ ( (("A"::Text):|[])
128 , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ]
131 , Map.map polarize $ amounts [ amount_usd $ -1 ]
136 { balance_by_account =
137 TreeMap.from_List const $
138 List.map (id *** Balance_by_Account_Sum . Map.map polarize) $
139 [ ("A":|[], amounts [ amount_usd $ 1 ])
140 , ("B":|[], amounts [ amount_usd $ -1 ])
143 Balance_by_Unit $ Map.fromList $
144 [ amount_usd $ Balance_by_Unit_Sum
145 { balance_by_unit_sum_quantity = Polarized_Both (-1) 1
146 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
152 , testCase "[A+$1, B+$1]" $
153 List.foldl (flip balance_cons)
155 [ ( (("A"::Text):|[])
156 , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ]
159 , Map.map polarize $ amounts [ amount_usd $ 1 ]
164 { balance_by_account =
165 TreeMap.from_List const $
166 List.map (id *** Balance_by_Account_Sum . Map.map polarize) $
167 [ ("A":|[], amounts [ amount_usd $ 1 ])
168 , ("B":|[], amounts [ amount_usd $ 1 ])
171 Balance_by_Unit $ Map.fromList $
172 [ amount_usd $ Balance_by_Unit_Sum
173 { balance_by_unit_sum_quantity = polarize 2
174 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
180 , testCase "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" $
181 List.foldl (flip balance_cons)
183 [ ( (("A"::Text):|[])
184 , Map.map polarize $ amounts [ amount_usd $ 1, amount_eur $ (2::Integer) ]
187 , Map.map polarize $ amounts [ amount_usd $ -1, amount_eur $ -2 ]
192 { balance_by_account =
193 TreeMap.from_List const $
195 , Balance_by_Account_Sum $
196 Map.fromListWith const $
197 [ amount_usd $ Polarized_Both (-1) 1
198 , amount_eur $ Polarized_Both (-2) 2
203 Balance_by_Unit $ Map.fromList $
204 [ amount_usd $ Balance_by_Unit_Sum
205 { balance_by_unit_sum_quantity = Polarized_Both (-1) 1
206 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
209 , amount_eur $ Balance_by_Unit_Sum
210 { balance_by_unit_sum_quantity = Polarized_Both (-2) 2
211 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
216 , testCase "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" $
217 List.foldl (flip balance_cons)
219 [ ( (("A"::Text):|[])
220 , Map.map polarize $ amounts [ amount_usd $ (1::Integer), amount_eur $ 2, amount_gbp $ 3 ]
223 , Map.map polarize $ amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ]
228 { balance_by_account =
229 TreeMap.from_List const $
230 List.map (id *** Balance_by_Account_Sum . Map.map polarize) $
231 [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ 2, amount_gbp $ 3 ])
232 , ("B":|[], amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ])
237 [ amount_usd $ Balance_by_Unit_Sum
238 { balance_by_unit_sum_quantity = Polarized_Both (-1) 1
239 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
243 , amount_eur $ Balance_by_Unit_Sum
244 { balance_by_unit_sum_quantity = Polarized_Both (-2) 2
245 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
249 , amount_gbp $ Balance_by_Unit_Sum
250 { balance_by_unit_sum_quantity = Polarized_Both (-3) 3
251 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
258 , testGroup "balance_union" $
259 [ testCase "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" $
262 { balance_by_account =
263 TreeMap.from_List const $
265 , Balance_by_Account_Sum $
266 Map.fromListWith const $
267 [ amount_usd $ polarize (1::Integer) ]
271 Balance_by_Unit $ Map.fromList $
272 [ amount_usd $ Balance_by_Unit_Sum
273 { balance_by_unit_sum_quantity = polarize 1
274 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
280 { balance_by_account =
281 TreeMap.from_List const $
283 , Balance_by_Account_Sum $
284 Map.fromListWith const $
285 [ amount_usd $ polarize 1 ]
289 Balance_by_Unit $ Map.fromList $
290 [ amount_usd $ Balance_by_Unit_Sum
291 { balance_by_unit_sum_quantity = polarize 1
292 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
299 { balance_by_account =
300 TreeMap.from_List const $
302 , Balance_by_Account_Sum $
303 Map.fromListWith const $
304 [ amount_usd $ polarize 2 ]
308 Balance_by_Unit $ Map.fromList $
309 [ amount_usd $ Balance_by_Unit_Sum
310 { balance_by_unit_sum_quantity = polarize 2
311 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
316 , testCase "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" $
319 { balance_by_account =
320 TreeMap.from_List const $
321 [ ( (("A"::Text):|[])
322 , Balance_by_Account_Sum $
323 Map.fromListWith const $
324 [ amount_usd $ polarize (1::Integer) ]
328 Balance_by_Unit $ Map.fromList $
329 [ amount_usd $ Balance_by_Unit_Sum
330 { balance_by_unit_sum_quantity = polarize 1
331 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
337 { balance_by_account =
338 TreeMap.from_List const $
340 , Balance_by_Account_Sum $
341 Map.fromListWith const $
342 [ amount_usd $ polarize 1 ]
346 Balance_by_Unit $ Map.fromList $
347 [ amount_usd $ Balance_by_Unit_Sum
348 { balance_by_unit_sum_quantity = polarize 1
349 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
356 { balance_by_account =
357 TreeMap.from_List const $
359 , Balance_by_Account_Sum $
360 Map.fromListWith const $
361 [ amount_usd $ polarize 1 ]
364 , Balance_by_Account_Sum $
365 Map.fromListWith const $
366 [ amount_usd $ polarize 1 ]
370 Balance_by_Unit $ Map.fromList $
371 [ amount_usd $ Balance_by_Unit_Sum
372 { balance_by_unit_sum_quantity = polarize 2
373 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
379 , testCase "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" $
382 { balance_by_account =
383 TreeMap.from_List const $
384 [ ( (("A"::Text):|[])
385 , Balance_by_Account_Sum $
386 Map.fromListWith const $
387 [ amount_usd $ polarize (1::Integer) ]
391 Balance_by_Unit $ Map.fromList $
392 [ amount_usd $ Balance_by_Unit_Sum
393 { balance_by_unit_sum_quantity = polarize 1
394 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
400 { balance_by_account =
401 TreeMap.from_List const $
403 , Balance_by_Account_Sum $
404 Map.fromListWith const $
405 [ amount_eur $ polarize 1 ]
409 Balance_by_Unit $ Map.fromList $
410 [ amount_eur $ Balance_by_Unit_Sum
411 { balance_by_unit_sum_quantity = polarize 1
412 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
419 { balance_by_account =
420 TreeMap.from_List const $
422 , Balance_by_Account_Sum $
423 Map.fromListWith const $
424 [ amount_usd $ polarize 1 ]
427 , Balance_by_Account_Sum $
428 Map.fromListWith const $
429 [ amount_eur $ polarize 1 ]
433 Balance_by_Unit $ Map.fromList $
434 [ amount_usd $ Balance_by_Unit_Sum
435 { balance_by_unit_sum_quantity = polarize 1
436 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
439 , amount_eur $ Balance_by_Unit_Sum
440 { balance_by_unit_sum_quantity = polarize 1
441 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
447 , testGroup "balance_expanded"
449 balance_expanded TreeMap.empty
451 (TreeMap.empty::Balance_Expanded (NonEmpty Text) Text Integer)
452 , testCase "A+$1 = A+$1" $
454 (TreeMap.from_List const $
456 , Balance_by_Account_Sum $
457 Map.fromListWith const $
458 [ amount_usd $ polarize 1 ]
460 ]::Balance_by_Account Text Text (Polarized Integer))
462 TreeMap.from_List const
463 [ ("A":|[], Strict.Clusive
465 Balance_by_Account_Sum $
467 amounts [ amount_usd $ 1 ]
469 Balance_by_Account_Sum $
471 amounts [ amount_usd $ 1 ]
474 , testCase "A/A+$1 = A+$1 A/A+$1" $
476 (TreeMap.from_List const $
478 , Balance_by_Account_Sum $
479 Map.fromListWith const $
480 [ amount_usd $ polarize 1 ]
482 ]::Balance_by_Account Text Text (Polarized Integer))
484 TreeMap.from_List const
485 [ ("A":|[], Strict.Clusive
487 Balance_by_Account_Sum $
489 amounts [ amount_usd $ 1 ]
491 Balance_by_Account_Sum $
495 , ("A":|["A"], Strict.Clusive
497 Balance_by_Account_Sum $
499 amounts [ amount_usd $ 1 ]
501 Balance_by_Account_Sum $
503 amounts [ amount_usd $ 1 ]
506 , testCase "A/B+$1 = A+$1 A/B+$1" $
508 (TreeMap.from_List const $
510 , Balance_by_Account_Sum $
511 Map.fromListWith const $
512 [ amount_usd $ polarize 1 ]
514 ]::Balance_by_Account Text Text (Polarized Integer))
516 TreeMap.from_List const
517 [ ("A":|[], Strict.Clusive
519 Balance_by_Account_Sum $
521 amounts [ amount_usd $ 1 ]
523 Balance_by_Account_Sum $
527 , ("A":|["B"], Strict.Clusive
529 Balance_by_Account_Sum $
531 amounts [ amount_usd $ 1 ]
533 Balance_by_Account_Sum $
535 amounts [ amount_usd $ 1 ]
538 , testCase "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" $
540 (TreeMap.from_List const $
541 [ ( ("A":|["B", "C"])
542 , Balance_by_Account_Sum $
543 Map.fromListWith const $
544 [ amount_usd $ polarize 1 ]
546 ]::Balance_by_Account Text Text (Polarized Integer))
548 TreeMap.from_List const
549 [ ("A":|[], Strict.Clusive
551 Balance_by_Account_Sum $
553 amounts [ amount_usd $ 1 ]
555 Balance_by_Account_Sum $
559 , ("A":|["B"], Strict.Clusive
561 Balance_by_Account_Sum $
563 amounts [ amount_usd $ 1 ]
565 Balance_by_Account_Sum $
569 , ("A":|["B", "C"], Strict.Clusive
571 Balance_by_Account_Sum $
573 amounts [ amount_usd $ 1 ]
575 Balance_by_Account_Sum $
577 amounts [ amount_usd $ 1 ]
580 , testCase "A+$1 A/B+$1 = A+$2 A/B+$1" $
582 (TreeMap.from_List const
584 , Balance_by_Account_Sum $
585 Map.fromListWith const $
586 [ amount_usd $ polarize 1 ]
589 , Balance_by_Account_Sum $
590 Map.fromListWith const $
591 [ amount_usd $ polarize 1 ]
593 ]::Balance_by_Account Text Text (Polarized Integer))
595 TreeMap.from_List const
596 [ ("A":|[], Strict.Clusive
598 Balance_by_Account_Sum $
600 amounts [ amount_usd $ 2 ]
602 Balance_by_Account_Sum $
604 amounts [ amount_usd $ 1 ]
606 , ("A":|["B"], Strict.Clusive
608 Balance_by_Account_Sum $
610 amounts [ amount_usd $ 1 ]
612 Balance_by_Account_Sum $
614 amounts [ amount_usd $ 1 ]
617 , testCase "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" $
619 (TreeMap.from_List const $
621 , Balance_by_Account_Sum $
622 Map.fromListWith const $
623 [ amount_usd $ polarize 1 ]
626 , Balance_by_Account_Sum $
627 Map.fromListWith const $
628 [ amount_usd $ polarize 1 ]
630 , ( ("A":|["B", "C"])
631 , Balance_by_Account_Sum $
632 Map.fromListWith const $
633 [ amount_usd $ polarize 1 ]
635 ]::Balance_by_Account Text Text (Polarized Integer))
637 TreeMap.from_List const
638 [ ("A":|[], Strict.Clusive
640 Balance_by_Account_Sum $
642 amounts [ amount_usd $ 3 ]
644 Balance_by_Account_Sum $
646 amounts [ amount_usd $ 1 ]
648 , ("A":|["B"], Strict.Clusive
650 Balance_by_Account_Sum $
652 amounts [ amount_usd $ 2 ]
654 Balance_by_Account_Sum $
656 amounts [ amount_usd $ 1 ]
658 , ("A":|["B", "C"], Strict.Clusive
660 Balance_by_Account_Sum $
662 amounts [ amount_usd $ 1 ]
664 Balance_by_Account_Sum $
666 amounts [ amount_usd $ 1 ]
669 , testCase "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" $
671 (TreeMap.from_List const
673 , Balance_by_Account_Sum $
674 Map.fromListWith const $
675 [ amount_usd $ polarize 1 ]
678 , Balance_by_Account_Sum $
679 Map.fromListWith const $
680 [ amount_usd $ polarize 1 ]
682 , ( ("A":|["B", "C"])
683 , Balance_by_Account_Sum $
684 Map.fromListWith const $
685 [ amount_usd $ polarize 1 ]
687 , ( ("A":|["B", "C", "D"])
688 , Balance_by_Account_Sum $
689 Map.fromListWith const $
690 [ amount_usd $ polarize 1 ]
692 ]::Balance_by_Account Text Text (Polarized Integer))
694 TreeMap.from_List const
695 [ ("A":|[], Strict.Clusive
697 Balance_by_Account_Sum $
699 amounts [ amount_usd $ 4 ]
701 Balance_by_Account_Sum $
703 amounts [ amount_usd $ 1 ]
705 , ("A":|["B"], Strict.Clusive
707 Balance_by_Account_Sum $
709 amounts [ amount_usd $ 3 ]
711 Balance_by_Account_Sum $
713 amounts [ amount_usd $ 1 ]
715 , ("A":|["B", "C"], Strict.Clusive
717 Balance_by_Account_Sum $
719 amounts [ amount_usd $ 2 ]
721 Balance_by_Account_Sum $
723 amounts [ amount_usd $ 1 ]
725 , ("A":|["B", "C", "D"], Strict.Clusive
727 Balance_by_Account_Sum $
729 amounts [ amount_usd $ 1 ]
731 Balance_by_Account_Sum $
733 amounts [ amount_usd $ 1 ]
736 , testCase "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" $
738 (TreeMap.from_List const
740 , Balance_by_Account_Sum $
741 Map.fromListWith const $
742 [ amount_usd $ polarize 1 ]
745 , Balance_by_Account_Sum $
746 Map.fromListWith const $
747 [ amount_usd $ polarize 1 ]
750 , Balance_by_Account_Sum $
751 Map.fromListWith const $
752 [ amount_usd $ polarize 1 ]
755 , Balance_by_Account_Sum $
756 Map.fromListWith const $
757 [ amount_usd $ polarize 1 ]
759 ]::Balance_by_Account Text Text (Polarized Integer))
761 TreeMap.from_List const
762 [ ("A":|[], Strict.Clusive
764 Balance_by_Account_Sum $
766 amounts [ amount_usd $ 3 ]
768 Balance_by_Account_Sum $
770 amounts [ amount_usd $ 1 ]
772 , ("A":|["B"], Strict.Clusive
774 Balance_by_Account_Sum $
776 amounts [ amount_usd $ 1 ]
778 Balance_by_Account_Sum $
780 amounts [ amount_usd $ 1 ]
782 , ("A":|["BB"], Strict.Clusive
784 Balance_by_Account_Sum $
786 amounts [ amount_usd $ 1 ]
788 Balance_by_Account_Sum $
790 amounts [ amount_usd $ 1 ]
792 , ("AA":|[], Strict.Clusive
794 Balance_by_Account_Sum $
796 amounts [ amount_usd $ 1 ]
798 Balance_by_Account_Sum $
802 , ("AA":|["B"], Strict.Clusive
804 Balance_by_Account_Sum $
806 amounts [ amount_usd $ 1 ]
808 Balance_by_Account_Sum $
810 amounts [ amount_usd $ 1 ]
814 , testGroup "balance_deviation"
815 [ testCase "{A+$1, $1}" $
818 { balance_by_account =
819 TreeMap.from_List const
820 [ ( (("A"::Text):|[])
821 , Balance_by_Account_Sum $
822 Map.fromListWith const $
823 [ amount_usd $ polarize (1::Integer) ]
826 , Balance_by_Account_Sum $
827 Map.fromListWith const $
832 Balance_by_Unit $ Map.fromList $
833 [ amount_usd $ Balance_by_Unit_Sum
834 { balance_by_unit_sum_quantity = polarize 1
835 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
842 (Balance_by_Unit $ Map.fromList
843 [ amount_usd $ Balance_by_Unit_Sum
844 { balance_by_unit_sum_quantity = polarize 1
845 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
849 , testCase "{A+$1 B+$1, $2}" $
852 { balance_by_account =
853 TreeMap.from_List const $
854 [ ( (("A"::Text):|[])
855 , Balance_by_Account_Sum $
856 Map.fromListWith const $
857 [ amount_usd $ polarize (1::Integer) ]
860 , Balance_by_Account_Sum $
861 Map.fromListWith const $
862 [ amount_usd $ polarize 1 ]
866 Balance_by_Unit $ Map.fromList $
867 [ amount_usd $ Balance_by_Unit_Sum
868 { balance_by_unit_sum_quantity = polarize 2
869 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
878 (Balance_by_Unit $ Map.fromList $
879 [ amount_usd $ Balance_by_Unit_Sum
880 { balance_by_unit_sum_quantity = polarize 2
881 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
887 , testGroup "is_balance_equilibrium_inferrable"
890 is_balance_equilibrium_inferrable $
892 (balance_empty::Balance Text Text Integer)
893 , testCase "{A+$0, $+0}" $
895 is_balance_equilibrium_inferrable $
898 { balance_by_account =
899 TreeMap.from_List const $
901 , Balance_by_Account_Sum $
902 Map.fromListWith const $
903 [ amount_usd $ polarize (0::Integer) ]
907 Balance_by_Unit $ Map.fromList $
908 [ amount_usd $ Balance_by_Unit_Sum
909 { balance_by_unit_sum_quantity = polarize (0::Integer)
910 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
915 , testCase "{A+$1, $+1}" $
917 is_balance_equilibrium_inferrable $
920 { balance_by_account =
921 TreeMap.from_List const $
922 [ ( (("A"::Text):|[])
923 , Balance_by_Account_Sum $
924 Map.fromListWith const $
925 [ amount_usd $ polarize (1::Integer) ]
929 Balance_by_Unit $ Map.fromList $
930 [ amount_usd $ Balance_by_Unit_Sum
931 { balance_by_unit_sum_quantity = polarize 1
932 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
937 , testCase "{A+$0+€0, $0 €+0}" $
939 is_balance_equilibrium_inferrable $
942 { balance_by_account =
943 TreeMap.from_List const $
944 [ ( (("A"::Text):|[])
945 , Balance_by_Account_Sum $
946 Map.fromListWith const $
947 [ amount_usd $ polarize (0::Integer)
948 , amount_eur $ polarize 0
953 Balance_by_Unit $ Map.fromList $
954 [ amount_usd $ Balance_by_Unit_Sum
955 { balance_by_unit_sum_quantity = polarize 0
956 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
959 , amount_eur $ Balance_by_Unit_Sum
960 { balance_by_unit_sum_quantity = polarize 0
961 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
966 , testCase "{A+$1 B-$1, $+0}" $
968 is_balance_equilibrium_inferrable $
971 { balance_by_account =
972 TreeMap.from_List const $
973 [ ( (("A"::Text):|[])
974 , Balance_by_Account_Sum $
975 Map.fromListWith const $
976 [ amount_usd $ polarize (1::Integer) ]
979 , Balance_by_Account_Sum $
980 Map.fromListWith const $
981 [ amount_usd $ polarize (-1) ]
985 Balance_by_Unit $ Map.fromList $
986 [ amount_usd $ Balance_by_Unit_Sum
987 { balance_by_unit_sum_quantity = polarize 0
988 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
994 , testCase "{A+$1 B, $+1}" $
996 is_balance_equilibrium_inferrable $
999 { balance_by_account =
1000 TreeMap.from_List const $
1001 [ ( (("A"::Text):|[])
1002 , Balance_by_Account_Sum $
1003 Map.fromListWith const $
1004 [ amount_usd $ polarize (1::Integer) ]
1007 , Balance_by_Account_Sum $
1008 Map.fromListWith const $
1013 Balance_by_Unit $ Map.fromList $
1014 [ amount_usd $ Balance_by_Unit_Sum
1015 { balance_by_unit_sum_quantity = polarize 1
1016 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1021 , testCase "{A+$1 B+€1, $+1 €+1}" $
1023 is_balance_equilibrium_inferrable $
1026 { balance_by_account =
1027 TreeMap.from_List const $
1028 [ ( (("A"::Text):|[])
1029 , Balance_by_Account_Sum $
1030 Map.fromListWith const $
1031 [ amount_usd $ polarize (1::Integer) ]
1034 , Balance_by_Account_Sum $
1035 Map.fromListWith const $
1036 [ amount_eur $ polarize 1 ]
1040 Balance_by_Unit $ Map.fromList $
1041 [ amount_usd $ Balance_by_Unit_Sum
1042 { balance_by_unit_sum_quantity = polarize 1
1043 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1046 , amount_eur $ Balance_by_Unit_Sum
1047 { balance_by_unit_sum_quantity = polarize 1
1048 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1053 , testCase "{A+$1 B-$1+€1, $+0 €+1}" $
1055 is_balance_equilibrium_inferrable $
1058 { balance_by_account =
1059 TreeMap.from_List const $
1060 [ ( (("A"::Text):|[])
1061 , Balance_by_Account_Sum $
1062 Map.fromListWith const $
1063 [ amount_usd $ polarize (1::Integer) ]
1066 , Balance_by_Account_Sum $
1067 Map.fromListWith const $
1068 [ amount_usd $ polarize (-1)
1069 , amount_eur $ polarize 1
1074 Balance_by_Unit $ Map.fromList $
1075 [ amount_usd $ Balance_by_Unit_Sum
1076 { balance_by_unit_sum_quantity = polarize 0
1077 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1081 , amount_eur $ Balance_by_Unit_Sum
1082 { balance_by_unit_sum_quantity = polarize 1
1083 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1088 , testCase "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" $
1090 is_balance_equilibrium_inferrable $
1093 { balance_by_account =
1094 TreeMap.from_List const $
1095 [ ( (("A"::Text):|[])
1096 , Balance_by_Account_Sum $
1097 Map.fromListWith const $
1098 [ amount_usd $ polarize (1::Integer)
1099 , amount_eur $ polarize 2
1100 , amount_gbp $ polarize 3
1104 , Balance_by_Account_Sum $
1105 Map.fromListWith const $
1106 [ amount_usd $ polarize (-1)
1107 , amount_eur $ polarize (-2)
1108 , amount_gbp $ polarize (-3)
1113 Balance_by_Unit $ Map.fromList $
1114 [ amount_usd $ Balance_by_Unit_Sum
1115 { balance_by_unit_sum_quantity = polarize 0
1116 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1120 , amount_eur $ Balance_by_Unit_Sum
1121 { balance_by_unit_sum_quantity = polarize 0
1122 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1126 , amount_gbp $ Balance_by_Unit_Sum
1127 { balance_by_unit_sum_quantity = polarize 0
1128 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,())
1135 , testGroup "balance_infer_equilibrium"
1136 [ testCase "{A+$1 B}" $
1137 snd (balance_infer_equilibrium $
1139 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1141 , amounts [ amount_usd $ (1::Integer) ] )
1148 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1150 , amounts [ amount_usd $ 1 ] )
1152 , amounts [ amount_usd $ -1 ] )
1154 , testCase "{A+$1 B-1€}" $
1155 snd (balance_infer_equilibrium $
1157 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1159 , amounts [ amount_usd $ (1::Integer) ] )
1161 , amounts [ amount_eur $ -1 ] )
1166 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1168 , amounts [ amount_usd $ 1, amount_eur $ (1::Integer)] )
1170 , amounts [ amount_eur $ -1, amount_usd $ -1 ] )
1172 , testCase "{A+$1 B+$1}" $
1173 snd (balance_infer_equilibrium $
1175 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1177 , amounts [ amount_usd $ (1::Integer) ] )
1179 , amounts [ amount_usd $ 1 ] )
1183 [ amount_usd $ Balance_by_Unit_Sum
1184 { balance_by_unit_sum_quantity = 2
1185 , balance_by_unit_sum_accounts = Map.fromList []}
1187 , testCase "{A+$1 B-$1 B-1€}" $
1188 snd (balance_infer_equilibrium $
1190 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1192 , amounts [ amount_usd $ (1::Integer) ] )
1194 , amounts [ amount_usd $ -1, amount_eur $ -1 ] )
1199 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
1201 , amounts [ amount_usd $ 1, amount_eur $ 1 ] )
1203 , amounts [ amount_usd $ -1, amount_eur $ -1 ] )