{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# 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.Arrow ((***)) import Control.Monad.IO.Class (liftIO) import Data.Decimal (DecimalRaw(..)) import qualified Data.Either import Data.Function (on) -- import Data.Functor.Compose (Compose(..)) import qualified Data.List import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.Map.Strict as Data.Map import Data.Maybe (fromJust) import qualified Data.Strict.Maybe as Strict 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 Text.PrettyPrint.Leijen.Text as PP import Hcompta.Account (Account) import qualified Hcompta.Account as Account import qualified Hcompta.Account.Read as Account.Read import Hcompta.Amount (Amount) import qualified Hcompta.Amount as Amount import qualified Hcompta.Amount.Read as Amount.Read import qualified Hcompta.Amount.Write as Amount.Write import qualified Hcompta.Amount.Style as Amount.Style import qualified Hcompta.Balance as Balance import qualified Hcompta.Date as Date import qualified Hcompta.Date.Read as Date.Read import qualified Hcompta.Date.Write as Date.Write import qualified Hcompta.Filter as Filter import qualified Hcompta.Filter.Read as Filter.Read import qualified Hcompta.Format.Ledger as Format.Ledger import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write import qualified Hcompta.Posting as Posting -- import qualified Hcompta.Journal as Journal import qualified Hcompta.Lib.Foldable as Lib.Foldable import qualified Hcompta.Lib.Interval as Lib.Interval import qualified Hcompta.Lib.Interval.Sieve as Lib.Interval.Sieve import qualified Hcompta.Lib.Parsec as P import qualified Hcompta.Lib.TreeMap as Lib.TreeMap main :: IO () main = defaultMain $ hUnitTestToTests test_Hcompta (~?) :: String -> Bool -> Test (~?) s b = s ~: (b ~?= True) test_Hcompta :: Test test_Hcompta = TestList [ "Lib" ~: TestList [ "TreeMap" ~: TestList [ "insert" ~: TestList [ "[] 0" ~: (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty) ~?= (Lib.TreeMap.TreeMap $ Data.Map.fromList [ ((0::Int), Lib.TreeMap.leaf ()) ]) , "[] 0/1" ~: (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty) ~?= (Lib.TreeMap.TreeMap $ Data.Map.fromList [ ((0::Int), Lib.TreeMap.Node { Lib.TreeMap.node_value = Strict.Nothing , Lib.TreeMap.node_size = 1 , Lib.TreeMap.node_descendants = Lib.TreeMap.singleton ((1::Int):|[]) () }) ]) ] , "union" ~: TestList [ ] , "map_by_depth_first" ~: TestList [ "[0, 0/1, 0/1/2, 1, 1/2/3]" ~: (Lib.TreeMap.map_by_depth_first (\descendants value -> Data.Map.foldl' (\acc v -> (++) acc $ Strict.fromMaybe undefined $ Lib.TreeMap.node_value v ) (Strict.fromMaybe [] value) (Lib.TreeMap.nodes descendants) ) $ Lib.TreeMap.from_List const [ (((0::Integer):|[]), [0]) , ((0:|1:[]), [0,1]) , ((0:|1:2:[]), [0,1,2]) , ((1:|[]), [1]) , ((1:|2:3:[]), [1,2,3]) ] ) ~?= (Lib.TreeMap.from_List const [ ((0:|[]), [0,0,1,0,1,2]) , ((0:|1:[]), [0,1,0,1,2]) , ((0:|1:2:[]), [0,1,2]) , ((1:|[]), [1,1,2,3]) , ((1:|2:[]), [1,2,3]) , ((1:|2:3:[]), [1,2,3]) ]) , "[0/0]" ~: (Lib.TreeMap.map_by_depth_first (\descendants value -> Data.Map.foldl' (\acc v -> (++) acc $ Strict.fromMaybe undefined $ Lib.TreeMap.node_value v ) (Strict.fromMaybe [] value) (Lib.TreeMap.nodes descendants) ) $ Lib.TreeMap.from_List const [ (((0::Integer):|0:[]), [0,0]) ] ) ~?= (Lib.TreeMap.from_List const [ ((0:|[]), [0,0]) , ((0:|0:[]), [0,0]) ]) ] , "flatten" ~: TestList [ "[0, 0/1, 0/1/2]" ~: (Lib.TreeMap.flatten id $ Lib.TreeMap.from_List const [ (((0::Integer):|[]), ()) , ((0:|1:[]), ()) , ((0:|1:2:[]), ()) ] ) ~?= (Data.Map.fromList [ ((0:|[]), ()) , ((0:|1:[]), ()) , ((0:|1:2:[]), ()) ]) , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~: (Lib.TreeMap.flatten id $ Lib.TreeMap.from_List const [ ((1:|[]), ()) , ((1:|2:[]), ()) , ((1:|22:[]), ()) , ((1:|2:3:[]), ()) , ((1:|2:33:[]), ()) , ((11:|[]), ()) , ((11:|2:[]), ()) , ((11:|2:3:[]), ()) , ((11:|2:33:[]), ()) ] ) ~?= (Data.Map.fromList [ (((1::Integer):|[]), ()) , ((1:|2:[]), ()) , ((1:|22:[]), ()) , ((1:|2:3:[]), ()) , ((1:|2:33:[]), ()) , ((11:|[]), ()) , ((11:|2:[]), ()) , ((11:|2:3:[]), ()) , ((11:|2:33:[]), ()) ]) ] ] , "Foldable" ~: TestList [ "accumLeftsAndFoldrRights" ~: TestList [ "Left" ~: (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $ [Left [0]]) ~?= (([(0::Integer)], [(""::String)])) , "repeat Left" ~: ((take 1 *** take 0) $ Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $ ( repeat (Left [0]) )) ~?= ([(0::Integer)], ([]::[String])) , "Right:Left:Right:Left" ~: (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $ ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] )) ~?= (([1, 0]::[Integer]), (["2", "1", "0"]::[String])) , "Right:Left:Right:repeat Left" ~: ((take 1 *** take 2) $ Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $ ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) )) ~?= (([1]::[Integer]), (["2", "1"]::[String])) ] ] , "Interval" ~: TestList [ "position" ~: TestList $ concatMap (\(mi, mj, p) -> let i = fromJust mi in let j = fromJust mj in let (le, ge) = case p of Lib.Interval.Equal -> (EQ, EQ) _ -> (LT, GT) in [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.position i j ~?= (p, le) , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.position j i ~?= (p, ge) ] ) [ ( (Lib.Interval.<..<) 0 (4::Integer) , (Lib.Interval.<..<) 5 9 , Lib.Interval.Away ) , ( (Lib.Interval.<..<) 0 4 , (Lib.Interval.<=..<) 4 9 , Lib.Interval.Adjacent ) , ( (Lib.Interval.<..<) 0 5 , (Lib.Interval.<..<) 4 9 , Lib.Interval.Overlap ) , ( (Lib.Interval.<..<) 0 5 , (Lib.Interval.<..<) 0 9 , Lib.Interval.Prefix ) , ( (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 1 8 , Lib.Interval.Include ) , ( (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 5 9 , Lib.Interval.Suffixed ) , ( (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 0 9 , Lib.Interval.Equal ) , ( (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<=) 0 9 , Lib.Interval.Prefix ) , ( (Lib.Interval.<=..<) 0 9 , (Lib.Interval.<..<) 0 9 , Lib.Interval.Suffixed ) , ( (Lib.Interval.<=..<=) 0 9 , (Lib.Interval.<..<) 0 9 , Lib.Interval.Include ) ] , "intersection" ~: TestList $ concatMap (\(mi, mj, e) -> let i = fromJust mi in let j = fromJust mj in [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.intersection i j ~?= e , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.intersection j i ~?= e ] ) [ ( (Lib.Interval.<..<) 0 (4::Integer) , (Lib.Interval.<..<) 5 9 , Nothing ) , ( (Lib.Interval.<..<=) 0 5 , (Lib.Interval.<=..<) 5 9 , (Lib.Interval.<=..<=) 5 5 ) , ( (Lib.Interval.<..<) 0 6 , (Lib.Interval.<..<) 4 9 , (Lib.Interval.<..<) 4 6 ) , ( (Lib.Interval.<..<=) 0 6 , (Lib.Interval.<=..<) 4 9 , (Lib.Interval.<=..<=) 4 6 ) , ( (Lib.Interval.<..<) 0 6 , (Lib.Interval.<=..<) 4 9 , (Lib.Interval.<=..<) 4 6 ) , ( (Lib.Interval.<..<=) 0 6 , (Lib.Interval.<..<) 4 9 , (Lib.Interval.<..<=) 4 6 ) , ( (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<=..<) 0 9 , (Lib.Interval.<..<=) 0 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<..<=) 0 9 , (Lib.Interval.<=..<) 0 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<=..<=) 0 9 , (Lib.Interval.<=..<=) 0 9 , (Lib.Interval.<=..<=) 0 9 ) ] , "union" ~: TestList $ concatMap (\(mi, mj, e) -> let i = fromJust mi in let j = fromJust mj in [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.union i j ~?= e , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.union j i ~?= e ] ) [ ( (Lib.Interval.<..<) 0 (4::Integer) , (Lib.Interval.<..<) 5 9 , Nothing ) , ( (Lib.Interval.<..<=) 0 5 , (Lib.Interval.<..<) 5 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<..<) 0 5 , (Lib.Interval.<=..<) 5 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<..<=) 0 5 , (Lib.Interval.<=..<) 5 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<..<) 0 6 , (Lib.Interval.<..<) 4 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 0 9 , (Lib.Interval.<..<) 0 9 ) , ( (Lib.Interval.<=..<) 0 9 , (Lib.Interval.<..<=) 0 9 , (Lib.Interval.<=..<=) 0 9 ) , ( (Lib.Interval.<..<=) 0 9 , (Lib.Interval.<=..<) 0 9 , (Lib.Interval.<=..<=) 0 9 ) , ( (Lib.Interval.<=..<=) 0 9 , (Lib.Interval.<=..<=) 0 9 , (Lib.Interval.<=..<=) 0 9 ) ] , "Sieve" ~: TestList $ [ "union" ~: TestList $ Data.List.concatMap (\(mis, me) -> let is = map (fromJust) mis in let e = map (fromJust) me in let sil = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty is in let sir = foldr (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton) Lib.Interval.Sieve.empty is in [ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ~: Lib.Interval.Sieve.intervals sil ~?= e , (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ reverse is) ~: Lib.Interval.Sieve.intervals sir ~?= e ] ) [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) , (Lib.Interval.<=..<=) 5 9 ] , [ (Lib.Interval.<=..<=) 0 9 ] ) , ( [ (Lib.Interval.<=..<=) 0 5 , (Lib.Interval.<=..<=) 0 9 ] , [ (Lib.Interval.<=..<=) 0 9 ] ) , ( [ (Lib.Interval.<=..<=) 0 4 , (Lib.Interval.<=..<=) 5 9 , (Lib.Interval.<=..<=) 3 6 ] , [ (Lib.Interval.<=..<=) 0 9 ] ) , ( [ (Lib.Interval.<=..<=) 1 4 , (Lib.Interval.<=..<=) 5 8 ] , [ (Lib.Interval.<=..<=) 1 4 , (Lib.Interval.<=..<=) 5 8 ] ) , ( [ (Lib.Interval.<=..<=) 1 8 , (Lib.Interval.<=..<=) 0 9 ] , [ (Lib.Interval.<=..<=) 0 9 ] ) , ( [ (Lib.Interval.<=..<=) 1 4 , (Lib.Interval.<=..<=) 5 8 , (Lib.Interval.<=..<=) 0 9 ] , [ (Lib.Interval.<=..<=) 0 9 ] ) ] ++ Data.List.concatMap (\(mis, mjs, me) -> let is = map fromJust mis in let js = map fromJust mjs in let e = map fromJust me in let iu = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty is in let ju = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty js in [ ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " u " ++ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~: Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union iu ju) ~?= e , ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " u " ++ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~: Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union ju iu) ~?= e ] ) [ ( [ (Lib.Interval.<=..<=) 0 (1::Integer) , (Lib.Interval.<=..<=) 2 4 ] , [ (Lib.Interval.<=..<=) 0 3 ] , [ (Lib.Interval.<=..<=) 0 4 ] ) , ( [ (Lib.Interval.<=..<=) 0 1 , (Lib.Interval.<=..<=) 2 3 , (Lib.Interval.<=..<=) 4 5 , (Lib.Interval.<=..<=) 6 7 ] , [ (Lib.Interval.<=..<=) 1 2 , (Lib.Interval.<=..<=) 3 4 , (Lib.Interval.<=..<=) 5 6 ] , [ (Lib.Interval.<=..<=) 0 7 ] ) , ( [ (Lib.Interval.<=..<=) 0 1 , (Lib.Interval.<=..<=) 2 3 ] , [ (Lib.Interval.<=..<=) 4 5 ] , [ (Lib.Interval.<=..<=) 0 1 , (Lib.Interval.<=..<=) 2 3 , (Lib.Interval.<=..<=) 4 5 ] ) , ( [ (Lib.Interval.<=..<=) 0 1 , (Lib.Interval.<=..<=) 4 5 ] , [ (Lib.Interval.<=..<=) 2 3 ] , [ (Lib.Interval.<=..<=) 0 1 , (Lib.Interval.<=..<=) 2 3 , (Lib.Interval.<=..<=) 4 5 ] ) ] , "intersection" ~: TestList $ Data.List.concatMap (\(mis, mjs, me) -> let is = map (fromJust) mis in let js = map (fromJust) mjs in let e = map (fromJust) me in let iu = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty is in let ju = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty js in [ ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " n " ++ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~: Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection iu ju) ~?= e , ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " n " ++ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~: Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection ju iu) ~?= e ] ) [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) ] , [ (Lib.Interval.<=..<=) 5 9 ] , [ ] ) , ( [ (Lib.Interval.<=..<=) 0 5 ] , [ (Lib.Interval.<=..<=) 5 9 ] , [ (Lib.Interval.<=..<=) 5 5 ] ) , ( [ (Lib.Interval.<=..<=) 0 5 ] , [ (Lib.Interval.<=..<=) 0 9 ] , [ (Lib.Interval.<=..<=) 0 5 ] ) , ( [ (Lib.Interval.<=..<=) 0 4 , (Lib.Interval.<=..<=) 5 9 ] , [ (Lib.Interval.<=..<=) 3 6 ] , [ (Lib.Interval.<=..<=) 3 4 , (Lib.Interval.<=..<=) 5 6 ] ) , ( [ (Lib.Interval.<=..<=) 1 4 , (Lib.Interval.<=..<=) 6 8 ] , [ (Lib.Interval.<=..<=) 2 3 , (Lib.Interval.<=..<=) 5 7 ] , [ (Lib.Interval.<=..<=) 2 3 , (Lib.Interval.<=..<=) 6 7 ] ) ] , "complement" ~: TestList $ Data.List.concatMap (\(mis, me) -> let is = map fromJust mis in let e = map fromJust me in let iu = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty is in [ show (Lib.Interval.Pretty $ Lib.Interval.Sieve.fmap_interval (Lib.Interval.fmap_unsafe $ Lib.Interval.Pretty) iu) ~: Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement iu) ~?= e ] ) [ ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 (5::Integer) , ((Lib.Interval.<=..<=) `on` Lib.Interval.Limited) 5 9 ] , [ Just $ (Lib.Interval...<) 0 , Just $ (Lib.Interval.<..) 9 ] ) , ( [ Just $ Lib.Interval.unlimited ] , [ ] ) , ( [ ] , [ Just $ Lib.Interval.unlimited ] ) , ( [ Just $ (Lib.Interval...<) 0 , Just $ (Lib.Interval.<..) 0 ] , [ Just $ Lib.Interval.point $ Lib.Interval.Limited 0 ] ) , ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 1 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 2 3 , ((Lib.Interval.<..<=) `on` Lib.Interval.Limited) 3 4 ] , [ Just $ (Lib.Interval...<) 0 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 1 2 , Just $ Lib.Interval.point $ Lib.Interval.Limited 3 , Just $ (Lib.Interval.<..) 4 ] ) ] , "complement_with" ~: TestList $ Data.List.concatMap (\(mib, mis, me) -> let ib = fromJust mib in let is = map fromJust mis in let e = map fromJust me in let iu = foldl (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)) Lib.Interval.Sieve.empty is in [ show (Lib.Interval.Pretty iu) ~: Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement_with ib iu) ~?= e ] ) [ ( (Lib.Interval.<=..<=) (-10) (10::Integer) , [ (Lib.Interval.<=..<) 0 5 , (Lib.Interval.<=..<=) 5 9 ] , [ (Lib.Interval.<=..<) (-10) 0 , (Lib.Interval.<..<=) 9 10 ] ) , ( (Lib.Interval.<=..<=) (-10) 10 , [ (Lib.Interval.<=..<=) (-10) 10 ] , [ ] ) , ( (Lib.Interval.<=..<=) (-10) 10 , [ ] , [ (Lib.Interval.<=..<=) (-10) 10 ] ) , ( (Lib.Interval.<=..<=) (-10) 10 , [ (Lib.Interval.<=..<) (-10) 0 , (Lib.Interval.<..<=) 0 10 ] , [ Just $ Lib.Interval.point 0 ] ) , ( (Lib.Interval.<=..<=) (-10) 10 , [ Just $ Lib.Interval.point 0 ] , [ (Lib.Interval.<=..<) (-10) 0 , (Lib.Interval.<..<=) 0 10 ] ) , ( (Lib.Interval.<=..<=) 0 10 , [ (Lib.Interval.<..<=) 0 10 ] , [ Just $ Lib.Interval.point 0 ] ) , ( (Lib.Interval.<=..<=) 0 10 , [ (Lib.Interval.<=..<) 0 10 ] , [ Just $ Lib.Interval.point 10 ] ) , ( Just $ Lib.Interval.point 0 , [ ] , [ Just $ Lib.Interval.point 0 ] ) , ( Just $ Lib.Interval.point 0 , [ Just $ Lib.Interval.point 0 ] , [ ] ) ] ] ] ] , "Account" ~: TestList [ "foldr" ~: TestList [ "[A]" ~: (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]] , "[A, B]" ~: (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]] , "[A, B, C]" ~: (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]] ] , "ascending" ~: TestList [ "[A]" ~: Account.ascending ("A":|[]) ~?= Nothing , "[A, B]" ~: Account.ascending ("A":|["B"]) ~?= Just ("A":|[]) , "[A, B, C]" ~: Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"]) ] , "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)"]] ] ] ] , "Amount" ~: TestList [ "+" ~: TestList [ "$1 + 1$ = $2" ~: (+) (Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just $ Amount.Style.Side_Left } , Amount.unit = "$" }) (Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just $ Amount.Style.Side_Right } , Amount.unit = "$" }) ~?= (Amount.nil { Amount.quantity = Decimal 0 2 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just $ Amount.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 = Amount.Style.nil { Amount.Style.unit_side = Just $ Amount.Style.Side_Left } , Amount.unit = "$" } , Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just $ Amount.Style.Side_Right } , Amount.unit = "$" } ] ~?= Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = Decimal 0 2 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just $ Amount.Style.Side_Left } , 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.nil { Amount.quantity = Decimal 0 0 }] , "\"00\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 }] , "\"0.\" = Right 0." ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0."::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' } }] , "\".0\" = Right 0.0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" (".0"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 1 } }] , "\"0,\" = Right 0," ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0,"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' } }] , "\",0\" = Right 0,0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" (",0"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.precision = 1 } }] , "\"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.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 1 } }] , "\"00.00\" = Right 0.00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00.00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 2 } }] , "\"0,0\" = Right 0,0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0,0"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.precision = 1 } }] , "\"00,00\" = Right 0,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00,00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.precision = 2 } }] , "\"0_0\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0_0"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1] , Amount.Style.precision = 0 } }] , "\"00_00\" = Right 0" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("00_00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2] , Amount.Style.precision = 0 } }] , "\"0,000.00\" = Right 0,000.00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("0,000.00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] , Amount.Style.precision = 2 } }] , "\"0.000,00\" = Right 0.000,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("0.000,00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 0 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] , Amount.Style.precision = 2 } }] , "\"1,000.00\" = Right 1,000.00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1,000.00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] , Amount.Style.precision = 2 } }] , "\"1.000,00\" = Right 1.000,00" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount) () "" ("1.000,00"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] , Amount.Style.precision = 2 } }] , "\"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.nil { Amount.quantity = Decimal 0 123 }] , "\"1.2\" = Right 1.2" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1.2"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 1 12 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 1 } }] , "\"1,2\" = Right 1,2" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1,2"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 1 12 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.precision = 1 } }] , "\"12.23\" = Right 12.23" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("12.34"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 2 1234 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 2 } }] , "\"12,23\" = Right 12,23" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("12,34"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 2 1234 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.precision = 2 } }] , "\"1_2\" = Right 1_2" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_2"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 12 , Amount.style = Amount.Style.nil { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1] , Amount.Style.precision = 0 } }] , "\"1_23\" = Right 1_23" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_23"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 123 , Amount.style = Amount.Style.nil { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2] , Amount.Style.precision = 0 } }] , "\"1_23_456\" = Right 1_23_456" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1_23_456"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 123456 , Amount.style = Amount.Style.nil { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2] , Amount.Style.precision = 0 } }] , "\"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.nil { Amount.quantity = Decimal 15 123456789012345678901 , Amount.style = Amount.Style.nil { 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.Style.precision = 15 } }] , "\"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.nil { Amount.quantity = Decimal 6 123456789012345678901 , Amount.style = Amount.Style.nil { 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.Style.precision = 6 } }] , "\"$1\" = Right $1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("$1"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"1$\" = Right 1$" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1$"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"$ 1\" = Right $ 1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("$ 1"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just True } , Amount.unit = "$" }] , "\"1 $\" = Right 1 $" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1 $"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just True } , Amount.unit = "$" }] , "\"-$1\" = Right $-1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("-$1"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 (-1) , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("\"4 2\"1"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , 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.nil { Amount.quantity = Decimal 0 1 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Nothing , Amount.Style.grouping_integral = Nothing , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 0 , Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , 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.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 2 , Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }] , "\"1.000,00$\" = Right 1.000,00$" ~: (Data.Either.rights $ [P.runParser (Amount.Read.amount <* P.eof) () "" ("1.000,00$"::Text)]) ~?= [Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just ',' , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3] , Amount.Style.grouping_fractional = Nothing , Amount.Style.precision = 2 , Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }] ] ] , "Write" ~: TestList [ "amount" ~: TestList [ "nil" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil) ~?= "0") , "nil @ prec=2" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.style = Amount.Style.nil { Amount.Style.precision = 2 } }) ~?= "0.00") , "123" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 0 123 }) ~?= "123") , "-123" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 0 (- 123) }) ~?= "-123") , "12.3 @ prec=0" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 1 123 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' } }) ~?= "12") , "12.5 @ prec=0" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 1 125 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' } }) ~?= "13") , "12.3 @ prec=1" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 1 123 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 1 } }) ~?= "12.3") , "1,234.56 @ prec=2" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 2 123456 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 2 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] } }) ~?= "1,234.56") , "123,456,789,01,2.3456789 @ prec=7" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 7 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 7 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3] } }) ~?= "123,456,789,01,2.3456789") , "1234567.8,90,123,456,789 @ prec=12" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 12 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 12 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3] } }) ~?= "1234567.8,90,123,456,789") , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 7 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 7 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1] } }) ~?= "1,2,3,4,5,6,7,89,012.3456789") , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Amount.Write.amount Amount.nil { Amount.quantity = Decimal 12 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 12 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1] } }) ~?= "1234567.890,12,3,4,5,6,7,8,9") ] , "amount_length" ~: TestList [ "nil" ~: ((Amount.Write.amount_length Amount.nil) ~?= 1) , "nil @ prec=2" ~: ((Amount.Write.amount_length Amount.nil { Amount.style = Amount.Style.nil { Amount.Style.precision = 2 } }) ~?= 4) , "123" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 0 123 }) ~?= 3) , "-123" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 0 (- 123) }) ~?= 4) , "12.3 @ prec=0" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 1 123 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' } }) ~?= 2) , "12.5 @ prec=0" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 1 125 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' } }) ~?= 2) , "12.3 @ prec=1" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 1 123 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 1 } }) ~?= 4) , "1,234.56 @ prec=2" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 2 123456 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 2 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3] } }) ~?= 8) , "123,456,789,01,2.3456789 @ prec=7" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 7 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 7 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3] } }) ~?= 24) , "1234567.8,90,123,456,789 @ prec=12" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 12 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 12 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3] } }) ~?= 24) , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 7 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 7 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1] } }) ~?= 28) , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 12 1234567890123456789 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 12 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1] } }) ~?= 28) , "1000000.000,00,0,0,0,0,0,0,0 @ prec=12" ~: ((Amount.Write.amount_length Amount.nil { Amount.quantity = Decimal 12 1000000000000000000 , Amount.style = Amount.Style.nil { Amount.Style.fractioning = Just '.' , Amount.Style.precision = 12 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1] } }) ~?= 28) , "999 @ prec=0" ~: ((Amount.Write.amount_length $ Amount.nil { Amount.quantity = Decimal 0 999 , Amount.style = Amount.Style.nil { Amount.Style.precision = 0 } }) ~?= 3) , "1000 @ prec=0" ~: ((Amount.Write.amount_length $ Amount.nil { Amount.quantity = Decimal 0 1000 , Amount.style = Amount.Style.nil { Amount.Style.precision = 0 } }) ~?= 4) , "10,00€ @ prec=2" ~: ((Amount.Write.amount_length $ Amount.eur 10) ~?= 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" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Date.Write.date Date.nil) ~?= "1970/01/01") , "2000/01/01_12:34:51CET" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ~: (Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.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" ] ] ] , "Filter" ~: TestList [ "test" ~: TestList [ "Filter_Account" ~: TestList [ "A A" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ]) (("A":|[]::Account)) , "* A" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Any ]) (("A":|[]::Account)) , ": A" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Many ]) (("A":|[]::Account)) , ":A A" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ]) (("A":|[]::Account)) , "A: A" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many ]) (("A":|[]::Account)) , "A: A:B" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many ]) (("A":|"B":[]::Account)) , "A:B A:B" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ]) (("A":|"B":[]::Account)) , "A::B A:B" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ]) (("A":|"B":[]::Account)) , ":B: A:B:C" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") , Filter.Filter_Account_Section_Many ]) (("A":|"B":"C":[]::Account)) , ":C A:B:C" ~? Filter.test (Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "C") ]) (("A":|"B":"C":[]::Account)) , "A:B:C::D A:B:C:CC:CCC:D:E" ~? Filter.test (Filter.Filter_Account Filter.Gt [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "C") , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "D") ]) (("A":|"B":"C":"CC":"CCC":"D":"E":[]::Account)) ] , "Filter_Bool" ~: TestList [ "Any A" ~? Filter.test (Filter.Any::Filter.Filter_Bool Filter.Filter_Account) (("A":|[]::Account)) ] , "Filter_Ord" ~: TestList [ "0 < (1, 2)" ~? Filter.test (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer)) (fromJust $ (Lib.Interval.<=..<=) 1 2) , "(-2, -1) < 0" ~? Filter.test (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer)) (fromJust $ (Lib.Interval.<=..<=) (-2) (-1)) , "not (1 < (0, 2))" ~? (not $ Filter.test (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer)) (fromJust $ (Lib.Interval.<=..<=) 0 2)) ] ] , "Read" ~: TestList [ "filter_account" ~: TestList [ "*" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("*"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Any ] ] , "A" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("A"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ] ] , "AA" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("AA"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "AA") ] ] , "::A" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("::A"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ] ] , ":A" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" (":A"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ] ] , "A:" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("A:"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many ] ] , "A::" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("A::"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Many ] ] , "A:B" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("A:B"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ] ] , "A::B" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("A::B"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ] ] , "A:::B" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("A:::B"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Many , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ] ] , "A: " ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.char ' ' <* P.eof) () "" ("A: "::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Eq [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Many ] ] , "<=A:B" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" ("<=A:B"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Le [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ] ] , ">=A:B" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" (">=A:B"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Ge [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ] ] , "A:B" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_account <* P.eof) () "" (">A:B"::Text)]) ~?= map (Filter.Filter_Posting_Type_Any,) [ Filter.Filter_Account Filter.Gt [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ] ] ] , "filter_bool" ~: TestList [ "( E )" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_bool [ P.char 'E' >> return (return $ Filter.Bool True) ] <* P.eof) () "" ("( E )"::Text)]) ~?= [ Filter.And (Filter.Bool True) Filter.Any ] , "( ( E ) )" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_bool [ P.char 'E' >> return (return $ Filter.Bool True) ] <* P.eof) () "" ("( ( E ) )"::Text)]) ~?= [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any ] , "( E ) & ( E )" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_bool [ P.char 'E' >> return (return $ Filter.Bool True) ] <* P.eof) () "" ("( E ) & ( E )"::Text)]) ~?= [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) (Filter.And (Filter.Bool True) Filter.Any) ] , "( E ) + ( E )" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_bool [ P.char 'E' >> return (return $ Filter.Bool True) ] <* P.eof) () "" ("( E ) + ( E )"::Text)]) ~?= [ Filter.Or (Filter.And (Filter.Bool True) Filter.Any) (Filter.And (Filter.Bool True) Filter.Any) ] , "( E ) - ( E )" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_bool [ P.char 'E' >> return (return $ Filter.Bool True) ] <* P.eof) () "" ("( E ) - ( E )"::Text)]) ~?= [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) (Filter.Not (Filter.And (Filter.Bool True) Filter.Any)) ] , "(- E )" ~: (Data.Either.rights $ [P.runParser (Filter.Read.filter_bool [ P.char 'E' >> return (return $ Filter.Bool True) ] <* P.eof) () "" ("(- E )"::Text)]) ~?= [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any ] ] ] ] , "Balance" ~: TestList [ "balance" ~: TestList [ "[A+$1] = A+$1 & $+1" ~: (Balance.cons (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } Balance.empty) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "[A+$1, A-$1] = {A+$0, $+0}" ~: (Data.List.foldl (flip Balance.cons) Balance.empty [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] } ]) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ [ ( "A":|[] , Balance.Account_Sum $ Data.Map.fromListWith const $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s)) [ Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1) ] ) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~: (Data.List.foldl (flip Balance.cons) Balance.empty [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] } ]) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Positive (Amount.usd $ 1) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Negative (Amount.eur $ -1) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~: (Data.List.foldl (flip Balance.cons) Balance.empty [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] } ]) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.usd $ -1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } ] } , "[A+$1, B+$1]" ~: (Data.List.foldl (flip Balance.cons) Balance.empty [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } ]) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } ] } , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~: (Data.List.foldl (flip Balance.cons) Balance.empty [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ] } , (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ] } ]) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ [ ("A":|[] , Balance.Account_Sum $ Data.Map.fromListWith const $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s)) [ Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1) , Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2) ] ) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2) , Balance.unit_sum_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 Balance.cons) Balance.empty [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ] } ]) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("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 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.Sum_Both (Amount.gbp $ -3) (Amount.gbp $ 3) , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } ] } ] , "union" ~: TestList [ "empty empty = empty" ~: Balance.union Balance.empty Balance.empty ~?= (Balance.empty::Balance.Balance Amount) , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~: Balance.union (Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] }) (Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] }) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~: Balance.union (Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] }) (Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["B":|[]] } ] }) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } ] } , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~: Balance.union (Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] }) (Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["B":|[]] } ] }) ~?= Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["B":|[]] } ] } ] , "expanded" ~: TestList [ "mempty" ~: Balance.expanded Lib.TreeMap.empty ~?= (Lib.TreeMap.empty::Balance.Expanded Amount) , "A+$1 = A+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const $ [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) , "A/A+$1 = A+$1 A/A+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [] }) , ("A":|["A"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) , "A/B+$1 = A+$1 A/B+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [] }) , ("A":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const $ [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [] }) , ("A":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [] }) , ("A":|["B", "C"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) , "A+$1 A/B+$1 = A+$2 A/B+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 2 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 3 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 2 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B", "C"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ 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" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("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 ]) ]) ~?= (Lib.TreeMap.from_List const [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 4 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 3 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B", "C"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 2 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B", "C", "D"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~: Balance.expanded (Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ]) , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ]) ~?= (Lib.TreeMap.from_List const [ ("A":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 3 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("A":|["BB"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) , ("AA":|[], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [] }) , ("AA":|["B"], Balance.Account_Sum_Expanded { Balance.inclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] , Balance.exclusive = Balance.Account_Sum $ Data.Map.map Amount.sum $ Amount.from_List [ Amount.usd $ 1 ] }) ]) ] , "deviation" ~: TestList [ "{A+$1, $1}" ~: (Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List []) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] }) ~?= (Balance.Deviation $ Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["B":|[]] } ]) , "{A+$1 B+$1, $2}" ~: (Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) [ "A":|[] , "B":|[] ] } ] }) ~?= (Balance.Deviation $ Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) [ ] } ]) ] , "is_equilibrium_inferrable" ~: TestList [ "nil" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ (Balance.empty::Balance.Balance Amount.Amount) , "{A+$0, $+0}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "{A+$1, $+1}" ~: TestCase $ (@=?) False $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "{A+$0+€0, $0 €+0}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "{A+$1, B-$1, $+0}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.usd $ -1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } ] } , "{A+$1 B, $+1}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List []) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } ] } , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["B":|[]] } ] } , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["B":|[]] } ] } , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $ (@=?) True $ Balance.is_equilibrium_inferrable $ Balance.deviation $ Balance.Balance { Balance.balance_by_account = Lib.TreeMap.from_List const $ Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $ [ ("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 ]) ] , Balance.balance_by_unit = Balance.Balance_by_Unit $ Data.Map.fromList $ Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s)) [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } , Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.gbp $ 0 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,()) ["A":|[], "B":|[]] } ] } ] , "infer_equilibrium" ~: TestList [ "{A+$1 B}" ~: (snd $ Balance.infer_equilibrium $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [] } ]) ~?= (Right $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] } ]) , "{A+$1 B-1€}" ~: (snd $ Balance.infer_equilibrium $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] } ]) ~?= (Right $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1, Amount.usd $ -1 ] } ]) , "{A+$1 B+$1}" ~: (snd $ Balance.infer_equilibrium $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } ]) ~?= (Left [ Balance.Unit_Sum { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2 , Balance.unit_sum_accounts = Data.Map.fromList []} ]) , "{A+$1 B-$1 B-1€}" ~: (snd $ Balance.infer_equilibrium $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] } ]) ~?= (Right $ Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1 ] } , (Format.Ledger.posting ("B":|[])) { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] } ]) ] ] , "Format" ~: TestList [ "Ledger" ~: TestList [ "Read" ~: TestList [ "posting_type" ~: TestList [ "A" ~: Format.Ledger.Read.posting_type ("A":|[]) ~?= (Posting.Posting_Type_Regular, "A":|[]) , "(" ~: Format.Ledger.Read.posting_type ("(":|[]) ~?= (Posting.Posting_Type_Regular, "(":|[]) , ")" ~: Format.Ledger.Read.posting_type (")":|[]) ~?= (Posting.Posting_Type_Regular, ")":|[]) , "()" ~: Format.Ledger.Read.posting_type ("()":|[]) ~?= (Posting.Posting_Type_Regular, "()":|[]) , "( )" ~: Format.Ledger.Read.posting_type ("( )":|[]) ~?= (Posting.Posting_Type_Regular, "( )":|[]) , "(A)" ~: Format.Ledger.Read.posting_type ("(A)":|[]) ~?= (Posting.Posting_Type_Virtual, "A":|[]) , "(A:B:C)" ~: Format.Ledger.Read.posting_type ("(A":|["B", "C)"]) ~?= (Posting.Posting_Type_Virtual, "A":|["B", "C"]) , "A:B:C" ~: Format.Ledger.Read.posting_type ("A":|["B", "C"]) ~?= (Posting.Posting_Type_Regular, "A":|["B", "C"]) , "(A):B:C" ~: Format.Ledger.Read.posting_type ("(A)":|["B", "C"]) ~?= (Posting.Posting_Type_Regular, "(A)":|["B", "C"]) , "A:(B):C" ~: Format.Ledger.Read.posting_type ("A":|["(B)", "C"]) ~?= (Posting.Posting_Type_Regular, "A":|["(B)", "C"]) , "A:B:(C)" ~: Format.Ledger.Read.posting_type ("A":|["B", "(C)"]) ~?= (Posting.Posting_Type_Regular, "A":|["B", "(C)"]) , "[" ~: Format.Ledger.Read.posting_type ("[":|[]) ~?= (Posting.Posting_Type_Regular, "[":|[]) , "]" ~: Format.Ledger.Read.posting_type ("]":|[]) ~?= (Posting.Posting_Type_Regular, "]":|[]) , "[]" ~: Format.Ledger.Read.posting_type ("[]":|[]) ~?= (Posting.Posting_Type_Regular, "[]":|[]) , "[ ]" ~: Format.Ledger.Read.posting_type ("[ ]":|[]) ~?= (Posting.Posting_Type_Regular, "[ ]":|[]) , "[A]" ~: Format.Ledger.Read.posting_type ("[A]":|[]) ~?= (Posting.Posting_Type_Virtual_Balanced, "A":|[]) , "[A:B:C]" ~: Format.Ledger.Read.posting_type ("[A":|["B", "C]"]) ~?= (Posting.Posting_Type_Virtual_Balanced, "A":|["B", "C"]) , "A:B:C" ~: Format.Ledger.Read.posting_type ("A":|["B", "C"]) ~?= (Posting.Posting_Type_Regular, "A":|["B", "C"]) , "[A]:B:C" ~: Format.Ledger.Read.posting_type ("[A]":|["B", "C"]) ~?= (Posting.Posting_Type_Regular, "[A]":|["B", "C"]) , "A:[B]:C" ~: Format.Ledger.Read.posting_type ("A":|["[B]", "C"]) ~?= (Posting.Posting_Type_Regular, "A":|["[B]", "C"]) , "A:B:[C]" ~: Format.Ledger.Read.posting_type ("A":|["B", "[C]"]) ~?= (Posting.Posting_Type_Regular, "A":|["B", "[C]"]) ] , "comment" ~: TestList [ "; some comment = Right \" some comment\"" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.comment <* P.eof) () "" ("; some comment"::Text)]) ~?= [ " some comment" ] , "; some comment \\n = Right \" some comment \"" ~: (Data.Either.rights $ [P.runParser (Format.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 (Format.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 (Format.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 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof) () "" ("; some comment \n"::Text)]) ~?= [ [" some comment "] ] ] , "tag_value" ~: TestList [ "," ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag_value <* P.eof) () "" (","::Text)]) ~?= [","] , ",\\n" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof) () "" (",\n"::Text)]) ~?= [","] , ",x" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag_value <* P.eof) () "" (",x"::Text)]) ~?= [",x"] , ",x:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof) () "" (",x:"::Text)]) ~?= [""] , "v, v, n:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof) () "" ("v, v, n:"::Text)]) ~?= ["v, v"] ] , "tag" ~: TestList [ "Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" ("Name:"::Text)]) ~?= [("Name", "")] , "Name:Value" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" ("Name:Value"::Text)]) ~?= [("Name", "Value")] , "Name:Value\\n" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.string "\n" <* P.eof) () "" ("Name:Value\n"::Text)]) ~?= [("Name", "Value")] , "Name:Val ue" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" ("Name:Val ue"::Text)]) ~?= [("Name", "Val ue")] , "Name:," ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" ("Name:,"::Text)]) ~?= [("Name", ",")] , "Name:Val,ue" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.eof) () "" ("Name:Val,ue"::Text)]) ~?= [("Name", "Val,ue")] , "Name:Val,ue:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof) () "" ("Name:Val,ue:"::Text)]) ~?= [("Name", "Val")] ] , "tags" ~: TestList [ "Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" ("Name:"::Text)]) ~?= [Data.Map.fromList [ ("Name", [""]) ] ] , "Name:," ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" ("Name:,"::Text)]) ~?= [Data.Map.fromList [ ("Name", [","]) ] ] , "Name:,Name:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" ("Name:,Name:"::Text)]) ~?= [Data.Map.fromList [ ("Name", ["", ""]) ] ] , "Name:,Name2:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" ("Name:,Name2:"::Text)]) ~?= [Data.Map.fromList [ ("Name", [""]) , ("Name2", [""]) ] ] , "Name: , Name2:" ~: (Data.Either.rights $ [P.runParser (Format.Ledger.Read.tags <* P.eof) () "" ("Name: , Name2:"::Text)]) ~?= [Data.Map.fromList [ ("Name", [" "]) , ("Name2", [""]) ] ] , "Name:,Name2:,Name3:" ~: (Data.Either.rights $ [P.runParser (Format.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 (Format.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 (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C"::Text)]) ~?= [ ( (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } , Posting.Posting_Type_Regular ) ] , " !A:B:C = Right !A:B:C" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" !A:B:C"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.posting_status = True } ] , " *A:B:C = Right *A:B:C" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" *A:B:C"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [] , Format.Ledger.posting_comments = [] , Format.Ledger.posting_dates = [] , Format.Ledger.posting_status = True , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.posting_tags = Data.Map.fromList [] } ] , " A:B:C $1 = Right A:B:C $1" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C $1"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B","C $1"])) { Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 = Right A:B:C $1" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C $1"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C $1 + 1€"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) , ("€", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Right , Amount.Style.unit_spaced = Just False } , Amount.unit = "€" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1$ = Right A:B:C $2" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C $1 + 1$"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 2 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C $1 + 1$ + 1$"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 3 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; some comment = Right A:B:C ; some comment" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; some comment"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [] , Format.Ledger.posting_comments = [" some comment"] , Format.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 fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; some comment\n ; some other comment"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [] , Format.Ledger.posting_comments = [" some comment", " some other comment"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C $1 ; some comment"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_comments = [" some comment"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } ] , " A:B:C ; N:V = Right A:B:C ; N:V" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; N:V"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_comments = [" N:V"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.posting_tags = Data.Map.fromList [ ("N", ["V"]) ] } ] , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~: (Data.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; some comment N:V"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_comments = [" some comment N:V"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.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.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting ) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.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.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; N:V\n ; N:V2"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_comments = [" N:V", " N:V2"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.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.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; N:V\n ; N2:V"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_comments = [" N:V", " N2:V"] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.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.List.map fst $ Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" A:B:C ; date:2001/01/01"::Text)]) ~?= [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_comments = [" date:2001/01/01"] , Format.Ledger.posting_dates = [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2001 01 01) (Time.TimeOfDay 0 0 0)) Time.utc ] , Format.Ledger.posting_sourcepos = P.newPos "" 1 1 , Format.Ledger.posting_tags = Data.Map.fromList [ ("date", ["2001/01/01"]) ] } ] , " (A:B:C) = Right (A:B:C)" ~: (Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" (A:B:C)"::Text)]) ~?= [ ( (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } , Posting.Posting_Type_Virtual ) ] , " [A:B:C] = Right [A:B:C]" ~: (Data.Either.rights $ [P.runParser_with_Error (Format.Ledger.Read.posting <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" (" [A:B:C]"::Text)]) ~?= [ ( (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_sourcepos = P.newPos "" 1 1 } , Posting.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_with_Error (Format.Ledger.Read.transaction <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)]) ~?= [ Format.Ledger.transaction { Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="some description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 2 1 } , (Format.Ledger.posting ("a":|["b", "c"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = -1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 3 1 } ] , Format.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 (Format.Ledger.Read.transaction <* P.newline <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction) "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)]) ~?= [ Format.Ledger.transaction { Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="some description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 2 1 } , (Format.Ledger.posting ("a":|["b", "c"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = -1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 3 1 } ] , Format.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 (Format.Ledger.Read.transaction <* P.eof) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.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)]) ~?= [ Format.Ledger.transaction { Format.Ledger.transaction_comments_after = [ " some comment" , " some other;comment" , " some Tag:" , " some last comment" ] , Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="some description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 5 1 } , (Format.Ledger.posting ("a":|["b", "c"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = -1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 6 1 } ] , Format.Ledger.transaction_tags = Data.Map.fromList [ ("Tag", [""]) ] , Format.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 (Format.Ledger.Read.journal "" {-<* P.eof-}) ( Format.Ledger.Read.context () Format.Ledger.journal ::Format.Ledger.Read.Context () [] Format.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{Format.Ledger.journal_last_read_time=Date.nil}) $ Data.Either.rights [jnl]) @?= [ Format.Ledger.journal { Format.Ledger.journal_transactions = [ Format.Ledger.transaction { Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 02) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="2° description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 5 1 } , (Format.Ledger.posting ("x":|["y", "z"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = -1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 6 1 } ] , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1 } , Format.Ledger.transaction { Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="1° description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 2 1 } , (Format.Ledger.posting ("a":|["b", "c"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = -1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] , Format.Ledger.posting_sourcepos = P.newPos "" 3 1 } ] , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1 } ] } ] ] ] , "Write" ~: TestList [ "account" ~: TestList [ "A" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.account Posting.Posting_Type_Regular $ "A":|[]) ~?= "A") , "A:B:C" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.account Posting.Posting_Type_Regular $ "A":|["B", "C"]) ~?= "A:B:C") , "(A:B:C)" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.account Posting.Posting_Type_Virtual $ "A":|["B", "C"]) ~?= "(A:B:C)") , "[A:B:C]" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.account Posting.Posting_Type_Virtual_Balanced $ "A":|["B", "C"]) ~?= "[A:B:C]") ] , "transaction" ~: TestList [ "nil" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.transaction Format.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" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.transaction $ Format.Ledger.transaction { Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="some description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] } , (Format.Ledger.posting ("a":|["b", "c"])) { Format.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" ~: ((Format.Ledger.Write.show Format.Ledger.Write.Style { Format.Ledger.Write.style_color=False , Format.Ledger.Write.style_align=True } $ Format.Ledger.Write.transaction $ Format.Ledger.transaction { Format.Ledger.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , Format.Ledger.transaction_description="some description" , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account [ (Format.Ledger.posting ("A":|["B", "C"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 1 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] } , (Format.Ledger.posting ("AA":|["BB", "CC"])) { Format.Ledger.posting_amounts = Data.Map.fromList [ ("$", Amount.nil { Amount.quantity = 123 , Amount.style = Amount.Style.nil { Amount.Style.unit_side = Just Amount.Style.Side_Left , Amount.Style.unit_spaced = Just False } , Amount.unit = "$" }) ] } ] }) ~?= "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123\n") ] ] ] ] ]