{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} module Balance.Test where import Control.Arrow ((***)) import Data.Bool import Data.Data () import Data.Either (Either(..)) import Data.Function (($), (.), id, const, flip) import qualified Data.List as List import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.Map.Strict as Map import Data.Ord (Ord(..)) import Data.Text (Text) import Data.Tuple (snd) import Prelude (Integer) import Test.Tasty import Test.Tasty.HUnit import qualified Data.TreeMap.Strict as TreeMap import Hcompta.Balance import qualified Hcompta.Lib.Strict as Strict import Hcompta.Polarize import Hcompta.Quantity -- {-# ANN module "HLint: ignore Use second" #-} -- {-# ANN module "HLint: ignore Redundant bracket" #-} -- {-# ANN module "HLint: ignore Redundant $" #-} amounts :: (Addable q, Ord u) => [(u, q)] -> Map.Map u q amounts = Map.fromListWith quantity_add amount_usd :: t -> (Text, t) amount_usd = ("$",) amount_eur :: t -> (Text, t) amount_eur = ("€",) amount_gbp :: t -> (Text, t) amount_gbp = ("£",) tests :: TestTree tests = testGroup "Balance" [ testGroup "balance_cons" [ testCase "[A+$1] = {A+$1, $+1}" $ (balance_cons ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ] ) balance_empty) @?= (Balance { balance_by_account = TreeMap.from_List const $ List.map (id *** Balance_by_Account_Sum . Map.map polarize) $ [ ("A":|[], amounts [ amount_usd $ 1 ]) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize $ 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } ) , testCase "[A+$1, A-$1] = {A+$0, $+0}" $ List.foldl (flip balance_cons) balance_empty [ ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ] ) , ( ("A":|[]) , Map.map polarize $ amounts [ amount_usd $ -1 ] ) ] @?= Balance { balance_by_account = TreeMap.from_List const $ [ ( "A":|[] , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ Polarized_Both (-1) ( 1) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-1) ( 1) , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" $ List.foldl (flip balance_cons) balance_empty [ ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ] ) , ( ("A":|[]) , Map.map polarize $ amounts [ amount_eur $ -1 ] ) ] @?= Balance { balance_by_account = TreeMap.from_List const $ List.map (id *** Balance_by_Account_Sum . Map.map polarize) $ [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ -1 ]) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Positive 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Negative (-1) , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "[A+$1, B-$1] = {A+$1 B-$1, $+0}" $ List.foldl (flip balance_cons) balance_empty [ ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ] ) , ( ("B":|[]) , Map.map polarize $ amounts [ amount_usd $ -1 ] ) ] @?= Balance { balance_by_account = TreeMap.from_List const $ List.map (id *** Balance_by_Account_Sum . Map.map polarize) $ [ ("A":|[], amounts [ amount_usd $ 1 ]) , ("B":|[], amounts [ amount_usd $ -1 ]) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-1) 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } , testCase "[A+$1, B+$1]" $ List.foldl (flip balance_cons) balance_empty [ ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ (1::Integer) ] ) , ( ("B":|[]) , Map.map polarize $ amounts [ amount_usd $ 1 ] ) ] @?= Balance { balance_by_account = TreeMap.from_List const $ List.map (id *** Balance_by_Account_Sum . Map.map polarize) $ [ ("A":|[], amounts [ amount_usd $ 1 ]) , ("B":|[], amounts [ amount_usd $ 1 ]) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } , testCase "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" $ List.foldl (flip balance_cons) balance_empty [ ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ 1, amount_eur $ (2::Integer) ] ) , ( ("A":|[]) , Map.map polarize $ amounts [ amount_usd $ -1, amount_eur $ -2 ] ) ] @?= Balance { balance_by_account = TreeMap.from_List const $ [ ("A":|[] , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ Polarized_Both (-1) 1 , amount_eur $ Polarized_Both (-2) 2 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-1) 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-2) 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" $ List.foldl (flip balance_cons) balance_empty [ ( (("A"::Text):|[]) , Map.map polarize $ amounts [ amount_usd $ (1::Integer), amount_eur $ 2, amount_gbp $ 3 ] ) , ( ("B":|[]) , Map.map polarize $ amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ] ) ] @?= Balance { balance_by_account = TreeMap.from_List const $ List.map (id *** Balance_by_Account_Sum . Map.map polarize) $ [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ 2, amount_gbp $ 3 ]) , ("B":|[], amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ]) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-1) 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-2) 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } , amount_gbp $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = Polarized_Both (-3) 3 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } ] , testGroup "balance_union" $ [ testCase "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" $ balance_union Balance { balance_by_account = TreeMap.from_List const $ [ ( ("A"::Text):|[] , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } (Balance { balance_by_account = TreeMap.from_List const $ [ ( "A":|[] , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] }) @?= Balance { balance_by_account = TreeMap.from_List const $ [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 2 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" $ balance_union Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } Balance { balance_by_account = TreeMap.from_List const $ [ ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "B":|[] ] } ] } @?= Balance { balance_by_account = TreeMap.from_List const $ [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } , testCase "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" $ balance_union Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } Balance { balance_by_account = TreeMap.from_List const $ [ ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_eur $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "B":|[] ] } ] } @?= Balance { balance_by_account = TreeMap.from_List const $ [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_eur $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "B":|[] ] } ] } ] , testGroup "balance_expanded" [ testCase "empty" $ balance_expanded TreeMap.empty @?= (TreeMap.empty::Balance_Expanded (NonEmpty Text) Text Integer) , testCase "A+$1 = A+$1" $ balance_expanded (TreeMap.from_List const $ [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , testCase "A/A+$1 = A+$1 A/A+$1" $ balance_expanded (TreeMap.from_List const $ [ ( ("A":|["A"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [] }) , ("A":|["A"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , testCase "A/B+$1 = A+$1 A/B+$1" $ balance_expanded (TreeMap.from_List const $ [ ( ("A":|["B"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [] }) , ("A":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , testCase "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" $ balance_expanded (TreeMap.from_List const $ [ ( ("A":|["B", "C"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [] }) , ("A":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [] }) , ("A":|["B", "C"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , testCase "A+$1 A/B+$1 = A+$2 A/B+$1" $ balance_expanded (TreeMap.from_List const [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 2 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , testCase "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" $ balance_expanded (TreeMap.from_List const $ [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B", "C"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 3 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 2 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B", "C"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , 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" $ balance_expanded (TreeMap.from_List const [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B", "C"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B", "C", "D"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 4 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 3 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B", "C"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 2 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B", "C", "D"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] , 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" $ balance_expanded (TreeMap.from_List const [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["B"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("A":|["BB"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) , ( ("AA":|["B"]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ]::Balance_by_Account Text Text (Polarized Integer)) @?= TreeMap.from_List const [ ("A":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 3 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("A":|["BB"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) , ("AA":|[], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [] }) , ("AA":|["B"], Strict.Clusive { Strict.inclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] , Strict.exclusive = Balance_by_Account_Sum $ Map.map polarize $ amounts [ amount_usd $ 1 ] }) ] ] , testGroup "balance_deviation" [ testCase "{A+$1, $1}" $ balance_deviation Balance { balance_by_account = TreeMap.from_List const [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } @?= Balance_Deviation (Balance_by_Unit $ Map.fromList [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "B":|[] ] } ]) , testCase "{A+$1 B+$1, $2}" $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } @?= Balance_Deviation (Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 2 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ ] } ]) ] , testGroup "is_balance_equilibrium_inferrable" [ testCase "empty" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation $ (balance_empty::Balance Text Text Integer) , testCase "{A+$0, $+0}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( ("A":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (0::Integer) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize (0::Integer) , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ ("A"::Text):|[] ] } ] } , testCase "{A+$1, $+1}" $ (@=?) False $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "{A+$0+€0, $0 €+0}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (0::Integer) , amount_eur $ polarize 0 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "{A+$1 B-$1, $+0}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (-1) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } , testCase "{A+$1 B, $+1}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } ] } , testCase "{A+$1 B+€1, $+1 €+1}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_eur $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "B":|[] ] } ] } , testCase "{A+$1 B-$1+€1, $+0 €+1}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (-1) , amount_eur $ polarize 1 ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 1 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "B":|[] ] } ] } , testCase "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" $ (@=?) True $ is_balance_equilibrium_inferrable $ balance_deviation $ Balance { balance_by_account = TreeMap.from_List const $ [ ( (("A"::Text):|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (1::Integer) , amount_eur $ polarize 2 , amount_gbp $ polarize 3 ] ) , ( ("B":|[]) , Balance_by_Account_Sum $ Map.fromListWith const $ [ amount_usd $ polarize (-1) , amount_eur $ polarize (-2) , amount_gbp $ polarize (-3) ] ) ] , balance_by_unit = Balance_by_Unit $ Map.fromList $ [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } , amount_eur $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } , amount_gbp $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = polarize 0 , balance_by_unit_sum_accounts = Map.fromList $ List.map (,()) [ "A":|[] , "B":|[] ] } ] } ] , testGroup "balance_infer_equilibrium" [ testCase "{A+$1 B}" $ snd (balance_infer_equilibrium $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( ("A"::Text):|[] , amounts [ amount_usd $ (1::Integer) ] ) , ( "B":|[] , amounts [] ) ]) @?= (Right $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( "A":|[] , amounts [ amount_usd $ 1 ] ) , ( "B":|[] , amounts [ amount_usd $ -1 ] ) ]) , testCase "{A+$1 B-1€}" $ snd (balance_infer_equilibrium $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( ("A"::Text):|[] , amounts [ amount_usd $ (1::Integer) ] ) , ( "B":|[] , amounts [ amount_eur $ -1 ] ) ]) @?= (Right $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( ("A"::Text):|[] , amounts [ amount_usd $ 1, amount_eur $ (1::Integer)] ) , ( "B":|[] , amounts [ amount_eur $ -1, amount_usd $ -1 ] ) ]) , testCase "{A+$1 B+$1}" $ snd (balance_infer_equilibrium $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( ("A"::Text):|[] , amounts [ amount_usd $ (1::Integer) ] ) , ( "B":|[] , amounts [ amount_usd $ 1 ] ) ]) @?= (Left [ amount_usd $ Balance_by_Unit_Sum { balance_by_unit_sum_quantity = 2 , balance_by_unit_sum_accounts = Map.fromList []} ]) , testCase "{A+$1 B-$1 B-1€}" $ snd (balance_infer_equilibrium $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( ("A"::Text):|[] , amounts [ amount_usd $ (1::Integer) ] ) , ( "B":|[] , amounts [ amount_usd $ -1, amount_eur $ -1 ] ) ]) @?= (Right $ Map.fromList $ List.map (\(acct, amts) -> (acct, [(acct, amts)])) $ [ ( "A":|[] , amounts [ amount_usd $ 1, amount_eur $ 1 ] ) , ( "B":|[] , amounts [ amount_usd $ -1, amount_eur $ -1 ] ) ]) ] ]