1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE TupleSections #-}
5 import Test.HUnit hiding ((~?))
6 import Test.Framework.Providers.HUnit (hUnitTestToTests)
7 import Test.Framework.Runners.Console (defaultMain)
9 import Control.Applicative ((<*))
10 import Control.Arrow ((***))
11 import Control.Monad.IO.Class (liftIO)
12 import Data.Decimal (DecimalRaw(..))
13 import qualified Data.Either
14 import qualified Data.List
15 import Data.List.NonEmpty (NonEmpty(..))
16 import qualified Data.Map.Strict as Data.Map
17 import Data.Text (Text)
18 import qualified Data.Time.Calendar as Time
19 import qualified Data.Time.LocalTime as Time
20 import qualified Text.Parsec as P hiding (char, space, spaces, string)
21 import qualified Text.Parsec.Pos as P
22 -- import qualified Text.PrettyPrint.Leijen.Text as PP
24 import qualified Hcompta.Model.Account as Account
25 import Hcompta.Model.Account (Account)
26 import qualified Hcompta.Model.Amount as Amount
27 import Hcompta.Model.Amount (Amount)
28 import qualified Hcompta.Model.Amount.Style as Amount.Style
29 import qualified Hcompta.Model.Date as Date
30 import qualified Hcompta.Model.Date.Read as Date.Read
31 import qualified Hcompta.Model.Filter as Filter
32 import qualified Hcompta.Model.Filter.Read as Filter.Read
33 import qualified Hcompta.Calc.Balance as Calc.Balance
34 import qualified Hcompta.Format.Ledger as Format.Ledger
35 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
36 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
37 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
38 import qualified Hcompta.Lib.Parsec as P
39 import qualified Hcompta.Lib.Foldable as Lib.Foldable
42 main = defaultMain $ hUnitTestToTests test_Hcompta
44 (~?) :: String -> Bool -> Test
45 (~?) s b = s ~: (b ~?= True)
51 [ "TreeMap" ~: TestList
52 [ "insert" ~: TestList
54 (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty)
56 (Lib.TreeMap.TreeMap $
58 [ ((0::Int), Lib.TreeMap.leaf ())
61 (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty)
63 (Lib.TreeMap.TreeMap $
65 [ ((0::Int), Lib.TreeMap.Node
66 { Lib.TreeMap.node_value = Nothing
67 , Lib.TreeMap.node_size = 1
68 , Lib.TreeMap.node_descendants =
69 Lib.TreeMap.singleton ((1::Int):|[]) ()
76 , "map_by_depth_first" ~: TestList
79 , "flatten" ~: TestList
80 [ "[0, 0/1, 0/1/2]" ~:
81 (Lib.TreeMap.flatten id $
82 Lib.TreeMap.from_List const
83 [ (((0::Integer):|[]), ())
94 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
95 (Lib.TreeMap.flatten id $
96 Lib.TreeMap.from_List const
105 , ((11:|2:33:[]), ())
110 [ (((1::Integer):|[]), ())
118 , ((11:|2:33:[]), ())
122 , "Foldable" ~: TestList
123 [ "accumLeftsAndFoldrRights" ~: TestList
125 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
128 (([(0::Integer)], [(""::String)]))
130 ((take 1 *** take 0) $
131 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
132 ( repeat (Left [0]) ))
134 ([(0::Integer)], ([]::[String]))
135 , "Right:Left:Right:Left" ~:
136 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
137 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
139 (([1, 0]::[Integer]), (["2", "1", "0"]::[String]))
140 , "Right:Left:Right:repeat Left" ~:
141 ((take 1 *** take 2) $
142 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
143 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
145 (([1]::[Integer]), (["2", "1"]::[String]))
149 , "Model" ~: TestList
150 [ "Account" ~: TestList
151 [ "foldr" ~: TestList
153 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
155 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
157 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
159 , "ascending" ~: TestList
161 Account.ascending ("A":|[]) ~?= Nothing
163 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
165 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
168 , "Amount" ~: TestList
173 { Amount.quantity = Decimal 0 1
174 , Amount.style = Amount.Style.nil
175 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
180 { Amount.quantity = Decimal 0 1
181 , Amount.style = Amount.Style.nil
182 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
188 { Amount.quantity = Decimal 0 2
189 , Amount.style = Amount.Style.nil
190 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
195 , "from_List" ~: TestList
196 [ "from_List [$1, 1$] = $2" ~:
199 { Amount.quantity = Decimal 0 1
200 , Amount.style = Amount.Style.nil
201 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
206 { Amount.quantity = Decimal 0 1
207 , Amount.style = Amount.Style.nil
208 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
216 { Amount.quantity = Decimal 0 2
217 , Amount.style = Amount.Style.nil
218 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
225 , "Filter" ~: TestList
227 [ "Test_Account" ~: TestList
230 [ Filter.Test_Account_Section_Text
231 (Filter.Test_Text_Exact "A")
236 [ Filter.Test_Account_Section_Any
241 [ Filter.Test_Account_Section_Many
246 [ Filter.Test_Account_Section_Many
247 , Filter.Test_Account_Section_Text
248 (Filter.Test_Text_Exact "A")
253 [ Filter.Test_Account_Section_Text
254 (Filter.Test_Text_Exact "A")
255 , Filter.Test_Account_Section_Many
260 [ Filter.Test_Account_Section_Text
261 (Filter.Test_Text_Exact "A")
262 , Filter.Test_Account_Section_Many
264 (("A":|"B":[]::Account))
267 [ Filter.Test_Account_Section_Text
268 (Filter.Test_Text_Exact "A")
269 , Filter.Test_Account_Section_Text
270 (Filter.Test_Text_Exact "B")
272 (("A":|"B":[]::Account))
275 [ Filter.Test_Account_Section_Text
276 (Filter.Test_Text_Exact "A")
277 , Filter.Test_Account_Section_Many
278 , Filter.Test_Account_Section_Text
279 (Filter.Test_Text_Exact "B")
281 (("A":|"B":[]::Account))
284 [ Filter.Test_Account_Section_Many
285 , Filter.Test_Account_Section_Text
286 (Filter.Test_Text_Exact "B")
287 , Filter.Test_Account_Section_Many
289 (("A":|"B":"C":[]::Account))
292 [ Filter.Test_Account_Section_Many
293 , Filter.Test_Account_Section_Text
294 (Filter.Test_Text_Exact "C")
296 (("A":|"B":"C":[]::Account))
298 , "Test_Bool" ~: TestList
301 (Filter.Any::Filter.Test_Bool Filter.Test_Account)
306 [ "test_account_section" ~: TestList
308 (Data.Either.rights $
310 (Filter.Read.test_account <* P.eof)
313 [ [Filter.Test_Account_Section_Any]
316 (Data.Either.rights $
318 (Filter.Read.test_account <* P.eof)
321 [ [Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")]
324 (Data.Either.rights $
326 (Filter.Read.test_account <* P.eof)
329 [ [Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "AA")]
332 (Data.Either.rights $
334 (Filter.Read.test_account <* P.eof)
335 () "" ("::A"::Text)])
337 [ [ Filter.Test_Account_Section_Many
338 , Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
342 (Data.Either.rights $
344 (Filter.Read.test_account <* P.eof)
347 [ [ Filter.Test_Account_Section_Many
348 , Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
352 (Data.Either.rights $
354 (Filter.Read.test_account <* P.eof)
357 [ [ Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
358 , Filter.Test_Account_Section_Many
362 (Data.Either.rights $
364 (Filter.Read.test_account <* P.eof)
365 () "" ("A::"::Text)])
367 [ [ Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
368 , Filter.Test_Account_Section_Many
372 (Data.Either.rights $
374 (Filter.Read.test_account <* P.eof)
375 () "" ("A:B"::Text)])
377 [ [ Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
378 , Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "B") ]
381 (Data.Either.rights $
383 (Filter.Read.test_account <* P.eof)
384 () "" ("A::B"::Text)])
386 [ [ Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
387 , Filter.Test_Account_Section_Many
388 , Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "B")
392 (Data.Either.rights $
394 (Filter.Read.test_account <* P.eof)
395 () "" ("A:::B"::Text)])
397 [ [ Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
398 , Filter.Test_Account_Section_Many
399 , Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "B")
403 (Data.Either.rights $
405 (Filter.Read.test_account <* P.char ' ' <* P.eof)
406 () "" ("A: "::Text)])
408 [ [ Filter.Test_Account_Section_Text (Filter.Test_Text_Exact "A")
409 , Filter.Test_Account_Section_Many
413 , "test_bool" ~: TestList
415 (Data.Either.rights $
417 (Filter.Read.test_bool
418 [ P.char 'E' >> return (return True) ]
420 () "" ("( E )"::Text)])
422 [ Filter.And (Filter.Bool True) Filter.Any
425 (Data.Either.rights $
427 (Filter.Read.test_bool
428 [ P.char 'E' >> return (return True) ]
430 () "" ("( ( E ) )"::Text)])
432 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
435 (Data.Either.rights $
437 (Filter.Read.test_bool
438 [ P.char 'E' >> return (return True) ]
440 () "" ("( E ) & ( E )"::Text)])
443 (Filter.And (Filter.Bool True) Filter.Any)
444 (Filter.And (Filter.Bool True) Filter.Any)
451 [ "Balance" ~: TestList
452 [ "balance" ~: TestList
453 [ "[A+$1] = A+$1 & $+1" ~:
454 (Calc.Balance.balance
455 (Format.Ledger.posting ("A":|[]))
456 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
461 { Calc.Balance.balance_by_account =
462 Lib.TreeMap.from_List const $
463 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
464 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
465 , Calc.Balance.balance_by_unit =
467 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
468 [ Calc.Balance.Unit_Sum
469 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
470 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
475 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
477 (flip Calc.Balance.balance)
479 [ (Format.Ledger.posting ("A":|[]))
480 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
482 , (Format.Ledger.posting ("A":|[]))
483 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
488 { Calc.Balance.balance_by_account =
489 Lib.TreeMap.from_List const $
491 , Data.Map.fromListWith const $
492 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance s, s))
493 [ Calc.Balance.Amount_Sum
494 { Calc.Balance.amount_sum_negative = Just $ Amount.usd $ -1
495 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
496 , Calc.Balance.amount_sum_balance = Amount.usd $ 0
500 , Calc.Balance.balance_by_unit =
502 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
503 [ Calc.Balance.Unit_Sum
504 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
505 { Calc.Balance.amount_sum_negative = Just $ Amount.usd $ -1
506 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
507 , Calc.Balance.amount_sum_balance = Amount.usd $ 0
509 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
514 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
516 (flip Calc.Balance.balance)
518 [ (Format.Ledger.posting ("A":|[]))
519 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
521 , (Format.Ledger.posting ("A":|[]))
522 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ]
527 { Calc.Balance.balance_by_account =
528 Lib.TreeMap.from_List const $
529 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
530 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
531 , Calc.Balance.balance_by_unit =
533 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
534 [ Calc.Balance.Unit_Sum
535 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
536 { Calc.Balance.amount_sum_negative = Nothing
537 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
538 , Calc.Balance.amount_sum_balance = Amount.usd $ 1
540 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
543 , Calc.Balance.Unit_Sum
544 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
545 { Calc.Balance.amount_sum_negative = Just $ Amount.eur $ -1
546 , Calc.Balance.amount_sum_positive = Nothing
547 , Calc.Balance.amount_sum_balance = Amount.eur $ -1
549 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
554 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
556 (flip Calc.Balance.balance)
558 [ (Format.Ledger.posting ("A":|[]))
559 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
561 , (Format.Ledger.posting ("B":|[]))
562 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
567 { Calc.Balance.balance_by_account =
568 Lib.TreeMap.from_List const $
569 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
570 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
571 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
573 , Calc.Balance.balance_by_unit =
575 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
576 [ Calc.Balance.Unit_Sum
577 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
578 { Calc.Balance.amount_sum_negative = Just $ Amount.usd $ -1
579 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
580 , Calc.Balance.amount_sum_balance = Amount.usd $ 0
582 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
589 (flip Calc.Balance.balance)
591 [ (Format.Ledger.posting ("A":|[]))
592 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
594 , (Format.Ledger.posting ("B":|[]))
595 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
600 { Calc.Balance.balance_by_account =
601 Lib.TreeMap.from_List const $
602 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
603 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
604 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
606 , Calc.Balance.balance_by_unit =
608 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
609 [ Calc.Balance.Unit_Sum
610 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 2
611 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
616 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
618 (flip Calc.Balance.balance)
620 [ (Format.Ledger.posting ("A":|[]))
621 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
623 , (Format.Ledger.posting ("A":|[]))
624 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
629 { Calc.Balance.balance_by_account =
630 Lib.TreeMap.from_List const $
632 , Data.Map.fromListWith const $
633 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance s, s))
634 [ Calc.Balance.Amount_Sum
635 { Calc.Balance.amount_sum_negative = Just $ Amount.usd $ -1
636 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
637 , Calc.Balance.amount_sum_balance = Amount.usd $ 0
639 , Calc.Balance.Amount_Sum
640 { Calc.Balance.amount_sum_negative = Just $ Amount.eur $ -2
641 , Calc.Balance.amount_sum_positive = Just $ Amount.eur $ 2
642 , Calc.Balance.amount_sum_balance = Amount.eur $ 0
647 , Calc.Balance.balance_by_unit =
649 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
650 [ Calc.Balance.Unit_Sum
651 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
652 { Calc.Balance.amount_sum_negative = Just $ Amount.usd $ -1
653 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
654 , Calc.Balance.amount_sum_balance = Amount.usd $ 0
656 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
659 , Calc.Balance.Unit_Sum
660 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
661 { Calc.Balance.amount_sum_negative = Just $ Amount.eur $ -2
662 , Calc.Balance.amount_sum_positive = Just $ Amount.eur $ 2
663 , Calc.Balance.amount_sum_balance = Amount.eur $ 0
665 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
670 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
672 (flip Calc.Balance.balance)
674 [ (Format.Ledger.posting ("A":|[]))
675 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
677 , (Format.Ledger.posting ("B":|[]))
678 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
683 { Calc.Balance.balance_by_account =
684 Lib.TreeMap.from_List const $
685 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
686 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
687 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
689 , Calc.Balance.balance_by_unit =
691 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
692 [ Calc.Balance.Unit_Sum
693 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
694 { Calc.Balance.amount_sum_negative = Just $ Amount.usd $ -1
695 , Calc.Balance.amount_sum_positive = Just $ Amount.usd $ 1
696 , Calc.Balance.amount_sum_balance = Amount.usd $ 0
698 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
701 , Calc.Balance.Unit_Sum
702 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
703 { Calc.Balance.amount_sum_negative = Just $ Amount.eur $ -2
704 , Calc.Balance.amount_sum_positive = Just $ Amount.eur $ 2
705 , Calc.Balance.amount_sum_balance = Amount.eur $ 0
707 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
710 , Calc.Balance.Unit_Sum
711 { Calc.Balance.unit_sum_amount = Calc.Balance.Amount_Sum
712 { Calc.Balance.amount_sum_negative = Just $ Amount.gbp $ -3
713 , Calc.Balance.amount_sum_positive = Just $ Amount.gbp $ 3
714 , Calc.Balance.amount_sum_balance = Amount.gbp $ 0
716 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
722 , "union" ~: TestList
724 Calc.Balance.union Calc.Balance.nil Calc.Balance.nil
726 (Calc.Balance.nil::Calc.Balance.Balance Amount)
727 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
729 (Calc.Balance.Balance
730 { Calc.Balance.balance_by_account =
731 Lib.TreeMap.from_List const $
732 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
733 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
734 , Calc.Balance.balance_by_unit =
736 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
737 [ Calc.Balance.Unit_Sum
738 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
739 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
744 (Calc.Balance.Balance
745 { Calc.Balance.balance_by_account =
746 Lib.TreeMap.from_List const $
747 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
748 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
749 , Calc.Balance.balance_by_unit =
751 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
752 [ Calc.Balance.Unit_Sum
753 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
754 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
761 { Calc.Balance.balance_by_account =
762 Lib.TreeMap.from_List const $
763 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
764 [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
765 , Calc.Balance.balance_by_unit =
767 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
768 [ Calc.Balance.Unit_Sum
769 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 2
770 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
775 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
777 (Calc.Balance.Balance
778 { Calc.Balance.balance_by_account =
779 Lib.TreeMap.from_List const $
780 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
781 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
782 , Calc.Balance.balance_by_unit =
784 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
785 [ Calc.Balance.Unit_Sum
786 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
787 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
792 (Calc.Balance.Balance
793 { Calc.Balance.balance_by_account =
794 Lib.TreeMap.from_List const $
795 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
796 [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
797 , Calc.Balance.balance_by_unit =
799 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
800 [ Calc.Balance.Unit_Sum
801 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
802 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
809 { Calc.Balance.balance_by_account =
810 Lib.TreeMap.from_List const $
811 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
812 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
813 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
814 , Calc.Balance.balance_by_unit =
816 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
817 [ Calc.Balance.Unit_Sum
818 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 2
819 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
824 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
826 (Calc.Balance.Balance
827 { Calc.Balance.balance_by_account =
828 Lib.TreeMap.from_List const $
829 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
830 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
831 , Calc.Balance.balance_by_unit =
833 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
834 [ Calc.Balance.Unit_Sum
835 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
836 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
841 (Calc.Balance.Balance
842 { Calc.Balance.balance_by_account =
843 Lib.TreeMap.from_List const $
844 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
845 [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
846 , Calc.Balance.balance_by_unit =
848 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
849 [ Calc.Balance.Unit_Sum
850 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.eur $ 1
851 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
858 { Calc.Balance.balance_by_account =
859 Lib.TreeMap.from_List const $
860 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
861 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
862 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
863 , Calc.Balance.balance_by_unit =
865 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
866 [ Calc.Balance.Unit_Sum
867 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
868 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
871 , Calc.Balance.Unit_Sum
872 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.eur $ 1
873 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
879 , "expanded" ~: TestList
880 [ "nil_By_Account" ~:
881 Calc.Balance.expanded
884 (Lib.TreeMap.empty::Calc.Balance.Expanded Amount)
886 Calc.Balance.expanded
887 (Lib.TreeMap.from_List const $
888 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
889 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
891 (Lib.TreeMap.from_List const $
892 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
893 { Calc.Balance.inclusive =
894 Data.Map.map Calc.Balance.amount_sum $
895 Amount.from_List [ Amount.usd $ 1 ]
896 , Calc.Balance.exclusive =
897 Data.Map.map Calc.Balance.amount_sum $
898 Amount.from_List [ Amount.usd $ 1 ]
901 , "A/A+$1 = A+$1 A/A+$1" ~:
902 Calc.Balance.expanded
903 (Lib.TreeMap.from_List const $
904 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
905 [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
907 (Lib.TreeMap.from_List const
908 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
909 { Calc.Balance.inclusive =
910 Data.Map.map Calc.Balance.amount_sum $
911 Amount.from_List [ Amount.usd $ 1 ]
912 , Calc.Balance.exclusive =
913 Data.Map.map Calc.Balance.amount_sum $
916 , ("A":|["A"], Calc.Balance.Account_Sum_Expanded
917 { Calc.Balance.inclusive =
918 Data.Map.map Calc.Balance.amount_sum $
919 Amount.from_List [ Amount.usd $ 1 ]
920 , Calc.Balance.exclusive =
921 Data.Map.map Calc.Balance.amount_sum $
922 Amount.from_List [ Amount.usd $ 1 ]
925 , "A/B+$1 = A+$1 A/B+$1" ~:
926 Calc.Balance.expanded
927 (Lib.TreeMap.from_List const $
928 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
929 [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
931 (Lib.TreeMap.from_List const
932 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
933 { Calc.Balance.inclusive =
934 Data.Map.map Calc.Balance.amount_sum $
935 Amount.from_List [ Amount.usd $ 1 ]
936 , Calc.Balance.exclusive =
937 Data.Map.map Calc.Balance.amount_sum $
940 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
941 { Calc.Balance.inclusive =
942 Data.Map.map Calc.Balance.amount_sum $
943 Amount.from_List [ Amount.usd $ 1 ]
944 , Calc.Balance.exclusive =
945 Data.Map.map Calc.Balance.amount_sum $
946 Amount.from_List [ Amount.usd $ 1 ]
949 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
950 Calc.Balance.expanded
951 (Lib.TreeMap.from_List const $
952 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
953 [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
955 (Lib.TreeMap.from_List const $
956 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
957 { Calc.Balance.inclusive =
958 Data.Map.map Calc.Balance.amount_sum $
959 Amount.from_List [ Amount.usd $ 1 ]
960 , Calc.Balance.exclusive =
961 Data.Map.map Calc.Balance.amount_sum $
964 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
965 { Calc.Balance.inclusive =
966 Data.Map.map Calc.Balance.amount_sum $
967 Amount.from_List [ Amount.usd $ 1 ]
968 , Calc.Balance.exclusive =
969 Data.Map.map Calc.Balance.amount_sum $
972 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
973 { Calc.Balance.inclusive =
974 Data.Map.map Calc.Balance.amount_sum $
975 Amount.from_List [ Amount.usd $ 1 ]
976 , Calc.Balance.exclusive =
977 Data.Map.map Calc.Balance.amount_sum $
978 Amount.from_List [ Amount.usd $ 1 ]
981 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
982 Calc.Balance.expanded
983 (Lib.TreeMap.from_List const $
984 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
985 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
986 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
989 (Lib.TreeMap.from_List const
990 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
991 { Calc.Balance.inclusive =
992 Data.Map.map Calc.Balance.amount_sum $
993 Amount.from_List [ Amount.usd $ 2 ]
994 , Calc.Balance.exclusive =
995 Data.Map.map Calc.Balance.amount_sum $
996 Amount.from_List [ Amount.usd $ 1 ]
998 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
999 { Calc.Balance.inclusive =
1000 Data.Map.map Calc.Balance.amount_sum $
1001 Amount.from_List [ Amount.usd $ 1 ]
1002 , Calc.Balance.exclusive =
1003 Data.Map.map Calc.Balance.amount_sum $
1004 Amount.from_List [ Amount.usd $ 1 ]
1007 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
1008 Calc.Balance.expanded
1009 (Lib.TreeMap.from_List const $
1010 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1011 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1012 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
1013 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
1016 (Lib.TreeMap.from_List const
1017 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
1018 { Calc.Balance.inclusive =
1019 Data.Map.map Calc.Balance.amount_sum $
1020 Amount.from_List [ Amount.usd $ 3 ]
1021 , Calc.Balance.exclusive =
1022 Data.Map.map Calc.Balance.amount_sum $
1023 Amount.from_List [ Amount.usd $ 1 ]
1025 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
1026 { Calc.Balance.inclusive =
1027 Data.Map.map Calc.Balance.amount_sum $
1028 Amount.from_List [ Amount.usd $ 2 ]
1029 , Calc.Balance.exclusive =
1030 Data.Map.map Calc.Balance.amount_sum $
1031 Amount.from_List [ Amount.usd $ 1 ]
1033 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
1034 { Calc.Balance.inclusive =
1035 Data.Map.map Calc.Balance.amount_sum $
1036 Amount.from_List [ Amount.usd $ 1 ]
1037 , Calc.Balance.exclusive =
1038 Data.Map.map Calc.Balance.amount_sum $
1039 Amount.from_List [ Amount.usd $ 1 ]
1042 , "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" ~:
1043 Calc.Balance.expanded
1044 (Lib.TreeMap.from_List const $
1045 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1046 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1047 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
1048 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
1049 , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
1052 (Lib.TreeMap.from_List const
1053 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
1054 { Calc.Balance.inclusive =
1055 Data.Map.map Calc.Balance.amount_sum $
1056 Amount.from_List [ Amount.usd $ 4 ]
1057 , Calc.Balance.exclusive =
1058 Data.Map.map Calc.Balance.amount_sum $
1059 Amount.from_List [ Amount.usd $ 1 ]
1061 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
1062 { Calc.Balance.inclusive =
1063 Data.Map.map Calc.Balance.amount_sum $
1064 Amount.from_List [ Amount.usd $ 3 ]
1065 , Calc.Balance.exclusive =
1066 Data.Map.map Calc.Balance.amount_sum $
1067 Amount.from_List [ Amount.usd $ 1 ]
1069 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
1070 { Calc.Balance.inclusive =
1071 Data.Map.map Calc.Balance.amount_sum $
1072 Amount.from_List [ Amount.usd $ 2 ]
1073 , Calc.Balance.exclusive =
1074 Data.Map.map Calc.Balance.amount_sum $
1075 Amount.from_List [ Amount.usd $ 1 ]
1077 , ("A":|["B", "C", "D"], Calc.Balance.Account_Sum_Expanded
1078 { Calc.Balance.inclusive =
1079 Data.Map.map Calc.Balance.amount_sum $
1080 Amount.from_List [ Amount.usd $ 1 ]
1081 , Calc.Balance.exclusive =
1082 Data.Map.map Calc.Balance.amount_sum $
1083 Amount.from_List [ Amount.usd $ 1 ]
1086 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
1087 Calc.Balance.expanded
1088 (Lib.TreeMap.from_List const $
1089 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1090 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1091 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
1092 , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
1093 , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ])
1096 (Lib.TreeMap.from_List const
1097 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
1098 { Calc.Balance.inclusive =
1099 Data.Map.map Calc.Balance.amount_sum $
1100 Amount.from_List [ Amount.usd $ 3 ]
1101 , Calc.Balance.exclusive =
1102 Data.Map.map Calc.Balance.amount_sum $
1103 Amount.from_List [ Amount.usd $ 1 ]
1105 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
1106 { Calc.Balance.inclusive =
1107 Data.Map.map Calc.Balance.amount_sum $
1108 Amount.from_List [ Amount.usd $ 1 ]
1109 , Calc.Balance.exclusive =
1110 Data.Map.map Calc.Balance.amount_sum $
1111 Amount.from_List [ Amount.usd $ 1 ]
1113 , ("A":|["BB"], Calc.Balance.Account_Sum_Expanded
1114 { Calc.Balance.inclusive =
1115 Data.Map.map Calc.Balance.amount_sum $
1116 Amount.from_List [ Amount.usd $ 1 ]
1117 , Calc.Balance.exclusive =
1118 Data.Map.map Calc.Balance.amount_sum $
1119 Amount.from_List [ Amount.usd $ 1 ]
1121 , ("AA":|[], Calc.Balance.Account_Sum_Expanded
1122 { Calc.Balance.inclusive =
1123 Data.Map.map Calc.Balance.amount_sum $
1124 Amount.from_List [ Amount.usd $ 1 ]
1125 , Calc.Balance.exclusive =
1126 Data.Map.map Calc.Balance.amount_sum $
1129 , ("AA":|["B"], Calc.Balance.Account_Sum_Expanded
1130 { Calc.Balance.inclusive =
1131 Data.Map.map Calc.Balance.amount_sum $
1132 Amount.from_List [ Amount.usd $ 1 ]
1133 , Calc.Balance.exclusive =
1134 Data.Map.map Calc.Balance.amount_sum $
1135 Amount.from_List [ Amount.usd $ 1 ]
1139 , "deviation" ~: TestList
1141 (Calc.Balance.deviation $
1142 Calc.Balance.Balance
1143 { Calc.Balance.balance_by_account =
1144 Lib.TreeMap.from_List const $
1145 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1146 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1147 , ("B":|[], Amount.from_List [])
1149 , Calc.Balance.balance_by_unit =
1151 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1152 [ Calc.Balance.Unit_Sum
1153 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
1154 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1160 (Calc.Balance.Deviation $
1162 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1163 [ Calc.Balance.Unit_Sum
1164 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
1165 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1169 , "{A+$1 B+$1, $2}" ~:
1170 (Calc.Balance.deviation $
1171 Calc.Balance.Balance
1172 { Calc.Balance.balance_by_account =
1173 Lib.TreeMap.from_List const $
1174 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1175 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1176 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
1178 , Calc.Balance.balance_by_unit =
1180 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1181 [ Calc.Balance.Unit_Sum
1182 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 2
1183 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1191 (Calc.Balance.Deviation $
1193 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1194 [ Calc.Balance.Unit_Sum
1195 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 2
1196 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1202 , "is_equilibrium_inferrable" ~: TestList
1203 [ "nil" ~: TestCase $
1205 Calc.Balance.is_equilibrium_inferrable $
1206 Calc.Balance.deviation $
1207 (Calc.Balance.nil::Calc.Balance.Balance Amount.Amount)
1208 , "{A+$0, $+0}" ~: TestCase $
1210 Calc.Balance.is_equilibrium_inferrable $
1211 Calc.Balance.deviation $
1212 Calc.Balance.Balance
1213 { Calc.Balance.balance_by_account =
1214 Lib.TreeMap.from_List const $
1215 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1216 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
1218 , Calc.Balance.balance_by_unit =
1220 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1221 [ Calc.Balance.Unit_Sum
1222 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 0
1223 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1228 , "{A+$1, $+1}" ~: TestCase $
1230 Calc.Balance.is_equilibrium_inferrable $
1231 Calc.Balance.deviation $
1232 Calc.Balance.Balance
1233 { Calc.Balance.balance_by_account =
1234 Lib.TreeMap.from_List const $
1235 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1236 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1238 , Calc.Balance.balance_by_unit =
1240 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1241 [ Calc.Balance.Unit_Sum
1242 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
1243 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1248 , "{A+$0+€0, $0 €+0}" ~: TestCase $
1250 Calc.Balance.is_equilibrium_inferrable $
1251 Calc.Balance.deviation $
1252 Calc.Balance.Balance
1253 { Calc.Balance.balance_by_account =
1254 Lib.TreeMap.from_List const $
1255 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1256 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
1258 , Calc.Balance.balance_by_unit =
1260 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1261 [ Calc.Balance.Unit_Sum
1262 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 0
1263 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1266 , Calc.Balance.Unit_Sum
1267 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.eur $ 0
1268 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1273 , "{A+$1, B-$1, $+0}" ~: TestCase $
1275 Calc.Balance.is_equilibrium_inferrable $
1276 Calc.Balance.deviation $
1277 Calc.Balance.Balance
1278 { Calc.Balance.balance_by_account =
1279 Lib.TreeMap.from_List const $
1280 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1281 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1282 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
1284 , Calc.Balance.balance_by_unit =
1286 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1287 [ Calc.Balance.Unit_Sum
1288 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 0
1289 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1294 , "{A+$1 B, $+1}" ~: TestCase $
1296 Calc.Balance.is_equilibrium_inferrable $
1297 Calc.Balance.deviation $
1298 Calc.Balance.Balance
1299 { Calc.Balance.balance_by_account =
1300 Lib.TreeMap.from_List const $
1301 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1302 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1303 , ("B":|[], Amount.from_List [])
1305 , Calc.Balance.balance_by_unit =
1307 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1308 [ Calc.Balance.Unit_Sum
1309 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
1310 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1315 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
1317 Calc.Balance.is_equilibrium_inferrable $
1318 Calc.Balance.deviation $
1319 Calc.Balance.Balance
1320 { Calc.Balance.balance_by_account =
1321 Lib.TreeMap.from_List const $
1322 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1323 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1324 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
1326 , Calc.Balance.balance_by_unit =
1328 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1329 [ Calc.Balance.Unit_Sum
1330 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 1
1331 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1334 , Calc.Balance.Unit_Sum
1335 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.eur $ 1
1336 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1341 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
1343 Calc.Balance.is_equilibrium_inferrable $
1344 Calc.Balance.deviation $
1345 Calc.Balance.Balance
1346 { Calc.Balance.balance_by_account =
1347 Lib.TreeMap.from_List const $
1348 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1349 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
1350 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
1352 , Calc.Balance.balance_by_unit =
1354 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1355 [ Calc.Balance.Unit_Sum
1356 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 0
1357 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1360 , Calc.Balance.Unit_Sum
1361 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.eur $ 1
1362 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1367 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
1369 Calc.Balance.is_equilibrium_inferrable $
1370 Calc.Balance.deviation $
1371 Calc.Balance.Balance
1372 { Calc.Balance.balance_by_account =
1373 Lib.TreeMap.from_List const $
1374 Data.List.map (id *** Data.Map.map Calc.Balance.amount_sum) $
1375 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
1376 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
1378 , Calc.Balance.balance_by_unit =
1380 Data.List.map (\s -> (Amount.unit $ Calc.Balance.amount_sum_balance $ Calc.Balance.unit_sum_amount s, s))
1381 [ Calc.Balance.Unit_Sum
1382 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 0
1383 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1386 , Calc.Balance.Unit_Sum
1387 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.eur $ 0
1388 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1391 , Calc.Balance.Unit_Sum
1392 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.gbp $ 0
1393 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
1399 , "infer_equilibrium" ~: TestList
1401 (snd $ Calc.Balance.infer_equilibrium $
1402 Format.Ledger.posting_by_Account
1403 [ (Format.Ledger.posting ("A":|[]))
1404 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1405 , (Format.Ledger.posting ("B":|[]))
1406 { Format.Ledger.posting_amounts=Amount.from_List [] }
1410 Format.Ledger.posting_by_Account
1411 [ (Format.Ledger.posting ("A":|[]))
1412 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1413 , (Format.Ledger.posting ("B":|[]))
1414 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] }
1417 (snd $ Calc.Balance.infer_equilibrium $
1418 Format.Ledger.posting_by_Account
1419 [ (Format.Ledger.posting ("A":|[]))
1420 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1421 , (Format.Ledger.posting ("B":|[]))
1422 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] }
1426 Format.Ledger.posting_by_Account
1427 [ (Format.Ledger.posting ("A":|[]))
1428 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1] }
1429 , (Format.Ledger.posting ("B":|[]))
1430 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1, Amount.usd $ -1 ] }
1433 (snd $ Calc.Balance.infer_equilibrium $
1434 Format.Ledger.posting_by_Account
1435 [ (Format.Ledger.posting ("A":|[]))
1436 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1437 , (Format.Ledger.posting ("B":|[]))
1438 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1442 [ Calc.Balance.Unit_Sum
1443 { Calc.Balance.unit_sum_amount = Calc.Balance.amount_sum $ Amount.usd $ 2
1444 , Calc.Balance.unit_sum_accounts = Data.Map.fromList []}
1446 , "{A+$1 B-$1 B-1€}" ~:
1447 (snd $ Calc.Balance.infer_equilibrium $
1448 Format.Ledger.posting_by_Account
1449 [ (Format.Ledger.posting ("A":|[]))
1450 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1451 , (Format.Ledger.posting ("B":|[]))
1452 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
1456 Format.Ledger.posting_by_Account
1457 [ (Format.Ledger.posting ("A":|[]))
1458 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1 ] }
1459 , (Format.Ledger.posting ("B":|[]))
1460 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
1465 , "Format" ~: TestList
1466 [ "Ledger" ~: TestList
1467 [ "Read" ~: TestList
1468 [ "account_name" ~: TestList
1470 (Data.Either.rights $
1472 (Format.Ledger.Read.account_name <* P.eof)
1477 (Data.Either.rights $
1479 (Format.Ledger.Read.account_name <* P.eof)
1484 (Data.Either.rights $
1486 (Format.Ledger.Read.account_name <* P.eof)
1487 () "" ("AA"::Text)])
1491 (Data.Either.rights $
1493 (Format.Ledger.Read.account_name <* P.eof)
1498 (Data.Either.rights $
1500 (Format.Ledger.Read.account_name <* P.eof)
1505 (Data.Either.rights $
1507 (Format.Ledger.Read.account_name <* P.eof)
1508 () "" ("A:"::Text)])
1512 (Data.Either.rights $
1514 (Format.Ledger.Read.account_name <* P.eof)
1515 () "" (":A"::Text)])
1519 (Data.Either.rights $
1521 (Format.Ledger.Read.account_name <* P.eof)
1522 () "" ("A "::Text)])
1526 (Data.Either.rights $
1528 (Format.Ledger.Read.account_name)
1529 () "" ("A "::Text)])
1533 (Data.Either.rights $
1535 (Format.Ledger.Read.account_name <* P.eof)
1536 () "" ("A A"::Text)])
1540 (Data.Either.rights $
1542 (Format.Ledger.Read.account_name <* P.eof)
1543 () "" ("A "::Text)])
1547 (Data.Either.rights $
1549 (Format.Ledger.Read.account_name <* P.eof)
1550 () "" ("A \n"::Text)])
1554 (Data.Either.rights $
1556 (Format.Ledger.Read.account_name <* P.eof)
1557 () "" ("(A)A"::Text)])
1561 (Data.Either.rights $
1563 (Format.Ledger.Read.account_name <* P.eof)
1564 () "" ("( )A"::Text)])
1568 (Data.Either.rights $
1570 (Format.Ledger.Read.account_name <* P.eof)
1571 () "" ("(A) A"::Text)])
1575 (Data.Either.rights $
1577 (Format.Ledger.Read.account_name <* P.eof)
1578 () "" ("[ ]A"::Text)])
1582 (Data.Either.rights $
1584 (Format.Ledger.Read.account_name <* P.eof)
1585 () "" ("(A) "::Text)])
1589 (Data.Either.rights $
1591 (Format.Ledger.Read.account_name <* P.eof)
1592 () "" ("(A)"::Text)])
1596 (Data.Either.rights $
1598 (Format.Ledger.Read.account_name <* P.eof)
1599 () "" ("A(A)"::Text)])
1603 (Data.Either.rights $
1605 (Format.Ledger.Read.account_name <* P.eof)
1606 () "" ("[A]A"::Text)])
1610 (Data.Either.rights $
1612 (Format.Ledger.Read.account_name <* P.eof)
1613 () "" ("[A] A"::Text)])
1617 (Data.Either.rights $
1619 (Format.Ledger.Read.account_name <* P.eof)
1620 () "" ("[A] "::Text)])
1624 (Data.Either.rights $
1626 (Format.Ledger.Read.account_name <* P.eof)
1627 () "" ("[A]"::Text)])
1631 , "account" ~: TestList
1633 (Data.Either.rights $
1635 (Format.Ledger.Read.account <* P.eof)
1640 (Data.Either.rights $
1642 (Format.Ledger.Read.account <* P.eof)
1647 (Data.Either.rights $
1649 (Format.Ledger.Read.account <* P.eof)
1650 () "" ("A:"::Text)])
1654 (Data.Either.rights $
1656 (Format.Ledger.Read.account <* P.eof)
1657 () "" (":A"::Text)])
1661 (Data.Either.rights $
1663 (Format.Ledger.Read.account <* P.eof)
1664 () "" ("A "::Text)])
1668 (Data.Either.rights $
1670 (Format.Ledger.Read.account <* P.eof)
1671 () "" (" A"::Text)])
1675 (Data.Either.rights $
1677 (Format.Ledger.Read.account <* P.eof)
1678 () "" ("A:B"::Text)])
1682 (Data.Either.rights $
1684 (Format.Ledger.Read.account <* P.eof)
1685 () "" ("A:B:C"::Text)])
1688 , "\"Aa:Bbb:Cccc\"" ~:
1689 (Data.Either.rights $
1691 (Format.Ledger.Read.account <* P.eof)
1692 () "" ("Aa:Bbb:Cccc"::Text)])
1694 ["Aa":|["Bbb", "Cccc"]]
1695 , "\"A a : B b b : C c c c\"" ~:
1696 (Data.Either.rights $
1698 (Format.Ledger.Read.account <* P.eof)
1699 () "" ("A a : B b b : C c c c"::Text)])
1701 ["A a ":|[" B b b ", " C c c c"]]
1703 (Data.Either.rights $
1705 (Format.Ledger.Read.account <* P.eof)
1706 () "" ("A: :C"::Text)])
1710 (Data.Either.rights $
1712 (Format.Ledger.Read.account <* P.eof)
1713 () "" ("A::C"::Text)])
1717 (Data.Either.rights $
1719 (Format.Ledger.Read.account <* P.eof)
1720 () "" ("A:B:(C)"::Text)])
1724 , "posting_type" ~: TestList
1726 Format.Ledger.Read.posting_type
1729 (Format.Ledger.Posting_Type_Regular, "A":|[])
1731 Format.Ledger.Read.posting_type
1734 (Format.Ledger.Posting_Type_Regular, "(":|[])
1736 Format.Ledger.Read.posting_type
1739 (Format.Ledger.Posting_Type_Regular, ")":|[])
1741 Format.Ledger.Read.posting_type
1744 (Format.Ledger.Posting_Type_Regular, "()":|[])
1746 Format.Ledger.Read.posting_type
1749 (Format.Ledger.Posting_Type_Regular, "( )":|[])
1751 Format.Ledger.Read.posting_type
1754 (Format.Ledger.Posting_Type_Virtual, "A":|[])
1756 Format.Ledger.Read.posting_type
1759 (Format.Ledger.Posting_Type_Virtual, "A":|["B", "C"])
1761 Format.Ledger.Read.posting_type
1764 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
1766 Format.Ledger.Read.posting_type
1769 (Format.Ledger.Posting_Type_Regular, "(A)":|["B", "C"])
1771 Format.Ledger.Read.posting_type
1774 (Format.Ledger.Posting_Type_Regular, "A":|["(B)", "C"])
1776 Format.Ledger.Read.posting_type
1779 (Format.Ledger.Posting_Type_Regular, "A":|["B", "(C)"])
1781 Format.Ledger.Read.posting_type
1784 (Format.Ledger.Posting_Type_Regular, "[":|[])
1786 Format.Ledger.Read.posting_type
1789 (Format.Ledger.Posting_Type_Regular, "]":|[])
1791 Format.Ledger.Read.posting_type
1794 (Format.Ledger.Posting_Type_Regular, "[]":|[])
1796 Format.Ledger.Read.posting_type
1799 (Format.Ledger.Posting_Type_Regular, "[ ]":|[])
1801 Format.Ledger.Read.posting_type
1804 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|[])
1806 Format.Ledger.Read.posting_type
1809 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|["B", "C"])
1811 Format.Ledger.Read.posting_type
1814 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
1816 Format.Ledger.Read.posting_type
1819 (Format.Ledger.Posting_Type_Regular, "[A]":|["B", "C"])
1821 Format.Ledger.Read.posting_type
1824 (Format.Ledger.Posting_Type_Regular, "A":|["[B]", "C"])
1826 Format.Ledger.Read.posting_type
1829 (Format.Ledger.Posting_Type_Regular, "A":|["B", "[C]"])
1831 , "amount" ~: TestList
1833 (Data.Either.rights $
1835 (Format.Ledger.Read.amount <* P.eof)
1839 , "\"0\" = Right 0" ~:
1840 (Data.Either.rights $
1842 (Format.Ledger.Read.amount <* P.eof)
1846 { Amount.quantity = Decimal 0 0
1848 , "\"00\" = Right 0" ~:
1849 (Data.Either.rights $
1851 (Format.Ledger.Read.amount <* P.eof)
1852 () "" ("00"::Text)])
1855 { Amount.quantity = Decimal 0 0
1857 , "\"0.\" = Right 0." ~:
1858 (Data.Either.rights $
1860 (Format.Ledger.Read.amount <* P.eof)
1861 () "" ("0."::Text)])
1864 { Amount.quantity = Decimal 0 0
1867 { Amount.Style.fractioning = Just '.'
1870 , "\".0\" = Right 0.0" ~:
1871 (Data.Either.rights $
1873 (Format.Ledger.Read.amount <* P.eof)
1874 () "" (".0"::Text)])
1877 { Amount.quantity = Decimal 0 0
1880 { Amount.Style.fractioning = Just '.'
1881 , Amount.Style.precision = 1
1884 , "\"0,\" = Right 0," ~:
1885 (Data.Either.rights $
1887 (Format.Ledger.Read.amount <* P.eof)
1888 () "" ("0,"::Text)])
1891 { Amount.quantity = Decimal 0 0
1894 { Amount.Style.fractioning = Just ','
1897 , "\",0\" = Right 0,0" ~:
1898 (Data.Either.rights $
1900 (Format.Ledger.Read.amount <* P.eof)
1901 () "" (",0"::Text)])
1904 { Amount.quantity = Decimal 0 0
1907 { Amount.Style.fractioning = Just ','
1908 , Amount.Style.precision = 1
1911 , "\"0_\" = Left" ~:
1912 (Data.Either.rights $
1914 (Format.Ledger.Read.amount <* P.eof)
1915 () "" ("0_"::Text)])
1918 , "\"_0\" = Left" ~:
1919 (Data.Either.rights $
1921 (Format.Ledger.Read.amount <* P.eof)
1922 () "" ("_0"::Text)])
1925 , "\"0.0\" = Right 0.0" ~:
1926 (Data.Either.rights $
1928 (Format.Ledger.Read.amount <* P.eof)
1929 () "" ("0.0"::Text)])
1932 { Amount.quantity = Decimal 0 0
1935 { Amount.Style.fractioning = Just '.'
1936 , Amount.Style.precision = 1
1939 , "\"00.00\" = Right 0.00" ~:
1940 (Data.Either.rights $
1942 (Format.Ledger.Read.amount <* P.eof)
1943 () "" ("00.00"::Text)])
1946 { Amount.quantity = Decimal 0 0
1949 { Amount.Style.fractioning = Just '.'
1950 , Amount.Style.precision = 2
1953 , "\"0,0\" = Right 0,0" ~:
1954 (Data.Either.rights $
1956 (Format.Ledger.Read.amount <* P.eof)
1957 () "" ("0,0"::Text)])
1960 { Amount.quantity = Decimal 0 0
1963 { Amount.Style.fractioning = Just ','
1964 , Amount.Style.precision = 1
1967 , "\"00,00\" = Right 0,00" ~:
1968 (Data.Either.rights $
1970 (Format.Ledger.Read.amount <* P.eof)
1971 () "" ("00,00"::Text)])
1974 { Amount.quantity = Decimal 0 0
1977 { Amount.Style.fractioning = Just ','
1978 , Amount.Style.precision = 2
1981 , "\"0_0\" = Right 0" ~:
1982 (Data.Either.rights $
1984 (Format.Ledger.Read.amount <* P.eof)
1985 () "" ("0_0"::Text)])
1988 { Amount.quantity = Decimal 0 0
1991 { Amount.Style.fractioning = Nothing
1992 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1993 , Amount.Style.precision = 0
1996 , "\"00_00\" = Right 0" ~:
1997 (Data.Either.rights $
1999 (Format.Ledger.Read.amount <* P.eof)
2000 () "" ("00_00"::Text)])
2003 { Amount.quantity = Decimal 0 0
2006 { Amount.Style.fractioning = Nothing
2007 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
2008 , Amount.Style.precision = 0
2011 , "\"0,000.00\" = Right 0,000.00" ~:
2012 (Data.Either.rights $
2014 (Format.Ledger.Read.amount <* P.eof)
2015 () "" ("0,000.00"::Text)])
2018 { Amount.quantity = Decimal 0 0
2021 { Amount.Style.fractioning = Just '.'
2022 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2023 , Amount.Style.precision = 2
2026 , "\"0.000,00\" = Right 0.000,00" ~:
2027 (Data.Either.rights $
2029 (Format.Ledger.Read.amount)
2030 () "" ("0.000,00"::Text)])
2033 { Amount.quantity = Decimal 0 0
2036 { Amount.Style.fractioning = Just ','
2037 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
2038 , Amount.Style.precision = 2
2041 , "\"1,000.00\" = Right 1,000.00" ~:
2042 (Data.Either.rights $
2044 (Format.Ledger.Read.amount <* P.eof)
2045 () "" ("1,000.00"::Text)])
2048 { Amount.quantity = Decimal 0 1000
2051 { Amount.Style.fractioning = Just '.'
2052 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2053 , Amount.Style.precision = 2
2056 , "\"1.000,00\" = Right 1.000,00" ~:
2057 (Data.Either.rights $
2059 (Format.Ledger.Read.amount)
2060 () "" ("1.000,00"::Text)])
2063 { Amount.quantity = Decimal 0 1000
2066 { Amount.Style.fractioning = Just ','
2067 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
2068 , Amount.Style.precision = 2
2071 , "\"1,000.00.\" = Left" ~:
2072 (Data.Either.rights $
2074 (Format.Ledger.Read.amount)
2075 () "" ("1,000.00."::Text)])
2078 , "\"1.000,00,\" = Left" ~:
2079 (Data.Either.rights $
2081 (Format.Ledger.Read.amount)
2082 () "" ("1.000,00,"::Text)])
2085 , "\"1,000.00_\" = Left" ~:
2086 (Data.Either.rights $
2088 (Format.Ledger.Read.amount)
2089 () "" ("1,000.00_"::Text)])
2092 , "\"12\" = Right 12" ~:
2093 (Data.Either.rights $
2095 (Format.Ledger.Read.amount <* P.eof)
2096 () "" ("123"::Text)])
2099 { Amount.quantity = Decimal 0 123
2101 , "\"1.2\" = Right 1.2" ~:
2102 (Data.Either.rights $
2104 (Format.Ledger.Read.amount <* P.eof)
2105 () "" ("1.2"::Text)])
2108 { Amount.quantity = Decimal 1 12
2111 { Amount.Style.fractioning = Just '.'
2112 , Amount.Style.precision = 1
2115 , "\"1,2\" = Right 1,2" ~:
2116 (Data.Either.rights $
2118 (Format.Ledger.Read.amount <* P.eof)
2119 () "" ("1,2"::Text)])
2122 { Amount.quantity = Decimal 1 12
2125 { Amount.Style.fractioning = Just ','
2126 , Amount.Style.precision = 1
2129 , "\"12.23\" = Right 12.23" ~:
2130 (Data.Either.rights $
2132 (Format.Ledger.Read.amount <* P.eof)
2133 () "" ("12.34"::Text)])
2136 { Amount.quantity = Decimal 2 1234
2139 { Amount.Style.fractioning = Just '.'
2140 , Amount.Style.precision = 2
2143 , "\"12,23\" = Right 12,23" ~:
2144 (Data.Either.rights $
2146 (Format.Ledger.Read.amount <* P.eof)
2147 () "" ("12,34"::Text)])
2150 { Amount.quantity = Decimal 2 1234
2153 { Amount.Style.fractioning = Just ','
2154 , Amount.Style.precision = 2
2157 , "\"1_2\" = Right 1_2" ~:
2158 (Data.Either.rights $
2160 (Format.Ledger.Read.amount <* P.eof)
2161 () "" ("1_2"::Text)])
2164 { Amount.quantity = Decimal 0 12
2167 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
2168 , Amount.Style.precision = 0
2171 , "\"1_23\" = Right 1_23" ~:
2172 (Data.Either.rights $
2174 (Format.Ledger.Read.amount <* P.eof)
2175 () "" ("1_23"::Text)])
2178 { Amount.quantity = Decimal 0 123
2181 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
2182 , Amount.Style.precision = 0
2185 , "\"1_23_456\" = Right 1_23_456" ~:
2186 (Data.Either.rights $
2188 (Format.Ledger.Read.amount <* P.eof)
2189 () "" ("1_23_456"::Text)])
2192 { Amount.quantity = Decimal 0 123456
2195 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
2196 , Amount.Style.precision = 0
2199 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
2200 (Data.Either.rights $
2202 (Format.Ledger.Read.amount <* P.eof)
2203 () "" ("1_23_456.7890_12345_678901"::Text)])
2206 { Amount.quantity = Decimal 15 123456789012345678901
2209 { Amount.Style.fractioning = Just '.'
2210 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
2211 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
2212 , Amount.Style.precision = 15
2215 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
2216 (Data.Either.rights $
2218 (Format.Ledger.Read.amount <* P.eof)
2219 () "" ("123456_78901_2345.678_90_1"::Text)])
2222 { Amount.quantity = Decimal 6 123456789012345678901
2225 { Amount.Style.fractioning = Just '.'
2226 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
2227 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
2228 , Amount.Style.precision = 6
2231 , "\"$1\" = Right $1" ~:
2232 (Data.Either.rights $
2234 (Format.Ledger.Read.amount <* P.eof)
2235 () "" ("$1"::Text)])
2238 { Amount.quantity = Decimal 0 1
2241 { Amount.Style.fractioning = Nothing
2242 , Amount.Style.grouping_integral = Nothing
2243 , Amount.Style.grouping_fractional = Nothing
2244 , Amount.Style.precision = 0
2245 , Amount.Style.unit_side = Just Amount.Style.Side_Left
2246 , Amount.Style.unit_spaced = Just False
2250 , "\"1$\" = Right 1$" ~:
2251 (Data.Either.rights $
2253 (Format.Ledger.Read.amount <* P.eof)
2254 () "" ("1$"::Text)])
2257 { Amount.quantity = Decimal 0 1
2260 { Amount.Style.fractioning = Nothing
2261 , Amount.Style.grouping_integral = Nothing
2262 , Amount.Style.grouping_fractional = Nothing
2263 , Amount.Style.precision = 0
2264 , Amount.Style.unit_side = Just Amount.Style.Side_Right
2265 , Amount.Style.unit_spaced = Just False
2269 , "\"$ 1\" = Right $ 1" ~:
2270 (Data.Either.rights $
2272 (Format.Ledger.Read.amount <* P.eof)
2273 () "" ("$ 1"::Text)])
2276 { Amount.quantity = Decimal 0 1
2279 { Amount.Style.fractioning = Nothing
2280 , Amount.Style.grouping_integral = Nothing
2281 , Amount.Style.grouping_fractional = Nothing
2282 , Amount.Style.precision = 0
2283 , Amount.Style.unit_side = Just Amount.Style.Side_Left
2284 , Amount.Style.unit_spaced = Just True
2288 , "\"1 $\" = Right 1 $" ~:
2289 (Data.Either.rights $
2291 (Format.Ledger.Read.amount <* P.eof)
2292 () "" ("1 $"::Text)])
2295 { Amount.quantity = Decimal 0 1
2298 { Amount.Style.fractioning = Nothing
2299 , Amount.Style.grouping_integral = Nothing
2300 , Amount.Style.grouping_fractional = Nothing
2301 , Amount.Style.precision = 0
2302 , Amount.Style.unit_side = Just Amount.Style.Side_Right
2303 , Amount.Style.unit_spaced = Just True
2307 , "\"-$1\" = Right $-1" ~:
2308 (Data.Either.rights $
2310 (Format.Ledger.Read.amount <* P.eof)
2311 () "" ("-$1"::Text)])
2314 { Amount.quantity = Decimal 0 (-1)
2317 { Amount.Style.fractioning = Nothing
2318 , Amount.Style.grouping_integral = Nothing
2319 , Amount.Style.grouping_fractional = Nothing
2320 , Amount.Style.precision = 0
2321 , Amount.Style.unit_side = Just Amount.Style.Side_Left
2322 , Amount.Style.unit_spaced = Just False
2326 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
2327 (Data.Either.rights $
2329 (Format.Ledger.Read.amount <* P.eof)
2330 () "" ("\"4 2\"1"::Text)])
2333 { Amount.quantity = Decimal 0 1
2336 { Amount.Style.fractioning = Nothing
2337 , Amount.Style.grouping_integral = Nothing
2338 , Amount.Style.grouping_fractional = Nothing
2339 , Amount.Style.precision = 0
2340 , Amount.Style.unit_side = Just Amount.Style.Side_Left
2341 , Amount.Style.unit_spaced = Just False
2343 , Amount.unit = "4 2"
2345 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
2346 (Data.Either.rights $
2348 (Format.Ledger.Read.amount <* P.eof)
2349 () "" ("1\"4 2\""::Text)])
2352 { Amount.quantity = Decimal 0 1
2355 { Amount.Style.fractioning = Nothing
2356 , Amount.Style.grouping_integral = Nothing
2357 , Amount.Style.grouping_fractional = Nothing
2358 , Amount.Style.precision = 0
2359 , Amount.Style.unit_side = Just Amount.Style.Side_Right
2360 , Amount.Style.unit_spaced = Just False
2362 , Amount.unit = "4 2"
2364 , "\"$1.000,00\" = Right $1.000,00" ~:
2365 (Data.Either.rights $
2367 (Format.Ledger.Read.amount <* P.eof)
2368 () "" ("$1.000,00"::Text)])
2371 { Amount.quantity = Decimal 0 1000
2374 { Amount.Style.fractioning = Just ','
2375 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
2376 , Amount.Style.grouping_fractional = Nothing
2377 , Amount.Style.precision = 2
2378 , Amount.Style.unit_side = Just Amount.Style.Side_Left
2379 , Amount.Style.unit_spaced = Just False
2383 , "\"1.000,00$\" = Right 1.000,00$" ~:
2384 (Data.Either.rights $
2386 (Format.Ledger.Read.amount <* P.eof)
2387 () "" ("1.000,00$"::Text)])
2390 { Amount.quantity = Decimal 0 1000
2393 { Amount.Style.fractioning = Just ','
2394 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
2395 , Amount.Style.grouping_fractional = Nothing
2396 , Amount.Style.precision = 2
2397 , Amount.Style.unit_side = Just Amount.Style.Side_Right
2398 , Amount.Style.unit_spaced = Just False
2403 , "comment" ~: TestList
2404 [ "; some comment = Right \" some comment\"" ~:
2405 (Data.Either.rights $
2407 (Format.Ledger.Read.comment <* P.eof)
2408 () "" ("; some comment"::Text)])
2411 , "; some comment \\n = Right \" some comment \"" ~:
2412 (Data.Either.rights $
2414 (Format.Ledger.Read.comment <* P.newline <* P.eof)
2415 () "" ("; some comment \n"::Text)])
2417 [ " some comment " ]
2418 , "; some comment \\r\\n = Right \" some comment \"" ~:
2419 (Data.Either.rights $
2421 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
2422 () "" ("; some comment \r\n"::Text)])
2424 [ " some comment " ]
2426 , "comments" ~: TestList
2427 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
2428 (Data.Either.rights $
2430 (Format.Ledger.Read.comments <* P.eof)
2431 () "" ("; some comment\n ; some other comment"::Text)])
2433 [ [" some comment", " some other comment"] ]
2434 , "; some comment \\n = Right \" some comment \"" ~:
2435 (Data.Either.rights $
2437 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
2438 () "" ("; some comment \n"::Text)])
2440 [ [" some comment "] ]
2442 , "date" ~: TestList
2444 (Data.Either.rights $
2445 [P.runParser_with_Error
2446 (Date.Read.date id Nothing <* P.eof)
2447 () "" ("2000/01/01"::Text)])
2449 [ Time.zonedTimeToUTC $
2452 (Time.fromGregorian 2000 01 01)
2453 (Time.TimeOfDay 0 0 0))
2455 , "2000/01/01 some text" ~:
2456 (Data.Either.rights $
2457 [P.runParser_with_Error
2458 (Date.Read.date id Nothing)
2459 () "" ("2000/01/01 some text"::Text)])
2461 [ Time.zonedTimeToUTC $
2464 (Time.fromGregorian 2000 01 01)
2465 (Time.TimeOfDay 0 0 0))
2467 , "2000/01/01 12:34" ~:
2468 (Data.Either.rights $
2469 [P.runParser_with_Error
2470 (Date.Read.date id Nothing <* P.eof)
2471 () "" ("2000/01/01 12:34"::Text)])
2473 [ Time.zonedTimeToUTC $
2476 (Time.fromGregorian 2000 01 01)
2477 (Time.TimeOfDay 12 34 0))
2479 , "2000/01/01 12:34:56" ~:
2480 (Data.Either.rights $
2481 [P.runParser_with_Error
2482 (Date.Read.date id Nothing <* P.eof)
2483 () "" ("2000/01/01 12:34:56"::Text)])
2485 [ Time.zonedTimeToUTC $
2488 (Time.fromGregorian 2000 01 01)
2489 (Time.TimeOfDay 12 34 56))
2491 , "2000/01/01 12:34 CET" ~:
2492 (Data.Either.rights $
2493 [P.runParser_with_Error
2494 (Date.Read.date id Nothing <* P.eof)
2495 () "" ("2000/01/01 12:34 CET"::Text)])
2497 [ Time.zonedTimeToUTC $
2500 (Time.fromGregorian 2000 01 01)
2501 (Time.TimeOfDay 12 34 0))
2502 (Time.TimeZone 60 True "CET")]
2503 , "2000/01/01 12:34 +0130" ~:
2504 (Data.Either.rights $
2505 [P.runParser_with_Error
2506 (Date.Read.date id Nothing <* P.eof)
2507 () "" ("2000/01/01 12:34 +0130"::Text)])
2509 [ Time.zonedTimeToUTC $
2512 (Time.fromGregorian 2000 01 01)
2513 (Time.TimeOfDay 12 34 0))
2514 (Time.TimeZone 90 False "+0130")]
2515 , "2000/01/01 12:34:56 CET" ~:
2516 (Data.Either.rights $
2517 [P.runParser_with_Error
2518 (Date.Read.date id Nothing <* P.eof)
2519 () "" ("2000/01/01 12:34:56 CET"::Text)])
2521 [ Time.zonedTimeToUTC $
2524 (Time.fromGregorian 2000 01 01)
2525 (Time.TimeOfDay 12 34 56))
2526 (Time.TimeZone 60 True "CET")]
2528 (Data.Either.rights $
2529 [P.runParser_with_Error
2530 (Date.Read.date id Nothing <* P.eof)
2531 () "" ("2001/02/29"::Text)])
2535 (Data.Either.rights $
2536 [P.runParser_with_Error
2537 (Date.Read.date id (Just 2000) <* P.eof)
2538 () "" ("01/01"::Text)])
2540 [ Time.zonedTimeToUTC $
2543 (Time.fromGregorian 2000 01 01)
2544 (Time.TimeOfDay 0 0 0))
2547 , "tag_value" ~: TestList
2549 (Data.Either.rights $
2551 (Format.Ledger.Read.tag_value <* P.eof)
2556 (Data.Either.rights $
2558 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
2559 () "" (",\n"::Text)])
2563 (Data.Either.rights $
2565 (Format.Ledger.Read.tag_value <* P.eof)
2566 () "" (",x"::Text)])
2570 (Data.Either.rights $
2572 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
2573 () "" (",x:"::Text)])
2577 (Data.Either.rights $
2579 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
2580 () "" ("v, v, n:"::Text)])
2586 (Data.Either.rights $
2588 (Format.Ledger.Read.tag <* P.eof)
2589 () "" ("Name:"::Text)])
2593 (Data.Either.rights $
2595 (Format.Ledger.Read.tag <* P.eof)
2596 () "" ("Name:Value"::Text)])
2599 , "Name:Value\\n" ~:
2600 (Data.Either.rights $
2602 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
2603 () "" ("Name:Value\n"::Text)])
2607 (Data.Either.rights $
2609 (Format.Ledger.Read.tag <* P.eof)
2610 () "" ("Name:Val ue"::Text)])
2612 [("Name", "Val ue")]
2614 (Data.Either.rights $
2616 (Format.Ledger.Read.tag <* P.eof)
2617 () "" ("Name:,"::Text)])
2621 (Data.Either.rights $
2623 (Format.Ledger.Read.tag <* P.eof)
2624 () "" ("Name:Val,ue"::Text)])
2626 [("Name", "Val,ue")]
2628 (Data.Either.rights $
2630 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
2631 () "" ("Name:Val,ue:"::Text)])
2635 , "tags" ~: TestList
2637 (Data.Either.rights $
2639 (Format.Ledger.Read.tags <* P.eof)
2640 () "" ("Name:"::Text)])
2647 (Data.Either.rights $
2649 (Format.Ledger.Read.tags <* P.eof)
2650 () "" ("Name:,"::Text)])
2657 (Data.Either.rights $
2659 (Format.Ledger.Read.tags <* P.eof)
2660 () "" ("Name:,Name:"::Text)])
2663 [ ("Name", ["", ""])
2667 (Data.Either.rights $
2669 (Format.Ledger.Read.tags <* P.eof)
2670 () "" ("Name:,Name2:"::Text)])
2677 , "Name: , Name2:" ~:
2678 (Data.Either.rights $
2680 (Format.Ledger.Read.tags <* P.eof)
2681 () "" ("Name: , Name2:"::Text)])
2688 , "Name:,Name2:,Name3:" ~:
2689 (Data.Either.rights $
2691 (Format.Ledger.Read.tags <* P.eof)
2692 () "" ("Name:,Name2:,Name3:"::Text)])
2700 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
2701 (Data.Either.rights $
2703 (Format.Ledger.Read.tags <* P.eof)
2704 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
2707 [ ("Name", ["Val ue"])
2708 , ("Name2", ["V a l u e"])
2709 , ("Name3", ["V al ue"])
2713 , "posting" ~: TestList
2714 [ " A:B:C = Right A:B:C" ~:
2715 (Data.Either.rights $
2716 [P.runParser_with_Error
2717 (Format.Ledger.Read.posting <* P.eof)
2718 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
2720 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
2721 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2723 , Format.Ledger.Posting_Type_Regular
2726 , " !A:B:C = Right !A:B:C" ~:
2727 (Data.List.map fst $
2728 Data.Either.rights $
2729 [P.runParser_with_Error
2730 (Format.Ledger.Read.posting <* P.eof)
2731 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
2733 [ (Format.Ledger.posting ("A":|["B", "C"]))
2734 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2735 , Format.Ledger.posting_status = True
2738 , " *A:B:C = Right *A:B:C" ~:
2739 (Data.List.map fst $
2740 Data.Either.rights $
2741 [P.runParser_with_Error
2742 (Format.Ledger.Read.posting <* P.eof)
2743 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
2745 [ (Format.Ledger.posting ("A":|["B", "C"]))
2746 { Format.Ledger.posting_amounts = Data.Map.fromList []
2747 , Format.Ledger.posting_comments = []
2748 , Format.Ledger.posting_dates = []
2749 , Format.Ledger.posting_status = True
2750 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2751 , Format.Ledger.posting_tags = Data.Map.fromList []
2754 , " A:B:C $1 = Right A:B:C $1" ~:
2755 (Data.List.map fst $
2756 Data.Either.rights $
2757 [P.runParser_with_Error
2758 (Format.Ledger.Read.posting <* P.eof)
2759 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
2761 [ (Format.Ledger.posting ("A":|["B","C $1"]))
2762 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2765 , " A:B:C $1 = Right A:B:C $1" ~:
2766 (Data.List.map fst $
2767 Data.Either.rights $
2768 [P.runParser_with_Error
2769 (Format.Ledger.Read.posting <* P.eof)
2770 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
2772 [ (Format.Ledger.posting ("A":|["B", "C"]))
2773 { Format.Ledger.posting_amounts = Data.Map.fromList
2775 { Amount.quantity = 1
2776 , Amount.style = Amount.Style.nil
2777 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2778 , Amount.Style.unit_spaced = Just False
2783 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2786 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
2787 (Data.List.map fst $
2788 Data.Either.rights $
2789 [P.runParser_with_Error
2790 (Format.Ledger.Read.posting <* P.eof)
2791 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
2793 [ (Format.Ledger.posting ("A":|["B", "C"]))
2794 { Format.Ledger.posting_amounts = Data.Map.fromList
2796 { Amount.quantity = 1
2797 , Amount.style = Amount.Style.nil
2798 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2799 , Amount.Style.unit_spaced = Just False
2804 { Amount.quantity = 1
2805 , Amount.style = Amount.Style.nil
2806 { Amount.Style.unit_side = Just Amount.Style.Side_Right
2807 , Amount.Style.unit_spaced = Just False
2812 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2815 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
2816 (Data.List.map fst $
2817 Data.Either.rights $
2818 [P.runParser_with_Error
2819 (Format.Ledger.Read.posting <* P.eof)
2820 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
2822 [ (Format.Ledger.posting ("A":|["B", "C"]))
2823 { Format.Ledger.posting_amounts = Data.Map.fromList
2825 { Amount.quantity = 2
2826 , Amount.style = Amount.Style.nil
2827 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2828 , Amount.Style.unit_spaced = Just False
2833 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2836 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
2837 (Data.List.map fst $
2838 Data.Either.rights $
2839 [P.runParser_with_Error
2840 (Format.Ledger.Read.posting <* P.eof)
2841 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
2843 [ (Format.Ledger.posting ("A":|["B", "C"]))
2844 { Format.Ledger.posting_amounts = Data.Map.fromList
2846 { Amount.quantity = 3
2847 , Amount.style = Amount.Style.nil
2848 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2849 , Amount.Style.unit_spaced = Just False
2854 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2857 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
2858 (Data.List.map fst $
2859 Data.Either.rights $
2860 [P.runParser_with_Error
2861 (Format.Ledger.Read.posting <* P.eof)
2862 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
2864 [ (Format.Ledger.posting ("A":|["B", "C"]))
2865 { Format.Ledger.posting_amounts = Data.Map.fromList []
2866 , Format.Ledger.posting_comments = [" some comment"]
2867 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2870 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
2871 (Data.List.map fst $
2872 Data.Either.rights $
2873 [P.runParser_with_Error
2874 (Format.Ledger.Read.posting <* P.eof)
2875 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
2877 [ (Format.Ledger.posting ("A":|["B", "C"]))
2878 { Format.Ledger.posting_amounts = Data.Map.fromList []
2879 , Format.Ledger.posting_comments = [" some comment", " some other comment"]
2880 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2883 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
2884 (Data.List.map fst $
2885 Data.Either.rights $
2886 [P.runParser_with_Error
2887 (Format.Ledger.Read.posting)
2888 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
2890 [ (Format.Ledger.posting ("A":|["B", "C"]))
2891 { Format.Ledger.posting_amounts = Data.Map.fromList
2893 { Amount.quantity = 1
2894 , Amount.style = Amount.Style.nil
2895 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2896 , Amount.Style.unit_spaced = Just False
2901 , Format.Ledger.posting_comments = [" some comment"]
2902 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2905 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
2906 (Data.List.map fst $
2907 Data.Either.rights $
2908 [P.runParser_with_Error
2909 (Format.Ledger.Read.posting <* P.eof)
2910 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
2912 [ (Format.Ledger.posting ("A":|["B", "C"]))
2913 { Format.Ledger.posting_comments = [" N:V"]
2914 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2915 , Format.Ledger.posting_tags = Data.Map.fromList
2920 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2921 (Data.List.map fst $
2922 Data.Either.rights $
2923 [P.runParser_with_Error
2924 (Format.Ledger.Read.posting <* P.eof)
2925 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2927 [ (Format.Ledger.posting ("A":|["B", "C"]))
2928 { Format.Ledger.posting_comments = [" some comment N:V"]
2929 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2930 , Format.Ledger.posting_tags = Data.Map.fromList
2935 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2936 (Data.List.map fst $
2937 Data.Either.rights $
2938 [P.runParser_with_Error
2939 (Format.Ledger.Read.posting )
2940 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2942 [ (Format.Ledger.posting ("A":|["B", "C"]))
2943 { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"]
2944 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2945 , Format.Ledger.posting_tags = Data.Map.fromList
2951 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2952 (Data.List.map fst $
2953 Data.Either.rights $
2954 [P.runParser_with_Error
2955 (Format.Ledger.Read.posting <* P.eof)
2956 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2958 [ (Format.Ledger.posting ("A":|["B", "C"]))
2959 { Format.Ledger.posting_comments = [" N:V", " N:V2"]
2960 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2961 , Format.Ledger.posting_tags = Data.Map.fromList
2962 [ ("N", ["V", "V2"])
2966 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2967 (Data.List.map fst $
2968 Data.Either.rights $
2969 [P.runParser_with_Error
2970 (Format.Ledger.Read.posting <* P.eof)
2971 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2973 [ (Format.Ledger.posting ("A":|["B", "C"]))
2974 { Format.Ledger.posting_comments = [" N:V", " N2:V"]
2975 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2976 , Format.Ledger.posting_tags = Data.Map.fromList
2982 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2983 (Data.List.map fst $
2984 Data.Either.rights $
2985 [P.runParser_with_Error
2986 (Format.Ledger.Read.posting <* P.eof)
2987 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2989 [ (Format.Ledger.posting ("A":|["B", "C"]))
2990 { Format.Ledger.posting_comments = [" date:2001/01/01"]
2991 , Format.Ledger.posting_dates =
2992 [ Time.zonedTimeToUTC $
2995 (Time.fromGregorian 2001 01 01)
2996 (Time.TimeOfDay 0 0 0))
2999 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3000 , Format.Ledger.posting_tags = Data.Map.fromList
3001 [ ("date", ["2001/01/01"])
3005 , " (A:B:C) = Right (A:B:C)" ~:
3006 (Data.Either.rights $
3007 [P.runParser_with_Error
3008 (Format.Ledger.Read.posting <* P.eof)
3009 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
3011 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
3012 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3014 , Format.Ledger.Posting_Type_Virtual
3017 , " [A:B:C] = Right [A:B:C]" ~:
3018 (Data.Either.rights $
3019 [P.runParser_with_Error
3020 (Format.Ledger.Read.posting <* P.eof)
3021 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
3023 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
3024 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3026 , Format.Ledger.Posting_Type_Virtual_Balanced
3030 , "transaction" ~: TestList
3031 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
3032 (Data.Either.rights $
3033 [P.runParser_with_Error
3034 (Format.Ledger.Read.transaction <* P.eof)
3035 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
3037 [ Format.Ledger.transaction
3038 { Format.Ledger.transaction_dates=
3039 ( Time.zonedTimeToUTC $
3042 (Time.fromGregorian 2000 01 01)
3043 (Time.TimeOfDay 0 0 0))
3046 , Format.Ledger.transaction_description="some description"
3047 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3048 [ (Format.Ledger.posting ("A":|["B", "C"]))
3049 { Format.Ledger.posting_amounts = Data.Map.fromList
3051 { Amount.quantity = 1
3052 , Amount.style = Amount.Style.nil
3053 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3054 , Amount.Style.unit_spaced = Just False
3059 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
3061 , (Format.Ledger.posting ("a":|["b", "c"]))
3062 { Format.Ledger.posting_amounts = Data.Map.fromList
3064 { Amount.quantity = -1
3065 , Amount.style = Amount.Style.nil
3066 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3067 , Amount.Style.unit_spaced = Just False
3072 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
3075 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
3078 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
3079 (Data.Either.rights $
3080 [P.runParser_with_Error
3081 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
3082 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
3084 [ Format.Ledger.transaction
3085 { Format.Ledger.transaction_dates=
3086 ( Time.zonedTimeToUTC $
3089 (Time.fromGregorian 2000 01 01)
3090 (Time.TimeOfDay 0 0 0))
3093 , Format.Ledger.transaction_description="some description"
3094 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3095 [ (Format.Ledger.posting ("A":|["B", "C"]))
3096 { Format.Ledger.posting_amounts = Data.Map.fromList
3098 { Amount.quantity = 1
3099 , Amount.style = Amount.Style.nil
3100 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3101 , Amount.Style.unit_spaced = Just False
3106 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
3108 , (Format.Ledger.posting ("a":|["b", "c"]))
3109 { Format.Ledger.posting_amounts = Data.Map.fromList
3111 { Amount.quantity = -1
3112 , Amount.style = Amount.Style.nil
3113 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3114 , Amount.Style.unit_spaced = Just False
3119 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
3122 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
3125 , "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" ~:
3126 (Data.Either.rights $
3127 [P.runParser_with_Error
3128 (Format.Ledger.Read.transaction <* P.eof)
3129 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description ; some comment\n ; some other;comment\n ; some Tag:\n ; some last comment\n A:B:C $1\n a:b:c"::Text)])
3131 [ Format.Ledger.transaction
3132 { Format.Ledger.transaction_comments_after =
3134 , " some other;comment"
3136 , " some last comment"
3138 , Format.Ledger.transaction_dates=
3139 ( Time.zonedTimeToUTC $
3142 (Time.fromGregorian 2000 01 01)
3143 (Time.TimeOfDay 0 0 0))
3146 , Format.Ledger.transaction_description="some description"
3147 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3148 [ (Format.Ledger.posting ("A":|["B", "C"]))
3149 { Format.Ledger.posting_amounts = Data.Map.fromList
3151 { Amount.quantity = 1
3152 , Amount.style = Amount.Style.nil
3153 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3154 , Amount.Style.unit_spaced = Just False
3159 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
3161 , (Format.Ledger.posting ("a":|["b", "c"]))
3162 { Format.Ledger.posting_amounts = Data.Map.fromList
3164 { Amount.quantity = -1
3165 , Amount.style = Amount.Style.nil
3166 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3167 , Amount.Style.unit_spaced = Just False
3172 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
3175 , Format.Ledger.transaction_tags = Data.Map.fromList
3178 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
3182 , "journal" ~: TestList
3183 [ "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
3185 P.runParserT_with_Error
3186 (Format.Ledger.Read.journal "" {-<* P.eof-})
3187 Format.Ledger.Read.nil_Context "" ("2000/01/01 1° description\n A:B:C $1\n a:b:c\n2000/01/02 2° description\n A:B:C $1\n x:y:z"::Text)
3189 (\j -> j{Format.Ledger.journal_last_read_time=
3190 Format.Ledger.journal_last_read_time Format.Ledger.journal}) $
3191 Data.Either.rights [jnl])
3193 [ Format.Ledger.journal
3194 { Format.Ledger.journal_transactions =
3195 Format.Ledger.transaction_by_Date
3196 [ Format.Ledger.transaction
3197 { Format.Ledger.transaction_dates=
3198 ( Time.zonedTimeToUTC $
3201 (Time.fromGregorian 2000 01 01)
3202 (Time.TimeOfDay 0 0 0))
3205 , Format.Ledger.transaction_description="1° description"
3206 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3207 [ (Format.Ledger.posting ("A":|["B", "C"]))
3208 { Format.Ledger.posting_amounts = Data.Map.fromList
3210 { Amount.quantity = 1
3211 , Amount.style = Amount.Style.nil
3212 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3213 , Amount.Style.unit_spaced = Just False
3218 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
3220 , (Format.Ledger.posting ("a":|["b", "c"]))
3221 { Format.Ledger.posting_amounts = Data.Map.fromList
3223 { Amount.quantity = -1
3224 , Amount.style = Amount.Style.nil
3225 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3226 , Amount.Style.unit_spaced = Just False
3231 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
3234 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
3236 , Format.Ledger.transaction
3237 { Format.Ledger.transaction_dates=
3238 ( Time.zonedTimeToUTC $
3241 (Time.fromGregorian 2000 01 02)
3242 (Time.TimeOfDay 0 0 0))
3245 , Format.Ledger.transaction_description="2° description"
3246 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3247 [ (Format.Ledger.posting ("A":|["B", "C"]))
3248 { Format.Ledger.posting_amounts = Data.Map.fromList
3250 { Amount.quantity = 1
3251 , Amount.style = Amount.Style.nil
3252 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3253 , Amount.Style.unit_spaced = Just False
3258 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
3260 , (Format.Ledger.posting ("x":|["y", "z"]))
3261 { Format.Ledger.posting_amounts = Data.Map.fromList
3263 { Amount.quantity = -1
3264 , Amount.style = Amount.Style.nil
3265 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3266 , Amount.Style.unit_spaced = Just False
3271 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
3274 , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1
3281 , "Write" ~: TestList
3282 [ "account" ~: TestList
3284 ((Format.Ledger.Write.show
3285 Format.Ledger.Write.Style
3286 { Format.Ledger.Write.style_color=False
3287 , Format.Ledger.Write.style_align=True
3289 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
3294 ((Format.Ledger.Write.show
3295 Format.Ledger.Write.Style
3296 { Format.Ledger.Write.style_color=False
3297 , Format.Ledger.Write.style_align=True
3299 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
3304 ((Format.Ledger.Write.show
3305 Format.Ledger.Write.Style
3306 { Format.Ledger.Write.style_color=False
3307 , Format.Ledger.Write.style_align=True
3309 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual $
3314 ((Format.Ledger.Write.show
3315 Format.Ledger.Write.Style
3316 { Format.Ledger.Write.style_color=False
3317 , Format.Ledger.Write.style_align=True
3319 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual_Balanced $
3324 , "amount" ~: TestList
3326 ((Format.Ledger.Write.show
3327 Format.Ledger.Write.Style
3328 { Format.Ledger.Write.style_color=False
3329 , Format.Ledger.Write.style_align=True
3331 Format.Ledger.Write.amount
3336 ((Format.Ledger.Write.show
3337 Format.Ledger.Write.Style
3338 { Format.Ledger.Write.style_color=False
3339 , Format.Ledger.Write.style_align=True
3341 Format.Ledger.Write.amount
3343 { Amount.style = Amount.Style.nil
3344 { Amount.Style.precision = 2 }
3349 ((Format.Ledger.Write.show
3350 Format.Ledger.Write.Style
3351 { Format.Ledger.Write.style_color=False
3352 , Format.Ledger.Write.style_align=True
3354 Format.Ledger.Write.amount
3356 { Amount.quantity = Decimal 0 123
3361 ((Format.Ledger.Write.show
3362 Format.Ledger.Write.Style
3363 { Format.Ledger.Write.style_color=False
3364 , Format.Ledger.Write.style_align=True
3366 Format.Ledger.Write.amount
3368 { Amount.quantity = Decimal 0 (- 123)
3372 , "12.3 @ prec=0" ~:
3373 ((Format.Ledger.Write.show
3374 Format.Ledger.Write.Style
3375 { Format.Ledger.Write.style_color=False
3376 , Format.Ledger.Write.style_align=True
3378 Format.Ledger.Write.amount
3380 { Amount.quantity = Decimal 1 123
3381 , Amount.style = Amount.Style.nil
3382 { Amount.Style.fractioning = Just '.'
3387 , "12.5 @ prec=0" ~:
3388 ((Format.Ledger.Write.show
3389 Format.Ledger.Write.Style
3390 { Format.Ledger.Write.style_color=False
3391 , Format.Ledger.Write.style_align=True
3393 Format.Ledger.Write.amount
3395 { Amount.quantity = Decimal 1 125
3396 , Amount.style = Amount.Style.nil
3397 { Amount.Style.fractioning = Just '.'
3402 , "12.3 @ prec=1" ~:
3403 ((Format.Ledger.Write.show
3404 Format.Ledger.Write.Style
3405 { Format.Ledger.Write.style_color=False
3406 , Format.Ledger.Write.style_align=True
3408 Format.Ledger.Write.amount
3410 { Amount.quantity = Decimal 1 123
3411 , Amount.style = Amount.Style.nil
3412 { Amount.Style.fractioning = Just '.'
3413 , Amount.Style.precision = 1
3418 , "1,234.56 @ prec=2" ~:
3419 ((Format.Ledger.Write.show
3420 Format.Ledger.Write.Style
3421 { Format.Ledger.Write.style_color=False
3422 , Format.Ledger.Write.style_align=True
3424 Format.Ledger.Write.amount
3426 { Amount.quantity = Decimal 2 123456
3427 , Amount.style = Amount.Style.nil
3428 { Amount.Style.fractioning = Just '.'
3429 , Amount.Style.precision = 2
3430 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
3435 , "123,456,789,01,2.3456789 @ prec=7" ~:
3436 ((Format.Ledger.Write.show
3437 Format.Ledger.Write.Style
3438 { Format.Ledger.Write.style_color=False
3439 , Format.Ledger.Write.style_align=True
3441 Format.Ledger.Write.amount
3443 { Amount.quantity = Decimal 7 1234567890123456789
3444 , Amount.style = Amount.Style.nil
3445 { Amount.Style.fractioning = Just '.'
3446 , Amount.Style.precision = 7
3447 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3451 "123,456,789,01,2.3456789")
3452 , "1234567.8,90,123,456,789 @ prec=12" ~:
3453 ((Format.Ledger.Write.show
3454 Format.Ledger.Write.Style
3455 { Format.Ledger.Write.style_color=False
3456 , Format.Ledger.Write.style_align=True
3458 Format.Ledger.Write.amount
3460 { Amount.quantity = Decimal 12 1234567890123456789
3461 , Amount.style = Amount.Style.nil
3462 { Amount.Style.fractioning = Just '.'
3463 , Amount.Style.precision = 12
3464 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3468 "1234567.8,90,123,456,789")
3469 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
3470 ((Format.Ledger.Write.show
3471 Format.Ledger.Write.Style
3472 { Format.Ledger.Write.style_color=False
3473 , Format.Ledger.Write.style_align=True
3475 Format.Ledger.Write.amount
3477 { Amount.quantity = Decimal 7 1234567890123456789
3478 , Amount.style = Amount.Style.nil
3479 { Amount.Style.fractioning = Just '.'
3480 , Amount.Style.precision = 7
3481 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3485 "1,2,3,4,5,6,7,89,012.3456789")
3486 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
3487 ((Format.Ledger.Write.show
3488 Format.Ledger.Write.Style
3489 { Format.Ledger.Write.style_color=False
3490 , Format.Ledger.Write.style_align=True
3492 Format.Ledger.Write.amount
3494 { Amount.quantity = Decimal 12 1234567890123456789
3495 , Amount.style = Amount.Style.nil
3496 { Amount.Style.fractioning = Just '.'
3497 , Amount.Style.precision = 12
3498 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3502 "1234567.890,12,3,4,5,6,7,8,9")
3504 , "amount_length" ~: TestList
3506 ((Format.Ledger.Write.amount_length
3511 ((Format.Ledger.Write.amount_length
3513 { Amount.style = Amount.Style.nil
3514 { Amount.Style.precision = 2 }
3519 ((Format.Ledger.Write.amount_length
3521 { Amount.quantity = Decimal 0 123
3526 ((Format.Ledger.Write.amount_length
3528 { Amount.quantity = Decimal 0 (- 123)
3532 , "12.3 @ prec=0" ~:
3533 ((Format.Ledger.Write.amount_length
3535 { Amount.quantity = Decimal 1 123
3536 , Amount.style = Amount.Style.nil
3537 { Amount.Style.fractioning = Just '.'
3542 , "12.5 @ prec=0" ~:
3543 ((Format.Ledger.Write.amount_length
3545 { Amount.quantity = Decimal 1 125
3546 , Amount.style = Amount.Style.nil
3547 { Amount.Style.fractioning = Just '.'
3552 , "12.3 @ prec=1" ~:
3553 ((Format.Ledger.Write.amount_length
3555 { Amount.quantity = Decimal 1 123
3556 , Amount.style = Amount.Style.nil
3557 { Amount.Style.fractioning = Just '.'
3558 , Amount.Style.precision = 1
3563 , "1,234.56 @ prec=2" ~:
3564 ((Format.Ledger.Write.amount_length
3566 { Amount.quantity = Decimal 2 123456
3567 , Amount.style = Amount.Style.nil
3568 { Amount.Style.fractioning = Just '.'
3569 , Amount.Style.precision = 2
3570 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
3575 , "123,456,789,01,2.3456789 @ prec=7" ~:
3576 ((Format.Ledger.Write.amount_length
3578 { Amount.quantity = Decimal 7 1234567890123456789
3579 , Amount.style = Amount.Style.nil
3580 { Amount.Style.fractioning = Just '.'
3581 , Amount.Style.precision = 7
3582 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3587 , "1234567.8,90,123,456,789 @ prec=12" ~:
3588 ((Format.Ledger.Write.amount_length
3590 { Amount.quantity = Decimal 12 1234567890123456789
3591 , Amount.style = Amount.Style.nil
3592 { Amount.Style.fractioning = Just '.'
3593 , Amount.Style.precision = 12
3594 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3599 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
3600 ((Format.Ledger.Write.amount_length
3602 { Amount.quantity = Decimal 7 1234567890123456789
3603 , Amount.style = Amount.Style.nil
3604 { Amount.Style.fractioning = Just '.'
3605 , Amount.Style.precision = 7
3606 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3611 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
3612 ((Format.Ledger.Write.amount_length
3614 { Amount.quantity = Decimal 12 1234567890123456789
3615 , Amount.style = Amount.Style.nil
3616 { Amount.Style.fractioning = Just '.'
3617 , Amount.Style.precision = 12
3618 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3623 , "1000000.000,00,0,0,0,0,0,0,0 @ prec=12" ~:
3624 ((Format.Ledger.Write.amount_length
3626 { Amount.quantity = Decimal 12 1000000000000000000
3627 , Amount.style = Amount.Style.nil
3628 { Amount.Style.fractioning = Just '.'
3629 , Amount.Style.precision = 12
3630 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3636 ((Format.Ledger.Write.amount_length $
3638 { Amount.quantity = Decimal 0 999
3639 , Amount.style = Amount.Style.nil
3640 { Amount.Style.precision = 0
3645 , "1000 @ prec=0" ~:
3646 ((Format.Ledger.Write.amount_length $
3648 { Amount.quantity = Decimal 0 1000
3649 , Amount.style = Amount.Style.nil
3650 { Amount.Style.precision = 0
3655 , "10,00€ @ prec=2" ~:
3656 ((Format.Ledger.Write.amount_length $ Amount.eur 10)
3660 , "date" ~: TestList
3662 ((Format.Ledger.Write.show
3663 Format.Ledger.Write.Style
3664 { Format.Ledger.Write.style_color=False
3665 , Format.Ledger.Write.style_align=True
3667 Format.Ledger.Write.date
3671 , "2000/01/01 12:34:51 CET" ~:
3672 (Format.Ledger.Write.show
3673 Format.Ledger.Write.Style
3674 { Format.Ledger.Write.style_color=False
3675 , Format.Ledger.Write.style_align=True
3677 Format.Ledger.Write.date $
3678 Time.zonedTimeToUTC $
3681 (Time.fromGregorian 2000 01 01)
3682 (Time.TimeOfDay 12 34 51))
3683 (Time.TimeZone 60 False "CET"))
3685 "2000/01/01 11:34:51"
3686 , "2000/01/01 12:34:51 +0100" ~:
3687 (Format.Ledger.Write.show
3688 Format.Ledger.Write.Style
3689 { Format.Ledger.Write.style_color=False
3690 , Format.Ledger.Write.style_align=True
3692 Format.Ledger.Write.date $
3693 Time.zonedTimeToUTC $
3696 (Time.fromGregorian 2000 01 01)
3697 (Time.TimeOfDay 12 34 51))
3698 (Time.TimeZone 60 False ""))
3700 "2000/01/01 11:34:51"
3701 , "2000/01/01 01:02:03" ~:
3702 (Format.Ledger.Write.show
3703 Format.Ledger.Write.Style
3704 { Format.Ledger.Write.style_color=False
3705 , Format.Ledger.Write.style_align=True
3707 Format.Ledger.Write.date $
3708 Time.zonedTimeToUTC $
3711 (Time.fromGregorian 2000 01 01)
3712 (Time.TimeOfDay 1 2 3))
3715 "2000/01/01 01:02:03"
3717 (Format.Ledger.Write.show
3718 Format.Ledger.Write.Style
3719 { Format.Ledger.Write.style_color=False
3720 , Format.Ledger.Write.style_align=True
3722 Format.Ledger.Write.date $
3723 Time.zonedTimeToUTC $
3726 (Time.fromGregorian 0 01 01)
3727 (Time.TimeOfDay 1 2 0))
3732 (Format.Ledger.Write.show
3733 Format.Ledger.Write.Style
3734 { Format.Ledger.Write.style_color=False
3735 , Format.Ledger.Write.style_align=True
3737 Format.Ledger.Write.date $
3738 Time.zonedTimeToUTC $
3741 (Time.fromGregorian 0 01 01)
3742 (Time.TimeOfDay 1 0 0))
3747 (Format.Ledger.Write.show
3748 Format.Ledger.Write.Style
3749 { Format.Ledger.Write.style_color=False
3750 , Format.Ledger.Write.style_align=True
3752 Format.Ledger.Write.date $
3753 Time.zonedTimeToUTC $
3756 (Time.fromGregorian 0 01 01)
3757 (Time.TimeOfDay 0 1 0))
3762 (Format.Ledger.Write.show
3763 Format.Ledger.Write.Style
3764 { Format.Ledger.Write.style_color=False
3765 , Format.Ledger.Write.style_align=True
3767 Format.Ledger.Write.date $
3768 Time.zonedTimeToUTC $
3771 (Time.fromGregorian 0 01 01)
3772 (Time.TimeOfDay 0 0 0))
3777 , "transaction" ~: TestList
3779 ((Format.Ledger.Write.show
3780 Format.Ledger.Write.Style
3781 { Format.Ledger.Write.style_color=False
3782 , Format.Ledger.Write.style_align=True
3784 Format.Ledger.Write.transaction
3785 Format.Ledger.transaction)
3788 , "2000/01/01 some description\\n\\ta:b:c\\n\\t ; first comment\\n\\t ; second comment\\n\\t ; third comment\\n\\tA:B:C $1" ~:
3789 ((Format.Ledger.Write.show
3790 Format.Ledger.Write.Style
3791 { Format.Ledger.Write.style_color=False
3792 , Format.Ledger.Write.style_align=True
3794 Format.Ledger.Write.transaction $
3795 Format.Ledger.transaction
3796 { Format.Ledger.transaction_dates=
3797 ( Time.zonedTimeToUTC $
3800 (Time.fromGregorian 2000 01 01)
3801 (Time.TimeOfDay 0 0 0))
3804 , Format.Ledger.transaction_description="some description"
3805 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3806 [ (Format.Ledger.posting ("A":|["B", "C"]))
3807 { Format.Ledger.posting_amounts = Data.Map.fromList
3809 { Amount.quantity = 1
3810 , Amount.style = Amount.Style.nil
3811 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3812 , Amount.Style.unit_spaced = Just False
3818 , (Format.Ledger.posting ("a":|["b", "c"]))
3819 { Format.Ledger.posting_comments = ["first comment","second comment","third comment"]
3824 "2000/01/01 some description\n\ta:b:c\n\t ; first comment\n\t ; second comment\n\t ; third comment\n\tA:B:C $1")
3825 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
3826 ((Format.Ledger.Write.show
3827 Format.Ledger.Write.Style
3828 { Format.Ledger.Write.style_color=False
3829 , Format.Ledger.Write.style_align=True
3831 Format.Ledger.Write.transaction $
3832 Format.Ledger.transaction
3833 { Format.Ledger.transaction_dates=
3834 ( Time.zonedTimeToUTC $
3837 (Time.fromGregorian 2000 01 01)
3838 (Time.TimeOfDay 0 0 0))
3841 , Format.Ledger.transaction_description="some description"
3842 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3843 [ (Format.Ledger.posting ("A":|["B", "C"]))
3844 { Format.Ledger.posting_amounts = Data.Map.fromList
3846 { Amount.quantity = 1
3847 , Amount.style = Amount.Style.nil
3848 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3849 , Amount.Style.unit_spaced = Just False
3855 , (Format.Ledger.posting ("AA":|["BB", "CC"]))
3856 { Format.Ledger.posting_amounts = Data.Map.fromList
3858 { Amount.quantity = 123
3859 , Amount.style = Amount.Style.nil
3860 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3861 , Amount.Style.unit_spaced = Just False
3870 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")