{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} import Prelude import Test.HUnit hiding ((~?)) import Test.Framework.Providers.HUnit (hUnitTestToTests) import Test.Framework.Runners.Console (defaultMain) -- import Control.Applicative (Const(..)) import Control.Monad.IO.Class (liftIO) import Data.Decimal (DecimalRaw(..)) import qualified Data.Either -- import Data.Functor.Compose (Compose(..)) import qualified Data.List import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.Map.Strict as Data.Map import Data.Text (Text) import qualified Data.Time.Calendar as Time import qualified Data.Time.LocalTime as Time import qualified Text.Parsec as P hiding (char, space, spaces, string) import qualified Text.Parsec.Pos as P import qualified Hcompta.Format.Ledger.Account.Read as Account.Read import qualified Hcompta.Format.Ledger.Amount as Amount import qualified Hcompta.Format.Ledger.Amount.Read as Amount.Read import qualified Hcompta.Format.Ledger.Amount.Style as Amount.Style import qualified Hcompta.Format.Ledger.Amount.Write as Amount.Write import qualified Hcompta.Date as Date import qualified Hcompta.Format.Ledger.Date.Read as Date.Read import qualified Hcompta.Format.Ledger.Date.Write as Date.Write import qualified Hcompta.Format.Ledger as Ledger import qualified Hcompta.Format.Ledger.Read as Ledger.Read import qualified Hcompta.Format.Ledger.Write as Ledger.Write import qualified Hcompta.Lib.Parsec as P import qualified Hcompta.Tag as Tag deriving instance Eq Ledger.Amount main :: IO () main = defaultMain $ hUnitTestToTests test_Hcompta -- (~?) :: String -> Bool -> Test -- (~?) s b = s ~: (b ~?= True) test_Hcompta :: Test test_Hcompta = TestList [ "Format" ~: TestList [ "Ledger" ~: TestList [ "Account" ~: TestList [ "Read" ~: TestList [ "section" ~: TestList [ "\"\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" (""::Text)]) ~?= [] , "\"A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A"::Text)]) ~?= ["A"] , "\"AA\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("AA"::Text)]) ~?= ["AA"] , "\" \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" (" "::Text)]) ~?= [] , "\":\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" (":"::Text)]) ~?= [] , "\"A:\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A:"::Text)]) ~?= [] , "\":A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" (":A"::Text)]) ~?= [] , "\"A \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A "::Text)]) ~?= [] , "\"A \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section) () "" ("A "::Text)]) ~?= ["A"] , "\"A A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A A"::Text)]) ~?= ["A A"] , "\"A \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A "::Text)]) ~?= [] , "\"A\t\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A\t"::Text)]) ~?= [] , "\"A \\n\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A \n"::Text)]) ~?= [] , "\"(A)A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("(A)A"::Text)]) ~?= ["(A)A"] , "\"( )A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("( )A"::Text)]) ~?= ["( )A"] , "\"(A) A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("(A) A"::Text)]) ~?= ["(A) A"] , "\"[ ]A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("[ ]A"::Text)]) ~?= ["[ ]A"] , "\"(A) \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("(A) "::Text)]) ~?= [] , "\"(A)\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("(A)"::Text)]) ~?= ["(A)"] , "\"A(A)\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("A(A)"::Text)]) ~?= [("A(A)"::Text)] , "\"[A]A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("[A]A"::Text)]) ~?= ["[A]A"] , "\"[A] A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("[A] A"::Text)]) ~?= ["[A] A"] , "\"[A] \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("[A] "::Text)]) ~?= [] , "\"[A]\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.section <* P.eof) () "" ("[A]"::Text)]) ~?= ["[A]"] ] , "account" ~: TestList [ "\"\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" (""::Text)]) ~?= [] , "\"A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A"::Text)]) ~?= ["A":|[]] , "\"A:\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A:"::Text)]) ~?= [] , "\":A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" (":A"::Text)]) ~?= [] , "\"A \"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A "::Text)]) ~?= [] , "\" A\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" (" A"::Text)]) ~?= [] , "\"A:B\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A:B"::Text)]) ~?= ["A":|["B"]] , "\"A:B:C\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A:B:C"::Text)]) ~?= ["A":|["B", "C"]] , "\"Aa:Bbb:Cccc\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("Aa:Bbb:Cccc"::Text)]) ~?= ["Aa":|["Bbb", "Cccc"]] , "\"A a : B b b : C c c c\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A a : B b b : C c c c"::Text)]) ~?= ["A a ":|[" B b b ", " C c c c"]] , "\"A: :C\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A: :C"::Text)]) ~?= ["A":|[" ", "C"]] , "\"A::C\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A::C"::Text)]) ~?= [] , "\"A:B:(C)\"" ~: (Data.Either.rights $ [P.runParser (Account.Read.account <* P.eof) () "" ("A:B:(C)"::Text)]) ~?= ["A":|["B", "(C)"]] ] ] ] , "Quantity" ~: TestList [ "+" ~: TestList [ "1 + 1 = 2" ~: (+) (Decimal 0 1) (Decimal 0 1) ~?= Decimal 0 2 ] ] , "Amount" ~: TestList [ {- "from_List" ~: TestList [ "from_List [$1, 1$] = $2" ~: Amount.from_List [ Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_style = Amount.Style.empty { Amount.Style.unit_side = Just $ Amount.Style.Side_Left } , Amount.amount_unit = "$" } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_style = Amount.Style.empty { Amount.Style.unit_side = Just $ Amount.Style.Side_Right } , Amount.amount_unit = "$" } ] ~?= Data.Map.fromList [ ("$", Amount.amount { Amount.amount_quantity = Decimal 0 2 , Amount.amount_style = Amount.Style.empty { Amount.Style.unit_side = Just $ Amount.Style.Side_Left } , Amount.amount_unit = "$" }) ] ] ,-} "Read" ~: TestList [ "amount" ~: TestList [ "\"\" = Left" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" (""::Text)]) ~?= [] , "\"0\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0"::Text)]) ~?= [ ( Amount.Style.empty , Amount.amount { Amount.amount_quantity = Decimal 0 0 } ) ] , "\"00\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00"::Text)]) ~?= [ ( Amount.Style.empty , Amount.amount { Amount.amount_quantity = Decimal 0 0 } ) ] , "\"0.\" = Right 0." ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0."::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' } , Amount.amount { Amount.amount_quantity = Decimal 0 0 } ) ] , "\".0\" = Right 0.0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" (".0"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' } , Amount.amount { Amount.amount_quantity = Decimal 1 0 } ) ] , "\"0,\" = Right 0," ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0,"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' } , Amount.amount { Amount.amount_quantity = Decimal 0 0 } ) ] , "\",0\" = Right 0,0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" (",0"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' } , Amount.amount { Amount.amount_quantity = Decimal 1 0 } ) ] , "\"0_\" = Left" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0_"::Text)]) ~?= [] , "\"_0\" = Left" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("_0"::Text)]) ~?= [] , "\"0.0\" = Right 0.0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0.0"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' } , Amount.amount { Amount.amount_quantity = Decimal 1 0 } ) ] , "\"00.00\" = Right 0.00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00.00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' } , Amount.amount { Amount.amount_quantity = Decimal 2 0 } ) ] , "\"0,0\" = Right 0,0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0,0"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' } , Amount.amount { Amount.amount_quantity = Decimal 1 0 } ) ] , "\"00,00\" = Right 0,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00,00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' } , Amount.amount { Amount.amount_quantity = Decimal 2 0 } ) ] , "\"0_0\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0_0"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1] } , Amount.amount { Amount.amount_quantity = Decimal 0 0 } ) ] , "\"00_00\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00_00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2] } , Amount.amount { Amount.amount_quantity = Decimal 0 0 } ) ] , "\"0,000.00\" = Right 0,000.00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0,000.00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] } , Amount.amount { Amount.amount_quantity = Decimal 2 0 } ) ] , "\"0.000,00\" = Right 0.000,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("0.000,00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] } , Amount.amount { Amount.amount_quantity = Decimal 2 0 } ) ] , "\"1,000.00\" = Right 1,000.00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1,000.00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] } , Amount.amount { Amount.amount_quantity = Decimal 2 100000 } ) ] , "\"1.000,00\" = Right 1.000,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("1.000,00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] } , Amount.amount { Amount.amount_quantity = Decimal 2 100000 } ) ] , "\"1,000.00.\" = Left" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("1,000.00."::Text)]) ~?= [] , "\"1.000,00,\" = Left" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("1.000,00,"::Text)]) ~?= [] , "\"1,000.00_\" = Left" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("1,000.00_"::Text)]) ~?= [] , "\"12\" = Right 12" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("123"::Text)]) ~?= [ ( Amount.Style.empty , Amount.amount { Amount.amount_quantity = Decimal 0 123 } ) ] , "\"1.2\" = Right 1.2" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1.2"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' } , Amount.amount { Amount.amount_quantity = Decimal 1 12 } ) ] , "\"1,2\" = Right 1,2" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1,2"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' } , Amount.amount { Amount.amount_quantity = Decimal 1 12 } ) ] , "\"12.34\" = Right 12.34" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("12.34"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' } , Amount.amount { Amount.amount_quantity = Decimal 2 1234 } ) ] , "\"12,34\" = Right 12,34" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("12,34"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' } , Amount.amount { Amount.amount_quantity = Decimal 2 1234 } ) ] , "\"1_2\" = Right 1_2" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_2"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1] } , Amount.amount { Amount.amount_quantity = Decimal 0 12 } ) ] , "\"1_23\" = Right 1_23" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_23"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2] } , Amount.amount { Amount.amount_quantity = Decimal 0 123 } ) ] , "\"1_23_456\" = Right 1_23_456" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_23_456"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2] } , Amount.amount { Amount.amount_quantity = Decimal 0 123456 } ) ] , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_23_456.7890_12345_678901"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2] , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6] } , Amount.amount { Amount.amount_quantity = Decimal 15 123456789012345678901 } ) ] , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("123456_78901_2345.678_90_1"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6] , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2] } , Amount.amount { Amount.amount_quantity = Decimal 6 123456789012345678901 } ) ] , "\"$1\" = Right $1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("$1"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_unit = "$" } ) ] , "\"1$\" = Right 1$" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1$"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_unit = "$" } ) ] , "\"$ 1\" = Right $ 1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("$ 1"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just True } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_unit = "$" } ) ] , "\"1 $\" = Right 1 $" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1 $"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just True } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_unit = "$" } ) ] , "\"-$1\" = Right $-1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("-$1"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 0 (-1) , Amount.amount_unit = "$" } ) ] , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("\"4 2\"1"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_unit = "4 2" } ) ] , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1\"4 2\""::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 0 1 , Amount.amount_unit = "4 2" } ) ] , "\"$1.000,00\" = Right $1.000,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("$1.000,00"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] , Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 2 100000 , Amount.amount_unit = "$" } ) ] , "\"1.000,00$\" = Right 1.000,00$" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1.000,00$"::Text)]) ~?= [ ( Amount.Style.empty { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] , Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , Amount.amount { Amount.amount_quantity = Decimal 2 100000 , Amount.amount_unit = "$" } ) ] ] ] , "Write" ~: TestList [ "amount" ~: TestList [ "empty" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty,) Amount.amount) ~?= "0") , "0.00" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 2 0 }) ~?= "0.00") , "123" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 0 123 }) ~?= "123") , "-123" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 0 (- 123) }) ~?= "-123") , "12.3" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' },) Amount.amount { Amount.amount_quantity = Decimal 1 123 }) ~?= "12.3") , "12.5" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' },) Amount.amount { Amount.amount_quantity = Decimal 1 125 }) ~?= "12.5") , "12.3" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' },) Amount.amount { Amount.amount_quantity = Decimal 1 123 }) ~?= "12.3") , "1,234.56" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] },) Amount.amount { Amount.amount_quantity = Decimal 2 123456 }) ~?= "1,234.56") , "123,456,789,01,2.3456789" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3] },) Amount.amount { Amount.amount_quantity = Decimal 7 1234567890123456789 }) ~?= "123,456,789,01,2.3456789") , "1234567.8,90,123,456,789" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3] },) Amount.amount { Amount.amount_quantity = Decimal 12 1234567890123456789 }) ~?= "1234567.8,90,123,456,789") , "1,2,3,4,5,6,7,89,012.3456789" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1] },) Amount.amount { Amount.amount_quantity = Decimal 7 1234567890123456789 }) ~?= "1,2,3,4,5,6,7,89,012.3456789") , "1234567.890,12,3,4,5,6,7,8,9" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Amount.Write.amount $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1] },) Amount.amount { Amount.amount_quantity = Decimal 12 1234567890123456789 }) ~?= "1234567.890,12,3,4,5,6,7,8,9") ] , "amount_length" ~: TestList [ "empty" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount) ~?= 1) , "0.00" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 2 0 }) ~?= 4) , "123" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 0 123 }) ~?= 3) , "-123" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 0 (- 123) }) ~?= 4) , "12.3" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' },) Amount.amount { Amount.amount_quantity = Decimal 1 123 }) ~?= 4) , "12.5" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' },) Amount.amount { Amount.amount_quantity = Decimal 1 125 }) ~?= 4) , "12.3" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' },) Amount.amount { Amount.amount_quantity = Decimal 1 123 }) ~?= 4) , "1,234.56" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] },) Amount.amount { Amount.amount_quantity = Decimal 2 123456 }) ~?= 8) , "123,456,789,01,2.3456789" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3] },) Amount.amount { Amount.amount_quantity = Decimal 7 1234567890123456789 }) ~?= 24) , "1234567.8,90,123,456,789" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3] },) Amount.amount { Amount.amount_quantity = Decimal 12 1234567890123456789 }) ~?= 24) , "1,2,3,4,5,6,7,89,012.3456789" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1] },) Amount.amount { Amount.amount_quantity = Decimal 7 1234567890123456789 }) ~?= 28) , "1234567.890,12,3,4,5,6,7,8,9" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1] },) Amount.amount { Amount.amount_quantity = Decimal 12 1234567890123456789 }) ~?= 28) , "1000000.000,00,0,0,0,0,0,0,0" ~: ((Amount.Write.amount_length $ (Amount.Style.empty { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1] },) Amount.amount { Amount.amount_quantity = Decimal 12 1000000000000000000 }) ~?= 28) , "999" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 0 999 }) ~?= 3) , "1000" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 0 1000 }) ~?= 4) , "10,00€" ~: ((Amount.Write.amount_length $ (Amount.Style.empty,) Amount.amount { Amount.amount_quantity = Decimal 2 1000 , Amount.amount_unit = "€" }) ~?= 6) ] ] ] , "Date" ~: TestList [ "Read" ~: TestList [ "date" ~: TestList [ "2000/01/01" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2000/01/01"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] , "2000/01/01 some text" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing) () "" ("2000/01/01 some text"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] , "2000/01/01_12:34" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2000/01/01_12:34"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.utc)] , "2000/01/01_12:34:56" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2000/01/01_12:34:56"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 56)) (Time.utc)] , "2000/01/01_12:34CET" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2000/01/01_12:34CET"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.TimeZone 60 True "CET")] , "2000/01/01_12:34+0130" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2000/01/01_12:34+0130"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.TimeZone 90 False "+0130")] , "2000/01/01_12:34:56CET" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2000/01/01_12:34:56CET"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 56)) (Time.TimeZone 60 True "CET")] , "2001/02/29" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id Nothing <* P.eof) () "" ("2001/02/29"::Text)]) ~?= [] , "01/01" ~: (Data.Either.rights $ [P.runParser_with_Error (Date.Read.date id (Just 2000) <* P.eof) () "" ("01/01"::Text)]) ~?= [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] ] ] , "Write" ~: TestList [ "date" ~: TestList [ "nil" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date Date.nil) ~?= "1970/01/01") , "2000/01/01_12:34:51CET" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 51)) (Time.TimeZone 60 False "CET")) ~?= "2000/01/01_11:34:51" , "2000/01/01_12:34:51+0100" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 51)) (Time.TimeZone 60 False "")) ~?= "2000/01/01_11:34:51" , "2000/01/01_01:02:03" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 1 2 3)) (Time.utc)) ~?= "2000/01/01_01:02:03" , "01/01_01:02" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 0 01 01) (Time.TimeOfDay 1 2 0)) (Time.utc)) ~?= "01/01_01:02" , "01/01_01:00" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 0 01 01) (Time.TimeOfDay 1 0 0)) (Time.utc)) ~?= "01/01_01:00" , "01/01_00:01" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 0 01 01) (Time.TimeOfDay 0 1 0)) (Time.utc)) ~?= "01/01_00:01" , "01/01" ~: (Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Date.Write.date $ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 0 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)) ~?= "01/01" ] ] ] , "Read" ~: TestList [ "posting_type" ~: TestList [ "A" ~: Ledger.Read.posting_type ("A":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|[]) , "(" ~: Ledger.Read.posting_type ("(":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "(":|[]) , ")" ~: Ledger.Read.posting_type (")":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, ")":|[]) , "()" ~: Ledger.Read.posting_type ("()":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "()":|[]) , "( )" ~: Ledger.Read.posting_type ("( )":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "( )":|[]) , "(A)" ~: Ledger.Read.posting_type ("(A)":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Virtual, "A":|[]) , "(A:B:C)" ~: Ledger.Read.posting_type ("(A":|["B", "C)"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Virtual, "A":|["B", "C"]) , "A:B:C" ~: Ledger.Read.posting_type ("A":|["B", "C"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|["B", "C"]) , "(A):B:C" ~: Ledger.Read.posting_type ("(A)":|["B", "C"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "(A)":|["B", "C"]) , "A:(B):C" ~: Ledger.Read.posting_type ("A":|["(B)", "C"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|["(B)", "C"]) , "A:B:(C)" ~: Ledger.Read.posting_type ("A":|["B", "(C)"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|["B", "(C)"]) , "[" ~: Ledger.Read.posting_type ("[":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "[":|[]) , "]" ~: Ledger.Read.posting_type ("]":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "]":|[]) , "[]" ~: Ledger.Read.posting_type ("[]":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "[]":|[]) , "[ ]" ~: Ledger.Read.posting_type ("[ ]":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "[ ]":|[]) , "[A]" ~: Ledger.Read.posting_type ("[A]":|[]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Virtual_Balanced, "A":|[]) , "[A:B:C]" ~: Ledger.Read.posting_type ("[A":|["B", "C]"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Virtual_Balanced, "A":|["B", "C"]) , "A:B:C" ~: Ledger.Read.posting_type ("A":|["B", "C"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|["B", "C"]) , "[A]:B:C" ~: Ledger.Read.posting_type ("[A]":|["B", "C"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "[A]":|["B", "C"]) , "A:[B]:C" ~: Ledger.Read.posting_type ("A":|["[B]", "C"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|["[B]", "C"]) , "A:B:[C]" ~: Ledger.Read.posting_type ("A":|["B", "[C]"]) ~?= Ledger.Posting_Typed (Ledger.Posting_Type_Regular, "A":|["B", "[C]"]) ] , "comment" ~: TestList [ "; some comment = Right \" some comment\"" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.comment <* P.eof) () "" ("; some comment"::Text)]) ~?= [ " some comment" ] , "; some comment \\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.comment <* P.newline <* P.eof) () "" ("; some comment \n"::Text)]) ~?= [ " some comment " ] , "; some comment \\r\\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.comment <* P.string "\r\n" <* P.eof) () "" ("; some comment \r\n"::Text)]) ~?= [ " some comment " ] ] , "comments" ~: TestList [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.comments <* P.eof) () "" ("; some comment\n ; some other comment"::Text)]) ~?= [ [" some comment", " some other comment"] ] , "; some comment \\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.comments <* P.string "\n" <* P.eof) () "" ("; some comment \n"::Text)]) ~?= [ [" some comment "] ] ] , "tag_value" ~: TestList [ "," ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag_value <* P.eof) () "" (","::Text)]) ~?= [","] , ",\\n" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag_value <* P.char '\n' <* P.eof) () "" (",\n"::Text)]) ~?= [","] , ",x" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag_value <* P.eof) () "" (",x"::Text)]) ~?= [",x"] , ",x:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag_value <* P.string ",x:" <* P.eof) () "" (",x:"::Text)]) ~?= [""] , "v, v, n:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag_value <* P.string ", n:" <* P.eof) () "" ("v, v, n:"::Text)]) ~?= ["v, v"] ] , "tag" ~: TestList [ "Name:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.eof) () "" ("Name:"::Text)]) ~?= [("Name":|[], "")] , "Name:Value" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.eof) () "" ("Name:Value"::Text)]) ~?= [("Name":|[], "Value")] , "Name:Value\\n" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.string "\n" <* P.eof) () "" ("Name:Value\n"::Text)]) ~?= [("Name":|[], "Value")] , "Name:Val ue" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.eof) () "" ("Name:Val ue"::Text)]) ~?= [("Name":|[], "Val ue")] , "Name:," ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.eof) () "" ("Name:,"::Text)]) ~?= [("Name":|[], ",")] , "Name:Val,ue" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.eof) () "" ("Name:Val,ue"::Text)]) ~?= [("Name":|[], "Val,ue")] , "Name:Val,ue:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.string ",ue:" <* P.eof) () "" ("Name:Val,ue:"::Text)]) ~?= [("Name":|[], "Val")] , "Name:Val,ue :" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tag <* P.eof) () "" ("Name:Val,ue :"::Text)]) ~?= [("Name":|[], "Val,ue :")] ] , "tags" ~: TestList [ "Name:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name:"::Text)]) ~?= [Data.Map.fromList [ ("Name":|[], [""]) ] ] , "Name:," ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name:,"::Text)]) ~?= [Data.Map.fromList [ ("Name":|[], [","]) ] ] , "Name:,Name:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name:,Name:"::Text)]) ~?= [Data.Map.fromList [ ("Name":|[], ["", ""]) ] ] , "Name:,Name2:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name:,Name2:"::Text)]) ~?= [Data.Map.fromList [ ("Name":|[], [""]) , ("Name2":|[], [""]) ] ] , "Name: , Name2:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name: , Name2:"::Text)]) ~?= [Data.Map.fromList [ ("Name":|[], [" "]) , ("Name2":|[], [""]) ] ] , "Name:,Name2:,Name3:" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name:,Name2:,Name3:"::Text)]) ~?= [Data.Map.fromList [ ("Name":|[], [""]) , ("Name2":|[], [""]) , ("Name3":|[], [""]) ] ] , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~: (Data.Either.rights $ [P.runParser (Ledger.Read.tags <* P.eof) () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)]) ~?= [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_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C"::Text)]) ~?= [ Ledger.Posting_Typed ( Ledger.Posting_Type_Regular , (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_sourcepos = P.newPos "" 1 1 } ) ] , " !A:B:C = Right !A:B:C" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" !A:B:C"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_status = True } ] , " *A:B:C = Right *A:B:C" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" *A:B:C"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [] , Ledger.posting_comments = [] , Ledger.posting_dates = [] , Ledger.posting_status = True , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = mempty } ] , " A:B:C $1 = Right A:B:C $1" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C $1"::Text)]) ~?= [ (Ledger.posting ("A":|["B","C $1"])) { Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 = Right A:B:C $1" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C $1"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C $1 + 1€"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) , ("€", 1) ] , Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1$ = Right A:B:C $2" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C $1 + 1$"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 2) ] , Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C $1 + 1$ + 1$"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 3) ] , Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; some comment = Right A:B:C ; some comment" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; some comment"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [] , Ledger.posting_comments = [" some comment"] , Ledger.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.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; some comment\n ; some other comment"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [] , Ledger.posting_comments = [" some comment", " some other comment"] , Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C $1 ; some comment"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_comments = [" some comment"] , Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; N:V = Right A:B:C ; N:V" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; N:V"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_comments = [" N:V"] , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = Tag.from_List [ ("N":|[], "V") ] } ] , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; some comment N:V"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_comments = [" some comment N:V"] , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = Tag.from_List [ ("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.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting ) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"] , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = Tag.from_List [ ("N":|[], "V v") , ("N2":|[], "V2 v2") ] } ] , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; N:V\n ; N:V2"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_comments = [" N:V", " N:V2"] , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = Tag.from_List [ ("N":|[], "V") , ("N":|[], "V2") ] } ] , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; N:V\n ; N2:V"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_comments = [" N:V", " N2:V"] , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = Tag.from_List [ ("N":|[], "V") , ("N2":|[], "V") ] } ] , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~: (Data.List.map (\(Ledger.Posting_Typed (_pt, p)) -> p) $ Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" A:B:C ; date:2001/01/01"::Text)]) ~?= [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_comments = [" date:2001/01/01"] , Ledger.posting_dates = [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2001 01 01) (Time.TimeOfDay 0 0 0)) Time.utc ] , Ledger.posting_sourcepos = P.newPos "" 1 1 , Ledger.posting_tags = Tag.from_List [ ("date":|[], "2001/01/01") ] } ] , " (A:B:C) = Right (A:B:C)" ~: (Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" (A:B:C)"::Text)]) ~?= [ Ledger.Posting_Typed ( Ledger.Posting_Type_Virtual , (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_sourcepos = P.newPos "" 1 1 } ) ] , " [A:B:C] = Right [A:B:C]" ~: (Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.posting <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" (" [A:B:C]"::Text)]) ~?= [ Ledger.Posting_Typed ( Ledger.Posting_Type_Virtual_Balanced , (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_sourcepos = P.newPos "" 1 1 } ) ] ] , "transaction" ~: TestList [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~: (Data.Either.rights $ [P.runParser_with_Error (Ledger.Read.transaction <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)]) ~?= [ Ledger.transaction { Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="some description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_sourcepos = P.newPos "" 2 1 } , (Ledger.posting ("a":|["b", "c"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", -1) ] , Ledger.posting_sourcepos = P.newPos "" 3 1 } ] , Ledger.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_with_Error (Ledger.Read.transaction <* P.newline <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)]) ~?= [ Ledger.transaction { Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="some description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_sourcepos = P.newPos "" 2 1 } , (Ledger.posting ("a":|["b", "c"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", -1) ] , Ledger.posting_sourcepos = P.newPos "" 3 1 } ] , Ledger.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_with_Error (Ledger.Read.transaction <* P.eof) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" ("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"::Text)]) ~?= [ Ledger.transaction { Ledger.transaction_comments_after = [ " some comment" , " some other;comment" , " some Tag:" , " some last comment" ] , Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="some description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_sourcepos = P.newPos "" 5 1 } , (Ledger.posting ("a":|["b", "c"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", -1) ] , Ledger.posting_sourcepos = P.newPos "" 6 1 } ] , Ledger.transaction_tags = Tag.from_List [ ("Tag":|[], "") ] , Ledger.transaction_sourcepos = P.newPos "" 1 1 } ] ] , "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_with_Error (Ledger.Read.journal "" {-<* P.eof-}) ( Ledger.Read.context () Ledger.journal ::Ledger.Read.Context () [] Ledger.Transaction) "" ("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"::Text) (Data.List.map (\j -> j{Ledger.journal_last_read_time=Date.nil}) $ Data.Either.rights [jnl]) @?= [ Ledger.journal { Ledger.journal_sections = fmap (Ledger.Chart_With . (mempty,)) $ [ Ledger.transaction { Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 02) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="2° description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_sourcepos = P.newPos "" 5 1 } , (Ledger.posting ("x":|["y", "z"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", -1) ] , Ledger.posting_sourcepos = P.newPos "" 6 1 } ] , Ledger.transaction_sourcepos = P.newPos "" 4 1 } , Ledger.transaction { Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="1° description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] , Ledger.posting_sourcepos = P.newPos "" 2 1 } , (Ledger.posting ("a":|["b", "c"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", -1) ] , Ledger.posting_sourcepos = P.newPos "" 3 1 } ] , Ledger.transaction_sourcepos = P.newPos "" 1 1 } ] , Ledger.journal_amount_styles = Amount.Style.Styles $ Data.Map.fromList [ ( Ledger.Unit "$" , Amount.Style.empty { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } ) ] } ] ] ] , "Write" ~: TestList [ "account" ~: TestList [ "A" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.account Ledger.Posting_Type_Regular $ "A":|[]) ~?= "A") , "A:B:C" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.account Ledger.Posting_Type_Regular $ "A":|["B", "C"]) ~?= "A:B:C") , "(A:B:C)" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.account Ledger.Posting_Type_Virtual $ "A":|["B", "C"]) ~?= "(A:B:C)") , "[A:B:C]" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.account Ledger.Posting_Type_Virtual_Balanced $ "A":|["B", "C"]) ~?= "[A:B:C]") ] , "transaction" ~: TestList [ "nil" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.transaction Amount.Style.styles Ledger.transaction) ~?= "1970/01/01\n\n") , "2000/01/01 some description\\n\\tA:B:C $1\\n\\ta:b:c\\n\\t ; first comment\\n\\t ; second comment\\n\\t ; third comment\\n" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.transaction Amount.Style.styles Ledger.transaction { Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="some description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] } , (Ledger.posting ("a":|["b", "c"])) { Ledger.posting_comments = ["first comment","second comment","third comment"] } ] }) ~?= "2000/01/01 some description\n\tA:B:C $1\n\ta:b:c\n\t ; first comment\n\t ; second comment\n\t ; third comment\n") , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~: ((Ledger.Write.show Ledger.Write.Style { Ledger.Write.style_color=False , Ledger.Write.style_align=True } $ Ledger.Write.transaction Amount.Style.styles Ledger.transaction { Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Ledger.transaction_description="some description" , Ledger.transaction_postings = Ledger.map_Postings_by_Account [ (Ledger.posting ("A":|["B", "C"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 1) ] } , (Ledger.posting ("AA":|["BB", "CC"])) { Ledger.posting_amounts = Data.Map.fromList [ ("$", 123) ] } ] }) ~?= "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123\n") ] ] ] ] ]