{-# LANGUAGE TupleSections #-} {-# LANGUAGE OverloadedStrings #-} import Prelude import Test.HUnit import Test.Framework.Providers.HUnit (hUnitTestToTests) import Test.Framework.Runners.Console (defaultMain) import Control.Applicative ((<*)) import Control.Monad.IO.Class (liftIO) import Data.Decimal (DecimalRaw(..)) import qualified Data.Either import qualified Data.List import qualified Data.Map.Strict as Data.Map import qualified Data.Time.Calendar as Time import qualified Data.Time.LocalTime as Time import qualified Text.Parsec as P import qualified Text.Parsec.Pos as P import qualified Hcompta.Model.Account as Account import qualified Hcompta.Model.Amount as Amount import qualified Hcompta.Model.Amount.Style as Style import qualified Hcompta.Model.Transaction as Transaction import qualified Hcompta.Model.Transaction.Posting as Posting import qualified Hcompta.Calc.Balance as Calc.Balance import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read import qualified Hcompta.Format.Ledger.Journal as Format.Ledger.Journal --instance Eq Text.Parsec.ParseError where -- (==) = const (const False) main :: IO () main = defaultMain $ hUnitTestToTests test_Hcompta test_Hcompta :: Test test_Hcompta = TestList [ "Model" ~: TestList [ "Account" ~: TestList [ "fold" ~: TestList [ "[] = []" ~: (reverse $ Account.fold [] (:) []) ~?= [] , "[A] = [[A]]" ~: (reverse $ Account.fold ["A"] (:) []) ~?= [["A"]] , "[A, B] = [[A], [A, B]]" ~: (reverse $ Account.fold ["A", "B"] (:) []) ~?= [["A"], ["A", "B"]] , "[A, B, C] = [[A], [A, B], [A, B, C]]" ~: (reverse $ Account.fold ["A", "B", "C"] (:) []) ~?= [["A"], ["A", "B"], ["A", "B", "C"]] ] , "ascending" ~: TestList [ "[] = []" ~: Account.ascending [] ~?= [] , "[A] = []" ~: Account.ascending ["A"] ~?= [] , "[A, B] = [A]" ~: Account.ascending ["A", "B"] ~?= ["A"] , "[A, B, C] = [A, B]" ~: Account.ascending ["A", "B", "C"] ~?= ["A", "B"] ] ] , "Amount" ~: TestList [ "+" ~: TestList [ "$1 + 1$ = $2" ~: (+) (Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.unit_side = Just $ Style.Side_Left } , Amount.unit = "$" }) (Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.unit_side = Just $ Style.Side_Right } , Amount.unit = "$" }) ~?= (Amount.nil { Amount.quantity = Decimal 0 2 , Amount.style = Style.nil { Style.unit_side = Just $ Style.Side_Left } , Amount.unit = "$" }) ] , "from_List" ~: TestList [ "from_List [$1, 1$] = $2" ~: Amount.from_List [ Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.unit_side = Just $ Style.Side_Left } , Amount.unit = "$" } , Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.unit_side = Just $ Style.Side_Right } , Amount.unit = "$" } ] ~?= Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = Decimal 0 2 , Amount.style = Style.nil { Style.unit_side = Just $ Style.Side_Left } , Amount.unit = "$" }) ] ] ] ] , "Calc" ~: TestList [ "Balance" ~: TestList [ "posting" ~: TestList [ "[A+$1] = A+$1 & $+1" ~: (Calc.Balance.posting Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] } Calc.Balance.nil) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "[A+$1, A-$1] = {A+$0, $+0}" ~: (Data.List.foldl (flip Calc.Balance.posting) Calc.Balance.nil [ Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] } , Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ -1 ] } ]) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 0 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~: (Data.List.foldl (flip Calc.Balance.posting) Calc.Balance.nil [ Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] } , Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.eur $ -1 ] } ]) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ -1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~: (Data.List.foldl (flip Calc.Balance.posting) Calc.Balance.nil [ Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] } , Posting.nil { Posting.account=["B"] , Posting.amounts=Amount.from_List [ Amount.usd $ -1 ] } ]) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.usd $ -1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } ] } , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~: (Data.List.foldl (flip Calc.Balance.posting) Calc.Balance.nil [ Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ] } , Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ] } ]) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: (Data.List.foldl (flip Calc.Balance.posting) Calc.Balance.nil [ Posting.nil { Posting.account=["A"] , Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ] } , Posting.nil { Posting.account=["B"] , Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ] } ]) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]) , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.gbp $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } ] } ] , "union" ~: TestList [ "nil nil = nil" ~: Calc.Balance.union Calc.Balance.nil Calc.Balance.nil ~?= Calc.Balance.nil , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~: Calc.Balance.union (Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] }) (Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] }) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 2 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 2 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~: Calc.Balance.union (Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] }) (Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["B"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["B"]] } ] }) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 2 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } ] } , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~: Calc.Balance.union (Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] }) (Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["B"], Amount.from_List [ Amount.eur $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["B"]] } ] }) ~?= Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.eur $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["B"]] } ] } ] , "expand" ~: TestList [ "nil_By_Account = nil_By_Account" ~: Calc.Balance.expand Calc.Balance.nil_By_Account ~?= (Calc.Balance.Expanded $ Calc.Balance.nil_By_Account) , "A+$1 = A+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A/A+$1 = A+$1 A/A+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A", "A"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "A"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A/B+$1 = A+$1 A/B+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A+$1 A/B+$1 = A+$2 A/B+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 2 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 3 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 2 ]) , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "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" ~: Calc.Balance.expand (Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 4 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 3 ]) , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 2 ]) , (["A", "B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A+$1 A/B+$1 B/A+$1 = A+$2 A/B+$1 B/A+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 2 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.usd $ 1 ]) , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ]) , "A+$1 A/B+$1 B/A+$1 = A+$2 A/B+$1 B/A+$1" ~: Calc.Balance.expand (Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Calc.Balance.Expanded $ Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 2 ]) , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.usd $ 1 ]) , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ]) ] , "is_equilibrated" ~: TestList [ "nil = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.nil , "{A+$0, $+0} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 0 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "{A+$1, $+1} = False" ~: TestCase $ (@=?) False $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "{A+$0+€0, $0 €+0} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "{A+$1, B-$1, $+0} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.usd $ -1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } ] } , "{A+$1 B, $+1} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List []) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } ] } , "{A+$1 B+€1, $+1 €+1} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.eur $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["B"]] } ] } , "{A+$1 B-$1+€1, $+0 €+1} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 1 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["B"]] } ] } , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0} = True" ~: TestCase $ (@=?) True $ Calc.Balance.is_equilibrated $ Calc.Balance.Balance { Calc.Balance.by_account = Data.Map.fromList [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]) , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]) ] , Calc.Balance.by_unit = Data.Map.fromList $ Data.List.map Calc.Balance.assoc_by_amount_unit $ [ Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.usd $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.eur $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } , Calc.Balance.Sum_by_Unit { Calc.Balance.amount = Amount.gbp $ 0 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,()) [["A"], ["B"]] } ] } ] ] ] , "Format" ~: TestList [ "Ledger" ~: TestList [ "Read" ~: TestList [ "account_name" ~: TestList [ "\"\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" ""]) ~?= [] , "\"A\" = Right \"A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "A"]) ~?= ["A"] , "\"AA\" = Right \"AA\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "AA"]) ~?= ["AA"] , "\" \" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" " "]) ~?= [] , "\":\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" ":"]) ~?= [] , "\"A:\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "A:"]) ~?= [] , "\":A\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" ":A"]) ~?= [] , "\"A \" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "A "]) ~?= [] , "\"A \" ^= Right" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name) () "" "A "]) ~?= ["A"] , "\"A A\" = Right \"A A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "A A"]) ~?= ["A A"] , "\"A \" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "A "]) ~?= [] , "\"A \\n\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "A \n"]) ~?= [] , "\"(A)A\" = Right \"(A)A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "(A)A"]) ~?= ["(A)A"] , "\"( )A\" = Right \"( )A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "( )A"]) ~?= ["( )A"] , "\"(A) A\" = Right \"(A) A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "(A) A"]) ~?= ["(A) A"] , "\"[ ]A\" = Right \"[ ]A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "[ ]A"]) ~?= ["[ ]A"] , "\"(A) \" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "(A) "]) ~?= [] , "\"(A)\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "(A)"]) ~?= [] , "\"[A]A\" = Right \"(A)A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "[A]A"]) ~?= ["[A]A"] , "\"[A] A\" = Right \"[A] A\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "[A] A"]) ~?= ["[A] A"] , "\"[A] \" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "[A] "]) ~?= [] , "\"[A]\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account_name <* P.eof) () "" "[A]"]) ~?= [] ] , "account" ~: TestList [ "\"\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" ""]) ~?= [] , "\"A\" = Right [\"A\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A"]) ~?= [["A"]] , "\"A:\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A:"]) ~?= [] , "\":A\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" ":A"]) ~?= [] , "\"A \" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A "]) ~?= [] , "\" A\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" " A"]) ~?= [] , "\"A:B\" = Right [\"A\", \"B\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A:B"]) ~?= [["A", "B"]] , "\"A:B:C\" = Right [\"A\", \"B\", \"C\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A:B:C"]) ~?= [["A", "B", "C"]] , "\"Aa:Bbb:Cccc\" = Right [\"Aa\", \"Bbb\", \":Cccc\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "Aa:Bbb:Cccc"]) ~?= [["Aa", "Bbb", "Cccc"]] , "\"A a : B b b : C c c c\" = Right [\"A a \", \" B b b \", \": C c c c\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A a : B b b : C c c c"]) ~?= [["A a ", " B b b ", " C c c c"]] , "\"A: :C\" = Right [\"A\", \" \", \"C\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A: :C"]) ~?= [["A", " ", "C"]] , "\"A::C\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.account <* P.eof) () "" "A::C"]) ~?= [] ] , "amount" ~: TestList [ "\"\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" ""]) ~?= [] , "\"0\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 }] , "\"00\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 }] , "\"0.\" = Right 0." ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0."]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just '.' } }] , "\".0\" = Right 0.0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" ".0"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.precision = 1 } }] , "\"0,\" = Right 0," ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0,"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just ',' } }] , "\",0\" = Right 0,0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" ",0"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.precision = 1 } }] , "\"0_\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0_"]) ~?= [] , "\"_0\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "_0"]) ~?= [] , "\"0.0\" = Right 0.0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0.0"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.precision = 1 } }] , "\"00.00\" = Right 0.00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "00.00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.precision = 2 } }] , "\"0,0\" = Right 0,0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0,0"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.precision = 1 } }] , "\"00,00\" = Right 0,00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "00,00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.precision = 2 } }] , "\"0_0\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0_0"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Just $ Style.Grouping '_' [1] , Style.precision = 0 } }] , "\"00_00\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "00_00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Just $ Style.Grouping '_' [2] , Style.precision = 0 } }] , "\"0,000.00\" = Right 0,000.00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "0,000.00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.grouping_integral = Just $ Style.Grouping ',' [3] , Style.precision = 2 } }] , "\"0.000,00\" = Right 0.000,00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount) () "" "0.000,00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.grouping_integral = Just $ Style.Grouping '.' [3] , Style.precision = 2 } }] , "\"1,000.00\" = Right 1,000.00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1,000.00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.grouping_integral = Just $ Style.Grouping ',' [3] , Style.precision = 2 } }] , "\"1.000,00\" = Right 1.000,00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount) () "" "1.000,00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.grouping_integral = Just $ Style.Grouping '.' [3] , Style.precision = 2 } }] , "\"1,000.00.\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount) () "" "1,000.00."]) ~?= [] , "\"1.000,00,\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount) () "" "1.000,00,"]) ~?= [] , "\"1,000.00_\" = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount) () "" "1,000.00_"]) ~?= [] , "\"12\" = Right 12" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "123"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 123 }] , "\"1.2\" = Right 1.2" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1.2"]) ~?= [Amount.nil { Amount.quantity = Decimal 1 12 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.precision = 1 } }] , "\"1,2\" = Right 1,2" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1,2"]) ~?= [Amount.nil { Amount.quantity = Decimal 1 12 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.precision = 1 } }] , "\"12.23\" = Right 12.23" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "12.34"]) ~?= [Amount.nil { Amount.quantity = Decimal 2 1234 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.precision = 2 } }] , "\"12,23\" = Right 12,23" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "12,34"]) ~?= [Amount.nil { Amount.quantity = Decimal 2 1234 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.precision = 2 } }] , "\"1_2\" = Right 1_2" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1_2"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 12 , Amount.style = Style.nil { Style.grouping_integral = Just $ Style.Grouping '_' [1] , Style.precision = 0 } }] , "\"1_23\" = Right 1_23" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1_23"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 123 , Amount.style = Style.nil { Style.grouping_integral = Just $ Style.Grouping '_' [2] , Style.precision = 0 } }] , "\"1_23_456\" = Right 1_23_456" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1_23_456"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 123456 , Amount.style = Style.nil { Style.grouping_integral = Just $ Style.Grouping '_' [3, 2] , Style.precision = 0 } }] , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1_23_456.7890_12345_678901"]) ~?= [Amount.nil { Amount.quantity = Decimal 15 123456789012345678901 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.grouping_integral = Just $ Style.Grouping '_' [3, 2] , Style.grouping_fractional = Just $ Style.Grouping '_' [4, 5, 6] , Style.precision = 15 } }] , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "123456_78901_2345.678_90_1"]) ~?= [Amount.nil { Amount.quantity = Decimal 6 123456789012345678901 , Amount.style = Style.nil { Style.fractioning = Just '.' , Style.grouping_integral = Just $ Style.Grouping '_' [4, 5, 6] , Style.grouping_fractional = Just $ Style.Grouping '_' [3, 2] , Style.precision = 6 } }] , "\"$1\" = Right $1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "$1"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"1$\" = Right 1$" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1$"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Right , Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"$ 1\" = Right $ 1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "$ 1"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just True } , Amount.unit = "$" }] , "\"1 $\" = Right 1 $" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1 $"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Right , Style.unit_spaced = Just True } , Amount.unit = "$" }] , "\"-$1\" = Right $-1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "-$1"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 (-1) , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "\"4 2\"1"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "4 2" }] , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1\"4 2\""]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Style.nil { Style.fractioning = Nothing , Style.grouping_integral = Nothing , Style.grouping_fractional = Nothing , Style.precision = 0 , Style.unit_side = Just Style.Side_Right , Style.unit_spaced = Just False } , Amount.unit = "4 2" }] , "\"$1.000,00\" = Right $1.000,00" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "$1.000,00"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.grouping_integral = Just $ Style.Grouping '.' [3] , Style.grouping_fractional = Nothing , Style.precision = 2 , Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"1.000,00$\" = Right 1.000,00$" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.amount <* P.eof) () "" "1.000,00$"]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Style.nil { Style.fractioning = Just ',' , Style.grouping_integral = Just $ Style.Grouping '.' [3] , Style.grouping_fractional = Nothing , Style.precision = 2 , Style.unit_side = Just Style.Side_Right , Style.unit_spaced = Just False } , Amount.unit = "$" }] ] , "comment" ~: TestList [ "; some comment = Right \" some comment\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.comment <* P.eof) () "" "; some comment"]) ~?= [ " some comment" ] , "; some comment \\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.comment <* P.newline <* P.eof) () "" "; some comment \n"]) ~?= [ " some comment " ] , "; some comment \\r\\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof) () "" "; some comment \r\n"]) ~?= [ " some comment " ] ] , "comments" ~: TestList [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.comments <* P.eof) () "" "; some comment\n ; some other comment"]) ~?= [ [" some comment", " some other comment"] ] , "; some comment \\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.comments <* P.string "\n" <* P.eof) () "" "; some comment \n"]) ~?= [ [" some comment "] ] ] , "date" ~: TestList [ "2000/01/01 = Right 2000/01/01" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2000/01/01"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] , "2000/01/01 some text = Right 2000/01/01" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing) () "" "2000/01/01 some text"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] , "2000/01/01 12:34 = Right 2000/01/01 12:34" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2000/01/01 12:34"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.utc)] , "2000/01/01 12:34:56 = Right 2000/01/01 12:34:56" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2000/01/01 12:34:56"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 56)) (Time.utc)] , "2000/01/01 12:34 CET = Right 2000/01/01 12:34 CET" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2000/01/01 12:34 CET"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.TimeZone 60 False "CET")] , "2000/01/01 12:34 +0130 = Right 2000/01/01 12:34 +0130" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2000/01/01 12:34 +0130"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.TimeZone 90 False "+0130")] , "2000/01/01 12:34:56 CET = Right 2000/01/01 12:34:56 CET" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2000/01/01 12:34:56 CET"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 56)) (Time.TimeZone 60 False "CET")] , "2001/02/29 = Left" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date Nothing <* P.eof) () "" "2001/02/29"]) ~?= [] , "01/01 = Right default_year/01/01" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.date (Just 2000) <* P.eof) () "" "01/01"]) ~?= [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] ] , "tag" ~: TestList [ "Name: = Right Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" "Name:"]) ~?= [("Name", "")] , "Name:Value = Right Name:Value" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" "Name:Value"]) ~?= [("Name", "Value")] , "Name:Val ue = Right Name:Val ue" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" "Name:Val ue"]) ~?= [("Name", "Val ue")] ] , "tags" ~: TestList [ "Name: = Right Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" "Name:"]) ~?= [Data.Map.fromList [ ("Name", [""]) ] ] , "Name:, = Right Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.char ',' <* P.eof) () "" "Name:,"]) ~?= [Data.Map.fromList [ ("Name", [""]) ] ] , "Name:,Name: = Right Name:,Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" "Name:,Name:"]) ~?= [Data.Map.fromList [ ("Name", ["", ""]) ] ] , "Name:,Name2: = Right Name:,Name2:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" "Name:,Name2:"]) ~?= [Data.Map.fromList [ ("Name", [""]) , ("Name2", [""]) ] ] , "Name: , Name2: = Right Name: ,Name2:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" "Name: , Name2:"]) ~?= [Data.Map.fromList [ ("Name", [" "]) , ("Name2", [""]) ] ] , "Name:,Name2:,Name3: = Right Name:,Name2:,Name3:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" "Name:,Name2:,Name3:"]) ~?= [Data.Map.fromList [ ("Name", [""]) , ("Name2", [""]) , ("Name3", [""]) ] ] , "Name:Val ue,Name2:V a l u e,Name3:V al ue = Right Name:Val ue,Name2:V a l u e,Name3:V al ue" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" "Name:Val ue,Name2:V a l u e,Name3:V al ue"]) ~?= [Data.Map.fromList [ ("Name", ["Val ue"]) , ("Name2", ["V a l u e"]) , ("Name3", ["V al ue"]) ] ] ] , "posting" ~: TestList [ " A:B:C = Right A:B:C" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.sourcepos = P.newPos "" 1 1 } ] , " !A:B:C = Right !A:B:C" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " !A:B:C"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.status = True } ] , " *A:B:C = Right *A:B:C" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " *A:B:C"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [] , Posting.comments = [] , Posting.dates = [] , Posting.status = True , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [] , Posting.type_ = Posting.Type_Regular } ] , " A:B:C $1 = Right A:B:C $1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C $1"]) ~?= [ Posting.nil { Posting.account = ["A","B","C $1"] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 = Right A:B:C $1" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C $1"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C $1 + 1€"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) , ("€", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Right , Style.unit_spaced = Just False } , Amount.unit = "€" }) ] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1$ = Right A:B:C $2" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C $1 + 1$"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 2 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C $1 + 1$ + 1$"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 3 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; some comment = Right A:B:C ; some comment" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; some comment"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [] , Posting.comments = [" some comment"] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; some comment\n ; some other comment"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [] , Posting.comments = [" some comment", " some other comment"] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting) Format.Ledger.Read.nil_Context "" " A:B:C $1 ; some comment"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.comments = [" some comment"] , Posting.sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; N:V = Right A:B:C ; N:V" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; N:V"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.comments = [" N:V"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [ ("N", ["V"]) ] } ] , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; some comment N:V"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.comments = [" some comment N:V"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [ ("N", ["V"]) ] } ] , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting ) Format.Ledger.Read.nil_Context "" " A:B:C ; some comment N:V v, N2:V2 v2"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.comments = [" some comment N:V v, N2:V2 v2"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [ ("N", ["V v"]) , ("N2", ["V2 v2"]) ] } ] , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; N:V\n ; N:V2"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.comments = [" N:V", " N:V2"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [ ("N", ["V", "V2"]) ] } ] , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; N:V\n ; N2:V"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.comments = [" N:V", " N2:V"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [ ("N", ["V"]) , ("N2", ["V"]) ] } ] , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " A:B:C ; date:2001/01/01"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.comments = [" date:2001/01/01"] , Posting.dates = [ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2001 01 01) (Time.TimeOfDay 0 0 0)) Time.utc ] , Posting.sourcepos = P.newPos "" 1 1 , Posting.tags = Data.Map.fromList [ ("date", ["2001/01/01"]) ] } ] , " (A:B:C) = Right (A:B:C)" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " (A:B:C)"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.type_ = Posting.Type_Virtual } ] , " [A:B:C] = Right [A:B:C]" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.posting <* P.eof) Format.Ledger.Read.nil_Context "" " [A:B:C]"]) ~?= [ Posting.nil { Posting.account = ["A","B","C"] , Posting.sourcepos = P.newPos "" 1 1 , Posting.type_ = Posting.Type_Virtual_Balanced } ] ] , "transaction" ~: TestList [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.transaction <* P.eof) Format.Ledger.Read.nil_Context "" "2000/01/01 some description\n A:B:C $1\n a:b:c"]) ~?= [ Transaction.nil { Transaction.dates= ( Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Transaction.description="some description" , Transaction.postings = Posting.from_List [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 2 1 } , Posting.nil { Posting.account = ["a","b","c"] , Posting.sourcepos = P.newPos "" 3 1 } ] , Transaction.sourcepos = P.newPos "" 1 1 } ] , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.transaction <* P.newline <* P.eof) Format.Ledger.Read.nil_Context "" "2000/01/01 some description\n A:B:C $1\n a:b:c\n"]) ~?= [ Transaction.nil { Transaction.dates= ( Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Transaction.description="some description" , Transaction.postings = Posting.from_List [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 2 1 } , Posting.nil { Posting.account = ["a","b","c"] , Posting.sourcepos = P.newPos "" 3 1 } ] , Transaction.sourcepos = P.newPos "" 1 1 } ] , "2000/01/01 some description ; some comment\\n ; some other;comment\\n; some Tag:\\n; some last comment\\n A:B:C $1\\n a:b:c" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.transaction <* P.eof) Format.Ledger.Read.nil_Context "" "2000/01/01 some description ; some comment\n ; some other;comment\n; some Tag:\n; some last comment\n A:B:C $1\n a:b:c"]) ~?= [ Transaction.nil { Transaction.comments_after = [ " some comment" , " some other;comment" , " some Tag:" , " some last comment" ] , Transaction.dates= ( Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Transaction.description="some description" , Transaction.postings = Posting.from_List [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 5 1 } , Posting.nil { Posting.account = ["a","b","c"] , Posting.sourcepos = P.newPos "" 6 1 , Posting.tags = Data.Map.fromList [] } ] , Transaction.sourcepos = P.newPos "" 1 1 , Transaction.tags = Data.Map.fromList [ ("Tag", [""]) ] } ] ] , "journal" ~: TestList [ "2000/01/01 1° description\\n A:B:C $1\\n a:b:c\\n2000/01/02 2° description\\n A:B:C $1\\n x:y:z" ~: TestCase $ do jnl <- liftIO $ P.runParserT (Format.Ledger.Read.journal "" {-<* P.eof-}) Format.Ledger.Read.nil_Context "" "2000/01/01 1° description\n A:B:C $1\n a:b:c\n2000/01/02 2° description\n A:B:C $1\n x:y:z" (Data.List.map (\j -> j{Format.Ledger.Journal.last_read_time= Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $ Data.Either.rights [jnl]) @?= [ Format.Ledger.Journal.nil { Format.Ledger.Journal.transactions = Transaction.from_List [ Transaction.nil { Transaction.dates= ( Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Transaction.description="1° description" , Transaction.postings = Posting.from_List [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 2 1 } , Posting.nil { Posting.account = ["a","b","c"] , Posting.sourcepos = P.newPos "" 3 1 } ] , Transaction.sourcepos = P.newPos "" 1 1 } , Transaction.nil { Transaction.dates= ( Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 02) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Transaction.description="2° description" , Transaction.postings = Posting.from_List [ Posting.nil { Posting.account = ["A","B","C"] , Posting.amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Style.nil { Style.unit_side = Just Style.Side_Left , Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Posting.sourcepos = P.newPos "" 5 1 } , Posting.nil { Posting.account = ["x","y","z"] , Posting.sourcepos = P.newPos "" 6 1 } ] , Transaction.sourcepos = P.newPos "" 4 1 } ] } ] ] ] ] ] ]