1 {-# LANGUAGE TupleSections #-}
2 {-# LANGUAGE OverloadedStrings #-}
6 import Test.Framework.Providers.HUnit (hUnitTestToTests)
7 import Test.Framework.Runners.Console (defaultMain)
9 import Control.Applicative ((<*))
10 import Control.Monad.IO.Class (liftIO)
11 import Data.Decimal (DecimalRaw(..))
12 import qualified Data.Either
13 import qualified Data.List
14 import qualified Data.Map.Strict as Data.Map
15 import Data.Text (Text)
16 import qualified Data.Time.Calendar as Time
17 import qualified Data.Time.LocalTime as Time
18 import qualified Text.Parsec as P
19 import qualified Text.Parsec.Pos as P
20 -- import qualified Text.PrettyPrint.Leijen.Text as PP
22 import qualified Hcompta.Model.Account as Account
23 import qualified Hcompta.Model.Amount as Amount
24 import qualified Hcompta.Model.Amount.Style as Amount.Style
25 import qualified Hcompta.Model.Date as Date
26 import qualified Hcompta.Model.Transaction as Transaction
27 import qualified Hcompta.Model.Transaction.Posting as Posting
28 import qualified Hcompta.Calc.Balance as Calc.Balance
29 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
30 import qualified Hcompta.Format.Ledger.Journal as Format.Ledger.Journal
31 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
33 --instance Eq Text.Parsec.ParseError where
34 -- (==) = const (const False)
37 main = defaultMain $ hUnitTestToTests test_Hcompta
43 [ "Account" ~: TestList
46 (reverse $ Account.fold [] (:) []) ~?= []
48 (reverse $ Account.fold ["A"] (:) []) ~?= [["A"]]
49 , "[A, B] = [[A], [A, B]]" ~:
50 (reverse $ Account.fold ["A", "B"] (:) []) ~?= [["A"], ["A", "B"]]
51 , "[A, B, C] = [[A], [A, B], [A, B, C]]" ~:
52 (reverse $ Account.fold ["A", "B", "C"] (:) []) ~?= [["A"], ["A", "B"], ["A", "B", "C"]]
54 , "ascending" ~: TestList
56 Account.ascending [] ~?= []
58 Account.ascending ["A"] ~?= []
60 Account.ascending ["A", "B"] ~?= ["A"]
61 , "[A, B, C] = [A, B]" ~:
62 Account.ascending ["A", "B", "C"] ~?= ["A", "B"]
65 , "Amount" ~: TestList
70 { Amount.quantity = Decimal 0 1
71 , Amount.style = Amount.Style.nil
72 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
77 { Amount.quantity = Decimal 0 1
78 , Amount.style = Amount.Style.nil
79 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
85 { Amount.quantity = Decimal 0 2
86 , Amount.style = Amount.Style.nil
87 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
92 , "from_List" ~: TestList
93 [ "from_List [$1, 1$] = $2" ~:
96 { Amount.quantity = Decimal 0 1
97 , Amount.style = Amount.Style.nil
98 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
103 { Amount.quantity = Decimal 0 1
104 , Amount.style = Amount.Style.nil
105 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
113 { Amount.quantity = Decimal 0 2
114 , Amount.style = Amount.Style.nil
115 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
124 [ "Balance" ~: TestList
125 [ "posting" ~: TestList
126 [ "[A+$1] = A+$1 & $+1" ~:
127 (Calc.Balance.posting
129 { Posting.account=["A"]
130 , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
135 { Calc.Balance.by_account =
137 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
138 , Calc.Balance.by_unit =
140 Data.List.map Calc.Balance.assoc_by_amount_unit $
141 [ Calc.Balance.Sum_by_Unit
142 { Calc.Balance.amount = Amount.usd $ 1
143 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
148 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
150 (flip Calc.Balance.posting)
153 { Posting.account=["A"]
154 , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
157 { Posting.account=["A"]
158 , Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
163 { Calc.Balance.by_account =
165 [ (["A"], Amount.from_List [ Amount.usd $ 0 ]) ]
166 , Calc.Balance.by_unit =
168 Data.List.map Calc.Balance.assoc_by_amount_unit $
169 [ Calc.Balance.Sum_by_Unit
170 { Calc.Balance.amount = Amount.usd $ 0
171 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
176 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
178 (flip Calc.Balance.posting)
181 { Posting.account=["A"]
182 , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
185 { Posting.account=["A"]
186 , Posting.amounts=Amount.from_List [ Amount.eur $ -1 ]
191 { Calc.Balance.by_account =
193 [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
194 , Calc.Balance.by_unit =
196 Data.List.map Calc.Balance.assoc_by_amount_unit $
197 [ Calc.Balance.Sum_by_Unit
198 { Calc.Balance.amount = Amount.usd $ 1
199 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
202 , Calc.Balance.Sum_by_Unit
203 { Calc.Balance.amount = Amount.eur $ -1
204 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
209 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
211 (flip Calc.Balance.posting)
214 { Posting.account=["A"]
215 , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
218 { Posting.account=["B"]
219 , Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
224 { Calc.Balance.by_account =
226 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
227 , (["B"], Amount.from_List [ Amount.usd $ -1 ])
229 , Calc.Balance.by_unit =
231 Data.List.map Calc.Balance.assoc_by_amount_unit $
232 [ Calc.Balance.Sum_by_Unit
233 { Calc.Balance.amount = Amount.usd $ 0
234 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
239 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
241 (flip Calc.Balance.posting)
244 { Posting.account=["A"]
245 , Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
248 { Posting.account=["A"]
249 , Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
254 { Calc.Balance.by_account =
256 [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
258 , Calc.Balance.by_unit =
260 Data.List.map Calc.Balance.assoc_by_amount_unit $
261 [ Calc.Balance.Sum_by_Unit
262 { Calc.Balance.amount = Amount.usd $ 0
263 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
266 , Calc.Balance.Sum_by_Unit
267 { Calc.Balance.amount = Amount.eur $ 0
268 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
273 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
275 (flip Calc.Balance.posting)
278 { Posting.account=["A"]
279 , Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
282 { Posting.account=["B"]
283 , Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
288 { Calc.Balance.by_account =
290 [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
291 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
293 , Calc.Balance.by_unit =
295 Data.List.map Calc.Balance.assoc_by_amount_unit $
296 [ Calc.Balance.Sum_by_Unit
297 { Calc.Balance.amount = Amount.usd $ 0
298 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
301 , Calc.Balance.Sum_by_Unit
302 { Calc.Balance.amount = Amount.eur $ 0
303 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
306 , Calc.Balance.Sum_by_Unit
307 { Calc.Balance.amount = Amount.gbp $ 0
308 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
314 , "union" ~: TestList
321 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
323 (Calc.Balance.Balance
324 { Calc.Balance.by_account =
326 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
327 , Calc.Balance.by_unit =
329 Data.List.map Calc.Balance.assoc_by_amount_unit $
330 [ Calc.Balance.Sum_by_Unit
331 { Calc.Balance.amount = Amount.usd $ 1
332 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
337 (Calc.Balance.Balance
338 { Calc.Balance.by_account =
340 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
341 , Calc.Balance.by_unit =
343 Data.List.map Calc.Balance.assoc_by_amount_unit $
344 [ Calc.Balance.Sum_by_Unit
345 { Calc.Balance.amount = Amount.usd $ 1
346 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
353 { Calc.Balance.by_account =
355 [ (["A"], Amount.from_List [ Amount.usd $ 2 ]) ]
356 , Calc.Balance.by_unit =
358 Data.List.map Calc.Balance.assoc_by_amount_unit $
359 [ Calc.Balance.Sum_by_Unit
360 { Calc.Balance.amount = Amount.usd $ 2
361 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
366 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
368 (Calc.Balance.Balance
369 { Calc.Balance.by_account =
371 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
372 , Calc.Balance.by_unit =
374 Data.List.map Calc.Balance.assoc_by_amount_unit $
375 [ Calc.Balance.Sum_by_Unit
376 { Calc.Balance.amount = Amount.usd $ 1
377 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
382 (Calc.Balance.Balance
383 { Calc.Balance.by_account =
385 [ (["B"], Amount.from_List [ Amount.usd $ 1 ]) ]
386 , Calc.Balance.by_unit =
388 Data.List.map Calc.Balance.assoc_by_amount_unit $
389 [ Calc.Balance.Sum_by_Unit
390 { Calc.Balance.amount = Amount.usd $ 1
391 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
398 { Calc.Balance.by_account =
400 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
401 , (["B"], Amount.from_List [ Amount.usd $ 1 ]) ]
402 , Calc.Balance.by_unit =
404 Data.List.map Calc.Balance.assoc_by_amount_unit $
405 [ Calc.Balance.Sum_by_Unit
406 { Calc.Balance.amount = Amount.usd $ 2
407 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
412 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
414 (Calc.Balance.Balance
415 { Calc.Balance.by_account =
417 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
418 , Calc.Balance.by_unit =
420 Data.List.map Calc.Balance.assoc_by_amount_unit $
421 [ Calc.Balance.Sum_by_Unit
422 { Calc.Balance.amount = Amount.usd $ 1
423 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
428 (Calc.Balance.Balance
429 { Calc.Balance.by_account =
431 [ (["B"], Amount.from_List [ Amount.eur $ 1 ]) ]
432 , Calc.Balance.by_unit =
434 Data.List.map Calc.Balance.assoc_by_amount_unit $
435 [ Calc.Balance.Sum_by_Unit
436 { Calc.Balance.amount = Amount.eur $ 1
437 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
444 { Calc.Balance.by_account =
446 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
447 , (["B"], Amount.from_List [ Amount.eur $ 1 ]) ]
448 , Calc.Balance.by_unit =
450 Data.List.map Calc.Balance.assoc_by_amount_unit $
451 [ Calc.Balance.Sum_by_Unit
452 { Calc.Balance.amount = Amount.usd $ 1
453 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
456 , Calc.Balance.Sum_by_Unit
457 { Calc.Balance.amount = Amount.eur $ 1
458 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
464 , "expand" ~: TestList
465 [ "nil_By_Account = nil_By_Account" ~:
467 Calc.Balance.nil_By_Account
469 (Calc.Balance.Expanded $
470 Calc.Balance.nil_By_Account)
474 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
476 (Calc.Balance.Expanded $
478 [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
479 , "A/A+$1 = A+$1 A/A+$1" ~:
482 [ (["A", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
484 (Calc.Balance.Expanded $
486 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
487 , (["A", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
488 , "A/B+$1 = A+$1 A/B+$1" ~:
491 [ (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
493 (Calc.Balance.Expanded $
495 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
496 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
497 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
500 [ (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
502 (Calc.Balance.Expanded $
504 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
505 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
506 , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
507 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
510 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
511 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
513 (Calc.Balance.Expanded $
515 [ (["A"], Amount.from_List [ Amount.usd $ 2 ])
516 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
517 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
520 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
521 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
522 , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ])
525 (Calc.Balance.Expanded $
527 [ (["A"], Amount.from_List [ Amount.usd $ 3 ])
528 , (["A", "B"], Amount.from_List [ Amount.usd $ 2 ])
529 , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ])
531 , "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" ~:
534 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
535 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
536 , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ])
537 , (["A", "B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
540 (Calc.Balance.Expanded $
542 [ (["A"], Amount.from_List [ Amount.usd $ 4 ])
543 , (["A", "B"], Amount.from_List [ Amount.usd $ 3 ])
544 , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 2 ])
545 , (["A", "B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
547 , "A+$1 A/B+$1 B/A+$1 = A+$2 A/B+$1 B/A+$1" ~:
550 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
551 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
552 , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
554 (Calc.Balance.Expanded $
556 [ (["A"], Amount.from_List [ Amount.usd $ 2 ])
557 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
558 , (["B"], Amount.from_List [ Amount.usd $ 1 ])
559 , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
560 , "A+$1 A/B+$1 B/A+$1 = A+$2 A/B+$1 B/A+$1" ~:
563 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
564 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
565 , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
567 (Calc.Balance.Expanded $
569 [ (["A"], Amount.from_List [ Amount.usd $ 2 ])
570 , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
571 , (["B"], Amount.from_List [ Amount.usd $ 1 ])
572 , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
574 , "is_equilibrated" ~: TestList
575 [ "nil = True" ~: TestCase $
577 Calc.Balance.is_equilibrated $
579 , "{A+$0, $+0} = True" ~: TestCase $
581 Calc.Balance.is_equilibrated $
583 { Calc.Balance.by_account =
585 [ (["A"], Amount.from_List [ Amount.usd $ 0 ])
587 , Calc.Balance.by_unit =
589 Data.List.map Calc.Balance.assoc_by_amount_unit $
590 [ Calc.Balance.Sum_by_Unit
591 { Calc.Balance.amount = Amount.usd $ 0
592 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
597 , "{A+$1, $+1} = False" ~: TestCase $
599 Calc.Balance.is_equilibrated $
601 { Calc.Balance.by_account =
603 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
605 , Calc.Balance.by_unit =
607 Data.List.map Calc.Balance.assoc_by_amount_unit $
608 [ Calc.Balance.Sum_by_Unit
609 { Calc.Balance.amount = Amount.usd $ 1
610 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
615 , "{A+$0+€0, $0 €+0} = True" ~: TestCase $
617 Calc.Balance.is_equilibrated $
619 { Calc.Balance.by_account =
621 [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
623 , Calc.Balance.by_unit =
625 Data.List.map Calc.Balance.assoc_by_amount_unit $
626 [ Calc.Balance.Sum_by_Unit
627 { Calc.Balance.amount = Amount.usd $ 0
628 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
631 , Calc.Balance.Sum_by_Unit
632 { Calc.Balance.amount = Amount.eur $ 0
633 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
638 , "{A+$1, B-$1, $+0} = True" ~: TestCase $
640 Calc.Balance.is_equilibrated $
642 { Calc.Balance.by_account =
644 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
645 , (["B"], Amount.from_List [ Amount.usd $ -1 ])
647 , Calc.Balance.by_unit =
649 Data.List.map Calc.Balance.assoc_by_amount_unit $
650 [ Calc.Balance.Sum_by_Unit
651 { Calc.Balance.amount = Amount.usd $ 0
652 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
657 , "{A+$1 B, $+1} = True" ~: TestCase $
659 Calc.Balance.is_equilibrated $
661 { Calc.Balance.by_account =
663 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
664 , (["B"], Amount.from_List [])
666 , Calc.Balance.by_unit =
668 Data.List.map Calc.Balance.assoc_by_amount_unit $
669 [ Calc.Balance.Sum_by_Unit
670 { Calc.Balance.amount = Amount.usd $ 1
671 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
676 , "{A+$1 B+€1, $+1 €+1} = True" ~: TestCase $
678 Calc.Balance.is_equilibrated $
680 { Calc.Balance.by_account =
682 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
683 , (["B"], Amount.from_List [ Amount.eur $ 1 ])
685 , Calc.Balance.by_unit =
687 Data.List.map Calc.Balance.assoc_by_amount_unit $
688 [ Calc.Balance.Sum_by_Unit
689 { Calc.Balance.amount = Amount.usd $ 1
690 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
693 , Calc.Balance.Sum_by_Unit
694 { Calc.Balance.amount = Amount.eur $ 1
695 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
700 , "{A+$1 B-$1+€1, $+0 €+1} = True" ~: TestCase $
702 Calc.Balance.is_equilibrated $
704 { Calc.Balance.by_account =
706 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
707 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
709 , Calc.Balance.by_unit =
711 Data.List.map Calc.Balance.assoc_by_amount_unit $
712 [ Calc.Balance.Sum_by_Unit
713 { Calc.Balance.amount = Amount.usd $ 0
714 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
717 , Calc.Balance.Sum_by_Unit
718 { Calc.Balance.amount = Amount.eur $ 1
719 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
724 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0} = True" ~: TestCase $
726 Calc.Balance.is_equilibrated $
728 { Calc.Balance.by_account =
730 [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
731 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
733 , Calc.Balance.by_unit =
735 Data.List.map Calc.Balance.assoc_by_amount_unit $
736 [ Calc.Balance.Sum_by_Unit
737 { Calc.Balance.amount = Amount.usd $ 0
738 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
741 , Calc.Balance.Sum_by_Unit
742 { Calc.Balance.amount = Amount.eur $ 0
743 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
746 , Calc.Balance.Sum_by_Unit
747 { Calc.Balance.amount = Amount.gbp $ 0
748 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
756 , "Format" ~: TestList
757 [ "Ledger" ~: TestList
759 [ "account_name" ~: TestList
761 (Data.Either.rights $
763 (Format.Ledger.Read.account_name <* P.eof)
767 , "\"A\" = Right \"A\"" ~:
768 (Data.Either.rights $
770 (Format.Ledger.Read.account_name <* P.eof)
774 , "\"AA\" = Right \"AA\"" ~:
775 (Data.Either.rights $
777 (Format.Ledger.Read.account_name <* P.eof)
782 (Data.Either.rights $
784 (Format.Ledger.Read.account_name <* P.eof)
789 (Data.Either.rights $
791 (Format.Ledger.Read.account_name <* P.eof)
796 (Data.Either.rights $
798 (Format.Ledger.Read.account_name <* P.eof)
803 (Data.Either.rights $
805 (Format.Ledger.Read.account_name <* P.eof)
810 (Data.Either.rights $
812 (Format.Ledger.Read.account_name <* P.eof)
816 , "\"A \" ^= Right" ~:
817 (Data.Either.rights $
819 (Format.Ledger.Read.account_name)
823 , "\"A A\" = Right \"A A\"" ~:
824 (Data.Either.rights $
826 (Format.Ledger.Read.account_name <* P.eof)
827 () "" ("A A"::Text)])
831 (Data.Either.rights $
833 (Format.Ledger.Read.account_name <* P.eof)
837 , "\"A \\n\" = Left" ~:
838 (Data.Either.rights $
840 (Format.Ledger.Read.account_name <* P.eof)
841 () "" ("A \n"::Text)])
844 , "\"(A)A\" = Right \"(A)A\"" ~:
845 (Data.Either.rights $
847 (Format.Ledger.Read.account_name <* P.eof)
848 () "" ("(A)A"::Text)])
851 , "\"( )A\" = Right \"( )A\"" ~:
852 (Data.Either.rights $
854 (Format.Ledger.Read.account_name <* P.eof)
855 () "" ("( )A"::Text)])
858 , "\"(A) A\" = Right \"(A) A\"" ~:
859 (Data.Either.rights $
861 (Format.Ledger.Read.account_name <* P.eof)
862 () "" ("(A) A"::Text)])
865 , "\"[ ]A\" = Right \"[ ]A\"" ~:
866 (Data.Either.rights $
868 (Format.Ledger.Read.account_name <* P.eof)
869 () "" ("[ ]A"::Text)])
872 , "\"(A) \" = Left" ~:
873 (Data.Either.rights $
875 (Format.Ledger.Read.account_name <* P.eof)
876 () "" ("(A) "::Text)])
879 , "\"(A)\" = Left" ~:
880 (Data.Either.rights $
882 (Format.Ledger.Read.account_name <* P.eof)
883 () "" ("(A)"::Text)])
886 , "\"[A]A\" = Right \"(A)A\"" ~:
887 (Data.Either.rights $
889 (Format.Ledger.Read.account_name <* P.eof)
890 () "" ("[A]A"::Text)])
893 , "\"[A] A\" = Right \"[A] A\"" ~:
894 (Data.Either.rights $
896 (Format.Ledger.Read.account_name <* P.eof)
897 () "" ("[A] A"::Text)])
900 , "\"[A] \" = Left" ~:
901 (Data.Either.rights $
903 (Format.Ledger.Read.account_name <* P.eof)
904 () "" ("[A] "::Text)])
907 , "\"[A]\" = Left" ~:
908 (Data.Either.rights $
910 (Format.Ledger.Read.account_name <* P.eof)
911 () "" ("[A]"::Text)])
915 , "account" ~: TestList
917 (Data.Either.rights $
919 (Format.Ledger.Read.account <* P.eof)
923 , "\"A\" = Right [\"A\"]" ~:
924 (Data.Either.rights $
926 (Format.Ledger.Read.account <* P.eof)
931 (Data.Either.rights $
933 (Format.Ledger.Read.account <* P.eof)
938 (Data.Either.rights $
940 (Format.Ledger.Read.account <* P.eof)
945 (Data.Either.rights $
947 (Format.Ledger.Read.account <* P.eof)
952 (Data.Either.rights $
954 (Format.Ledger.Read.account <* P.eof)
958 , "\"A:B\" = Right [\"A\", \"B\"]" ~:
959 (Data.Either.rights $
961 (Format.Ledger.Read.account <* P.eof)
962 () "" ("A:B"::Text)])
965 , "\"A:B:C\" = Right [\"A\", \"B\", \"C\"]" ~:
966 (Data.Either.rights $
968 (Format.Ledger.Read.account <* P.eof)
969 () "" ("A:B:C"::Text)])
972 , "\"Aa:Bbb:Cccc\" = Right [\"Aa\", \"Bbb\", \":Cccc\"]" ~:
973 (Data.Either.rights $
975 (Format.Ledger.Read.account <* P.eof)
976 () "" ("Aa:Bbb:Cccc"::Text)])
978 [["Aa", "Bbb", "Cccc"]]
979 , "\"A a : B b b : C c c c\" = Right [\"A a \", \" B b b \", \": C c c c\"]" ~:
980 (Data.Either.rights $
982 (Format.Ledger.Read.account <* P.eof)
983 () "" ("A a : B b b : C c c c"::Text)])
985 [["A a ", " B b b ", " C c c c"]]
986 , "\"A: :C\" = Right [\"A\", \" \", \"C\"]" ~:
987 (Data.Either.rights $
989 (Format.Ledger.Read.account <* P.eof)
990 () "" ("A: :C"::Text)])
993 , "\"A::C\" = Left" ~:
994 (Data.Either.rights $
996 (Format.Ledger.Read.account <* P.eof)
997 () "" ("A::C"::Text)])
1001 , "amount" ~: TestList
1003 (Data.Either.rights $
1005 (Format.Ledger.Read.amount <* P.eof)
1009 , "\"0\" = Right 0" ~:
1010 (Data.Either.rights $
1012 (Format.Ledger.Read.amount <* P.eof)
1016 { Amount.quantity = Decimal 0 0
1018 , "\"00\" = Right 0" ~:
1019 (Data.Either.rights $
1021 (Format.Ledger.Read.amount <* P.eof)
1022 () "" ("00"::Text)])
1025 { Amount.quantity = Decimal 0 0
1027 , "\"0.\" = Right 0." ~:
1028 (Data.Either.rights $
1030 (Format.Ledger.Read.amount <* P.eof)
1031 () "" ("0."::Text)])
1034 { Amount.quantity = Decimal 0 0
1037 { Amount.Style.fractioning = Just '.'
1040 , "\".0\" = Right 0.0" ~:
1041 (Data.Either.rights $
1043 (Format.Ledger.Read.amount <* P.eof)
1044 () "" (".0"::Text)])
1047 { Amount.quantity = Decimal 0 0
1050 { Amount.Style.fractioning = Just '.'
1051 , Amount.Style.precision = 1
1054 , "\"0,\" = Right 0," ~:
1055 (Data.Either.rights $
1057 (Format.Ledger.Read.amount <* P.eof)
1058 () "" ("0,"::Text)])
1061 { Amount.quantity = Decimal 0 0
1064 { Amount.Style.fractioning = Just ','
1067 , "\",0\" = Right 0,0" ~:
1068 (Data.Either.rights $
1070 (Format.Ledger.Read.amount <* P.eof)
1071 () "" (",0"::Text)])
1074 { Amount.quantity = Decimal 0 0
1077 { Amount.Style.fractioning = Just ','
1078 , Amount.Style.precision = 1
1081 , "\"0_\" = Left" ~:
1082 (Data.Either.rights $
1084 (Format.Ledger.Read.amount <* P.eof)
1085 () "" ("0_"::Text)])
1088 , "\"_0\" = Left" ~:
1089 (Data.Either.rights $
1091 (Format.Ledger.Read.amount <* P.eof)
1092 () "" ("_0"::Text)])
1095 , "\"0.0\" = Right 0.0" ~:
1096 (Data.Either.rights $
1098 (Format.Ledger.Read.amount <* P.eof)
1099 () "" ("0.0"::Text)])
1102 { Amount.quantity = Decimal 0 0
1105 { Amount.Style.fractioning = Just '.'
1106 , Amount.Style.precision = 1
1109 , "\"00.00\" = Right 0.00" ~:
1110 (Data.Either.rights $
1112 (Format.Ledger.Read.amount <* P.eof)
1113 () "" ("00.00"::Text)])
1116 { Amount.quantity = Decimal 0 0
1119 { Amount.Style.fractioning = Just '.'
1120 , Amount.Style.precision = 2
1123 , "\"0,0\" = Right 0,0" ~:
1124 (Data.Either.rights $
1126 (Format.Ledger.Read.amount <* P.eof)
1127 () "" ("0,0"::Text)])
1130 { Amount.quantity = Decimal 0 0
1133 { Amount.Style.fractioning = Just ','
1134 , Amount.Style.precision = 1
1137 , "\"00,00\" = Right 0,00" ~:
1138 (Data.Either.rights $
1140 (Format.Ledger.Read.amount <* P.eof)
1141 () "" ("00,00"::Text)])
1144 { Amount.quantity = Decimal 0 0
1147 { Amount.Style.fractioning = Just ','
1148 , Amount.Style.precision = 2
1151 , "\"0_0\" = Right 0" ~:
1152 (Data.Either.rights $
1154 (Format.Ledger.Read.amount <* P.eof)
1155 () "" ("0_0"::Text)])
1158 { Amount.quantity = Decimal 0 0
1161 { Amount.Style.fractioning = Nothing
1162 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1163 , Amount.Style.precision = 0
1166 , "\"00_00\" = Right 0" ~:
1167 (Data.Either.rights $
1169 (Format.Ledger.Read.amount <* P.eof)
1170 () "" ("00_00"::Text)])
1173 { Amount.quantity = Decimal 0 0
1176 { Amount.Style.fractioning = Nothing
1177 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1178 , Amount.Style.precision = 0
1181 , "\"0,000.00\" = Right 0,000.00" ~:
1182 (Data.Either.rights $
1184 (Format.Ledger.Read.amount <* P.eof)
1185 () "" ("0,000.00"::Text)])
1188 { Amount.quantity = Decimal 0 0
1191 { Amount.Style.fractioning = Just '.'
1192 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1193 , Amount.Style.precision = 2
1196 , "\"0.000,00\" = Right 0.000,00" ~:
1197 (Data.Either.rights $
1199 (Format.Ledger.Read.amount)
1200 () "" ("0.000,00"::Text)])
1203 { Amount.quantity = Decimal 0 0
1206 { Amount.Style.fractioning = Just ','
1207 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1208 , Amount.Style.precision = 2
1211 , "\"1,000.00\" = Right 1,000.00" ~:
1212 (Data.Either.rights $
1214 (Format.Ledger.Read.amount <* P.eof)
1215 () "" ("1,000.00"::Text)])
1218 { Amount.quantity = Decimal 0 1000
1221 { Amount.Style.fractioning = Just '.'
1222 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1223 , Amount.Style.precision = 2
1226 , "\"1.000,00\" = Right 1.000,00" ~:
1227 (Data.Either.rights $
1229 (Format.Ledger.Read.amount)
1230 () "" ("1.000,00"::Text)])
1233 { Amount.quantity = Decimal 0 1000
1236 { Amount.Style.fractioning = Just ','
1237 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1238 , Amount.Style.precision = 2
1241 , "\"1,000.00.\" = Left" ~:
1242 (Data.Either.rights $
1244 (Format.Ledger.Read.amount)
1245 () "" ("1,000.00."::Text)])
1248 , "\"1.000,00,\" = Left" ~:
1249 (Data.Either.rights $
1251 (Format.Ledger.Read.amount)
1252 () "" ("1.000,00,"::Text)])
1255 , "\"1,000.00_\" = Left" ~:
1256 (Data.Either.rights $
1258 (Format.Ledger.Read.amount)
1259 () "" ("1,000.00_"::Text)])
1262 , "\"12\" = Right 12" ~:
1263 (Data.Either.rights $
1265 (Format.Ledger.Read.amount <* P.eof)
1266 () "" ("123"::Text)])
1269 { Amount.quantity = Decimal 0 123
1271 , "\"1.2\" = Right 1.2" ~:
1272 (Data.Either.rights $
1274 (Format.Ledger.Read.amount <* P.eof)
1275 () "" ("1.2"::Text)])
1278 { Amount.quantity = Decimal 1 12
1281 { Amount.Style.fractioning = Just '.'
1282 , Amount.Style.precision = 1
1285 , "\"1,2\" = Right 1,2" ~:
1286 (Data.Either.rights $
1288 (Format.Ledger.Read.amount <* P.eof)
1289 () "" ("1,2"::Text)])
1292 { Amount.quantity = Decimal 1 12
1295 { Amount.Style.fractioning = Just ','
1296 , Amount.Style.precision = 1
1299 , "\"12.23\" = Right 12.23" ~:
1300 (Data.Either.rights $
1302 (Format.Ledger.Read.amount <* P.eof)
1303 () "" ("12.34"::Text)])
1306 { Amount.quantity = Decimal 2 1234
1309 { Amount.Style.fractioning = Just '.'
1310 , Amount.Style.precision = 2
1313 , "\"12,23\" = Right 12,23" ~:
1314 (Data.Either.rights $
1316 (Format.Ledger.Read.amount <* P.eof)
1317 () "" ("12,34"::Text)])
1320 { Amount.quantity = Decimal 2 1234
1323 { Amount.Style.fractioning = Just ','
1324 , Amount.Style.precision = 2
1327 , "\"1_2\" = Right 1_2" ~:
1328 (Data.Either.rights $
1330 (Format.Ledger.Read.amount <* P.eof)
1331 () "" ("1_2"::Text)])
1334 { Amount.quantity = Decimal 0 12
1337 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1338 , Amount.Style.precision = 0
1341 , "\"1_23\" = Right 1_23" ~:
1342 (Data.Either.rights $
1344 (Format.Ledger.Read.amount <* P.eof)
1345 () "" ("1_23"::Text)])
1348 { Amount.quantity = Decimal 0 123
1351 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1352 , Amount.Style.precision = 0
1355 , "\"1_23_456\" = Right 1_23_456" ~:
1356 (Data.Either.rights $
1358 (Format.Ledger.Read.amount <* P.eof)
1359 () "" ("1_23_456"::Text)])
1362 { Amount.quantity = Decimal 0 123456
1365 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1366 , Amount.Style.precision = 0
1369 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1370 (Data.Either.rights $
1372 (Format.Ledger.Read.amount <* P.eof)
1373 () "" ("1_23_456.7890_12345_678901"::Text)])
1376 { Amount.quantity = Decimal 15 123456789012345678901
1379 { Amount.Style.fractioning = Just '.'
1380 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1381 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1382 , Amount.Style.precision = 15
1385 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1386 (Data.Either.rights $
1388 (Format.Ledger.Read.amount <* P.eof)
1389 () "" ("123456_78901_2345.678_90_1"::Text)])
1392 { Amount.quantity = Decimal 6 123456789012345678901
1395 { Amount.Style.fractioning = Just '.'
1396 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1397 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1398 , Amount.Style.precision = 6
1401 , "\"$1\" = Right $1" ~:
1402 (Data.Either.rights $
1404 (Format.Ledger.Read.amount <* P.eof)
1405 () "" ("$1"::Text)])
1408 { Amount.quantity = Decimal 0 1
1411 { Amount.Style.fractioning = Nothing
1412 , Amount.Style.grouping_integral = Nothing
1413 , Amount.Style.grouping_fractional = Nothing
1414 , Amount.Style.precision = 0
1415 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1416 , Amount.Style.unit_spaced = Just False
1420 , "\"1$\" = Right 1$" ~:
1421 (Data.Either.rights $
1423 (Format.Ledger.Read.amount <* P.eof)
1424 () "" ("1$"::Text)])
1427 { Amount.quantity = Decimal 0 1
1430 { Amount.Style.fractioning = Nothing
1431 , Amount.Style.grouping_integral = Nothing
1432 , Amount.Style.grouping_fractional = Nothing
1433 , Amount.Style.precision = 0
1434 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1435 , Amount.Style.unit_spaced = Just False
1439 , "\"$ 1\" = Right $ 1" ~:
1440 (Data.Either.rights $
1442 (Format.Ledger.Read.amount <* P.eof)
1443 () "" ("$ 1"::Text)])
1446 { Amount.quantity = Decimal 0 1
1449 { Amount.Style.fractioning = Nothing
1450 , Amount.Style.grouping_integral = Nothing
1451 , Amount.Style.grouping_fractional = Nothing
1452 , Amount.Style.precision = 0
1453 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1454 , Amount.Style.unit_spaced = Just True
1458 , "\"1 $\" = Right 1 $" ~:
1459 (Data.Either.rights $
1461 (Format.Ledger.Read.amount <* P.eof)
1462 () "" ("1 $"::Text)])
1465 { Amount.quantity = Decimal 0 1
1468 { Amount.Style.fractioning = Nothing
1469 , Amount.Style.grouping_integral = Nothing
1470 , Amount.Style.grouping_fractional = Nothing
1471 , Amount.Style.precision = 0
1472 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1473 , Amount.Style.unit_spaced = Just True
1477 , "\"-$1\" = Right $-1" ~:
1478 (Data.Either.rights $
1480 (Format.Ledger.Read.amount <* P.eof)
1481 () "" ("-$1"::Text)])
1484 { Amount.quantity = Decimal 0 (-1)
1487 { Amount.Style.fractioning = Nothing
1488 , Amount.Style.grouping_integral = Nothing
1489 , Amount.Style.grouping_fractional = Nothing
1490 , Amount.Style.precision = 0
1491 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1492 , Amount.Style.unit_spaced = Just False
1496 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1497 (Data.Either.rights $
1499 (Format.Ledger.Read.amount <* P.eof)
1500 () "" ("\"4 2\"1"::Text)])
1503 { Amount.quantity = Decimal 0 1
1506 { Amount.Style.fractioning = Nothing
1507 , Amount.Style.grouping_integral = Nothing
1508 , Amount.Style.grouping_fractional = Nothing
1509 , Amount.Style.precision = 0
1510 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1511 , Amount.Style.unit_spaced = Just False
1513 , Amount.unit = "4 2"
1515 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1516 (Data.Either.rights $
1518 (Format.Ledger.Read.amount <* P.eof)
1519 () "" ("1\"4 2\""::Text)])
1522 { Amount.quantity = Decimal 0 1
1525 { Amount.Style.fractioning = Nothing
1526 , Amount.Style.grouping_integral = Nothing
1527 , Amount.Style.grouping_fractional = Nothing
1528 , Amount.Style.precision = 0
1529 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1530 , Amount.Style.unit_spaced = Just False
1532 , Amount.unit = "4 2"
1534 , "\"$1.000,00\" = Right $1.000,00" ~:
1535 (Data.Either.rights $
1537 (Format.Ledger.Read.amount <* P.eof)
1538 () "" ("$1.000,00"::Text)])
1541 { Amount.quantity = Decimal 0 1000
1544 { Amount.Style.fractioning = Just ','
1545 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1546 , Amount.Style.grouping_fractional = Nothing
1547 , Amount.Style.precision = 2
1548 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1549 , Amount.Style.unit_spaced = Just False
1553 , "\"1.000,00$\" = Right 1.000,00$" ~:
1554 (Data.Either.rights $
1556 (Format.Ledger.Read.amount <* P.eof)
1557 () "" ("1.000,00$"::Text)])
1560 { Amount.quantity = Decimal 0 1000
1563 { Amount.Style.fractioning = Just ','
1564 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1565 , Amount.Style.grouping_fractional = Nothing
1566 , Amount.Style.precision = 2
1567 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1568 , Amount.Style.unit_spaced = Just False
1573 , "comment" ~: TestList
1574 [ "; some comment = Right \" some comment\"" ~:
1575 (Data.Either.rights $
1577 (Format.Ledger.Read.comment <* P.eof)
1578 () "" ("; some comment"::Text)])
1581 , "; some comment \\n = Right \" some comment \"" ~:
1582 (Data.Either.rights $
1584 (Format.Ledger.Read.comment <* P.newline <* P.eof)
1585 () "" ("; some comment \n"::Text)])
1587 [ " some comment " ]
1588 , "; some comment \\r\\n = Right \" some comment \"" ~:
1589 (Data.Either.rights $
1591 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
1592 () "" ("; some comment \r\n"::Text)])
1594 [ " some comment " ]
1596 , "comments" ~: TestList
1597 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
1598 (Data.Either.rights $
1600 (Format.Ledger.Read.comments <* P.eof)
1601 () "" ("; some comment\n ; some other comment"::Text)])
1603 [ [" some comment", " some other comment"] ]
1604 , "; some comment \\n = Right \" some comment \"" ~:
1605 (Data.Either.rights $
1607 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
1608 () "" ("; some comment \n"::Text)])
1610 [ [" some comment "] ]
1612 , "date" ~: TestList
1613 [ "2000/01/01 = Right 2000/01/01" ~:
1614 (Data.Either.rights $
1616 (Format.Ledger.Read.date Nothing <* P.eof)
1617 () "" ("2000/01/01"::Text)])
1621 (Time.fromGregorian 2000 01 01)
1622 (Time.TimeOfDay 0 0 0))
1624 , "2000/01/01 some text = Right 2000/01/01" ~:
1625 (Data.Either.rights $
1627 (Format.Ledger.Read.date Nothing)
1628 () "" ("2000/01/01 some text"::Text)])
1632 (Time.fromGregorian 2000 01 01)
1633 (Time.TimeOfDay 0 0 0))
1635 , "2000/01/01 12:34 = Right 2000/01/01 12:34" ~:
1636 (Data.Either.rights $
1638 (Format.Ledger.Read.date Nothing <* P.eof)
1639 () "" ("2000/01/01 12:34"::Text)])
1643 (Time.fromGregorian 2000 01 01)
1644 (Time.TimeOfDay 12 34 0))
1646 , "2000/01/01 12:34:56 = Right 2000/01/01 12:34:56" ~:
1647 (Data.Either.rights $
1649 (Format.Ledger.Read.date Nothing <* P.eof)
1650 () "" ("2000/01/01 12:34:56"::Text)])
1654 (Time.fromGregorian 2000 01 01)
1655 (Time.TimeOfDay 12 34 56))
1657 , "2000/01/01 12:34 CET = Right 2000/01/01 12:34 CET" ~:
1658 (Data.Either.rights $
1660 (Format.Ledger.Read.date Nothing <* P.eof)
1661 () "" ("2000/01/01 12:34 CET"::Text)])
1665 (Time.fromGregorian 2000 01 01)
1666 (Time.TimeOfDay 12 34 0))
1667 (Time.TimeZone 60 True "CET")]
1668 , "2000/01/01 12:34 +0130 = Right 2000/01/01 12:34 +0130" ~:
1669 (Data.Either.rights $
1671 (Format.Ledger.Read.date Nothing <* P.eof)
1672 () "" ("2000/01/01 12:34 +0130"::Text)])
1676 (Time.fromGregorian 2000 01 01)
1677 (Time.TimeOfDay 12 34 0))
1678 (Time.TimeZone 90 False "+0130")]
1679 , "2000/01/01 12:34:56 CET = Right 2000/01/01 12:34:56 CET" ~:
1680 (Data.Either.rights $
1682 (Format.Ledger.Read.date Nothing <* P.eof)
1683 () "" ("2000/01/01 12:34:56 CET"::Text)])
1687 (Time.fromGregorian 2000 01 01)
1688 (Time.TimeOfDay 12 34 56))
1689 (Time.TimeZone 60 True "CET")]
1690 , "2001/02/29 = Left" ~:
1691 (Data.Either.rights $
1693 (Format.Ledger.Read.date Nothing <* P.eof)
1694 () "" ("2001/02/29"::Text)])
1697 , "01/01 = Right default_year/01/01" ~:
1698 (Data.Either.rights $
1700 (Format.Ledger.Read.date (Just 2000) <* P.eof)
1701 () "" ("01/01"::Text)])
1705 (Time.fromGregorian 2000 01 01)
1706 (Time.TimeOfDay 0 0 0))
1710 [ "Name: = Right Name:" ~:
1711 (Data.Either.rights $
1713 (Format.Ledger.Read.tag <* P.eof)
1714 () "" ("Name:"::Text)])
1717 , "Name:Value = Right Name:Value" ~:
1718 (Data.Either.rights $
1720 (Format.Ledger.Read.tag <* P.eof)
1721 () "" ("Name:Value"::Text)])
1724 , "Name:Val ue = Right Name:Val ue" ~:
1725 (Data.Either.rights $
1727 (Format.Ledger.Read.tag <* P.eof)
1728 () "" ("Name:Val ue"::Text)])
1730 [("Name", "Val ue")]
1732 , "tags" ~: TestList
1733 [ "Name: = Right Name:" ~:
1734 (Data.Either.rights $
1736 (Format.Ledger.Read.tags <* P.eof)
1737 () "" ("Name:"::Text)])
1743 , "Name:, = Right Name:" ~:
1744 (Data.Either.rights $
1746 (Format.Ledger.Read.tags <* P.char ',' <* P.eof)
1747 () "" ("Name:,"::Text)])
1753 , "Name:,Name: = Right Name:,Name:" ~:
1754 (Data.Either.rights $
1756 (Format.Ledger.Read.tags <* P.eof)
1757 () "" ("Name:,Name:"::Text)])
1760 [ ("Name", ["", ""])
1763 , "Name:,Name2: = Right Name:,Name2:" ~:
1764 (Data.Either.rights $
1766 (Format.Ledger.Read.tags <* P.eof)
1767 () "" ("Name:,Name2:"::Text)])
1774 , "Name: , Name2: = Right Name: ,Name2:" ~:
1775 (Data.Either.rights $
1777 (Format.Ledger.Read.tags <* P.eof)
1778 () "" ("Name: , Name2:"::Text)])
1785 , "Name:,Name2:,Name3: = Right Name:,Name2:,Name3:" ~:
1786 (Data.Either.rights $
1788 (Format.Ledger.Read.tags <* P.eof)
1789 () "" ("Name:,Name2:,Name3:"::Text)])
1797 , "Name:Val ue,Name2:V a l u e,Name3:V al ue = Right Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
1798 (Data.Either.rights $
1800 (Format.Ledger.Read.tags <* P.eof)
1801 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
1804 [ ("Name", ["Val ue"])
1805 , ("Name2", ["V a l u e"])
1806 , ("Name3", ["V al ue"])
1810 , "posting" ~: TestList
1811 [ " A:B:C = Right A:B:C" ~:
1812 (Data.Either.rights $
1814 (Format.Ledger.Read.posting <* P.eof)
1815 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
1818 { Posting.account = ["A","B","C"]
1819 , Posting.sourcepos = P.newPos "" 1 1
1821 , Posting.Type_Regular
1824 , " !A:B:C = Right !A:B:C" ~:
1825 (Data.List.map fst $
1826 Data.Either.rights $
1828 (Format.Ledger.Read.posting <* P.eof)
1829 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
1832 { Posting.account = ["A","B","C"]
1833 , Posting.sourcepos = P.newPos "" 1 1
1834 , Posting.status = True
1837 , " *A:B:C = Right *A:B:C" ~:
1838 (Data.List.map fst $
1839 Data.Either.rights $
1841 (Format.Ledger.Read.posting <* P.eof)
1842 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
1845 { Posting.account = ["A","B","C"]
1846 , Posting.amounts = Data.Map.fromList []
1847 , Posting.comments = []
1848 , Posting.dates = []
1849 , Posting.status = True
1850 , Posting.sourcepos = P.newPos "" 1 1
1851 , Posting.tags = Data.Map.fromList []
1854 , " A:B:C $1 = Right A:B:C $1" ~:
1855 (Data.List.map fst $
1856 Data.Either.rights $
1858 (Format.Ledger.Read.posting <* P.eof)
1859 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1862 { Posting.account = ["A","B","C $1"]
1863 , Posting.sourcepos = P.newPos "" 1 1
1866 , " A:B:C $1 = Right A:B:C $1" ~:
1867 (Data.List.map fst $
1868 Data.Either.rights $
1870 (Format.Ledger.Read.posting <* P.eof)
1871 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1874 { Posting.account = ["A","B","C"]
1875 , Posting.amounts = Data.Map.fromList
1877 { Amount.quantity = 1
1878 , Amount.style = Amount.Style.nil
1879 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1880 , Amount.Style.unit_spaced = Just False
1885 , Posting.sourcepos = P.newPos "" 1 1
1888 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
1889 (Data.List.map fst $
1890 Data.Either.rights $
1892 (Format.Ledger.Read.posting <* P.eof)
1893 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
1896 { Posting.account = ["A","B","C"]
1897 , Posting.amounts = Data.Map.fromList
1899 { Amount.quantity = 1
1900 , Amount.style = Amount.Style.nil
1901 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1902 , Amount.Style.unit_spaced = Just False
1907 { Amount.quantity = 1
1908 , Amount.style = Amount.Style.nil
1909 { Amount.Style.unit_side = Just Amount.Style.Side_Right
1910 , Amount.Style.unit_spaced = Just False
1915 , Posting.sourcepos = P.newPos "" 1 1
1918 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
1919 (Data.List.map fst $
1920 Data.Either.rights $
1922 (Format.Ledger.Read.posting <* P.eof)
1923 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
1926 { Posting.account = ["A","B","C"]
1927 , Posting.amounts = Data.Map.fromList
1929 { Amount.quantity = 2
1930 , Amount.style = Amount.Style.nil
1931 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1932 , Amount.Style.unit_spaced = Just False
1937 , Posting.sourcepos = P.newPos "" 1 1
1940 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
1941 (Data.List.map fst $
1942 Data.Either.rights $
1944 (Format.Ledger.Read.posting <* P.eof)
1945 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
1948 { Posting.account = ["A","B","C"]
1949 , Posting.amounts = Data.Map.fromList
1951 { Amount.quantity = 3
1952 , Amount.style = Amount.Style.nil
1953 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1954 , Amount.Style.unit_spaced = Just False
1959 , Posting.sourcepos = P.newPos "" 1 1
1962 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
1963 (Data.List.map fst $
1964 Data.Either.rights $
1966 (Format.Ledger.Read.posting <* P.eof)
1967 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
1970 { Posting.account = ["A","B","C"]
1971 , Posting.amounts = Data.Map.fromList []
1972 , Posting.comments = [" some comment"]
1973 , Posting.sourcepos = P.newPos "" 1 1
1976 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
1977 (Data.List.map fst $
1978 Data.Either.rights $
1980 (Format.Ledger.Read.posting <* P.eof)
1981 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
1984 { Posting.account = ["A","B","C"]
1985 , Posting.amounts = Data.Map.fromList []
1986 , Posting.comments = [" some comment", " some other comment"]
1987 , Posting.sourcepos = P.newPos "" 1 1
1990 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
1991 (Data.List.map fst $
1992 Data.Either.rights $
1994 (Format.Ledger.Read.posting)
1995 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
1998 { Posting.account = ["A","B","C"]
1999 , Posting.amounts = Data.Map.fromList
2001 { Amount.quantity = 1
2002 , Amount.style = Amount.Style.nil
2003 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2004 , Amount.Style.unit_spaced = Just False
2009 , Posting.comments = [" some comment"]
2010 , Posting.sourcepos = P.newPos "" 1 1
2013 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
2014 (Data.List.map fst $
2015 Data.Either.rights $
2017 (Format.Ledger.Read.posting <* P.eof)
2018 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
2021 { Posting.account = ["A","B","C"]
2022 , Posting.comments = [" N:V"]
2023 , Posting.sourcepos = P.newPos "" 1 1
2024 , Posting.tags = Data.Map.fromList
2029 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2030 (Data.List.map fst $
2031 Data.Either.rights $
2033 (Format.Ledger.Read.posting <* P.eof)
2034 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2037 { Posting.account = ["A","B","C"]
2038 , Posting.comments = [" some comment N:V"]
2039 , Posting.sourcepos = P.newPos "" 1 1
2040 , Posting.tags = Data.Map.fromList
2045 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2046 (Data.List.map fst $
2047 Data.Either.rights $
2049 (Format.Ledger.Read.posting )
2050 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2053 { Posting.account = ["A","B","C"]
2054 , Posting.comments = [" some comment N:V v, N2:V2 v2"]
2055 , Posting.sourcepos = P.newPos "" 1 1
2056 , Posting.tags = Data.Map.fromList
2062 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2063 (Data.List.map fst $
2064 Data.Either.rights $
2066 (Format.Ledger.Read.posting <* P.eof)
2067 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2070 { Posting.account = ["A","B","C"]
2071 , Posting.comments = [" N:V", " N:V2"]
2072 , Posting.sourcepos = P.newPos "" 1 1
2073 , Posting.tags = Data.Map.fromList
2074 [ ("N", ["V", "V2"])
2078 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2079 (Data.List.map fst $
2080 Data.Either.rights $
2082 (Format.Ledger.Read.posting <* P.eof)
2083 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2086 { Posting.account = ["A","B","C"]
2087 , Posting.comments = [" N:V", " N2:V"]
2088 , Posting.sourcepos = P.newPos "" 1 1
2089 , Posting.tags = Data.Map.fromList
2095 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2096 (Data.List.map fst $
2097 Data.Either.rights $
2099 (Format.Ledger.Read.posting <* P.eof)
2100 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2103 { Posting.account = ["A","B","C"]
2104 , Posting.comments = [" date:2001/01/01"]
2108 (Time.fromGregorian 2001 01 01)
2109 (Time.TimeOfDay 0 0 0))
2112 , Posting.sourcepos = P.newPos "" 1 1
2113 , Posting.tags = Data.Map.fromList
2114 [ ("date", ["2001/01/01"])
2118 , " (A:B:C) = Right (A:B:C)" ~:
2119 (Data.Either.rights $
2121 (Format.Ledger.Read.posting <* P.eof)
2122 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
2125 { Posting.account = ["A","B","C"]
2126 , Posting.sourcepos = P.newPos "" 1 1
2128 , Posting.Type_Virtual
2131 , " [A:B:C] = Right [A:B:C]" ~:
2132 (Data.Either.rights $
2134 (Format.Ledger.Read.posting <* P.eof)
2135 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
2138 { Posting.account = ["A","B","C"]
2139 , Posting.sourcepos = P.newPos "" 1 1
2141 , Posting.Type_Virtual_Balanced
2145 , "transaction" ~: TestList
2146 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
2147 (Data.Either.rights $
2149 (Format.Ledger.Read.transaction <* P.eof)
2150 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
2153 { Transaction.dates=
2156 (Time.fromGregorian 2000 01 01)
2157 (Time.TimeOfDay 0 0 0))
2160 , Transaction.description="some description"
2161 , Transaction.postings = Posting.from_List
2163 { Posting.account = ["A","B","C"]
2164 , Posting.amounts = Data.Map.fromList
2166 { Amount.quantity = 1
2167 , Amount.style = Amount.Style.nil
2168 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2169 , Amount.Style.unit_spaced = Just False
2174 , Posting.sourcepos = P.newPos "" 2 1
2177 { Posting.account = ["a","b","c"]
2178 , Posting.sourcepos = P.newPos "" 3 1
2181 , Transaction.sourcepos = P.newPos "" 1 1
2184 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
2185 (Data.Either.rights $
2187 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
2188 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
2191 { Transaction.dates=
2194 (Time.fromGregorian 2000 01 01)
2195 (Time.TimeOfDay 0 0 0))
2198 , Transaction.description="some description"
2199 , Transaction.postings = Posting.from_List
2201 { Posting.account = ["A","B","C"]
2202 , Posting.amounts = Data.Map.fromList
2204 { Amount.quantity = 1
2205 , Amount.style = Amount.Style.nil
2206 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2207 , Amount.Style.unit_spaced = Just False
2212 , Posting.sourcepos = P.newPos "" 2 1
2215 { Posting.account = ["a","b","c"]
2216 , Posting.sourcepos = P.newPos "" 3 1
2219 , Transaction.sourcepos = P.newPos "" 1 1
2222 , "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" ~:
2223 (Data.Either.rights $
2225 (Format.Ledger.Read.transaction <* P.eof)
2226 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)])
2229 { Transaction.comments_after =
2231 , " some other;comment"
2233 , " some last comment"
2235 , Transaction.dates=
2238 (Time.fromGregorian 2000 01 01)
2239 (Time.TimeOfDay 0 0 0))
2242 , Transaction.description="some description"
2243 , Transaction.postings = Posting.from_List
2245 { Posting.account = ["A","B","C"]
2246 , Posting.amounts = Data.Map.fromList
2248 { Amount.quantity = 1
2249 , Amount.style = Amount.Style.nil
2250 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2251 , Amount.Style.unit_spaced = Just False
2256 , Posting.sourcepos = P.newPos "" 5 1
2259 { Posting.account = ["a","b","c"]
2260 , Posting.sourcepos = P.newPos "" 6 1
2261 , Posting.tags = Data.Map.fromList []
2264 , Transaction.sourcepos = P.newPos "" 1 1
2265 , Transaction.tags = Data.Map.fromList
2271 , "journal" ~: TestList
2272 [ "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
2275 (Format.Ledger.Read.journal "" {-<* P.eof-})
2276 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)
2278 (\j -> j{Format.Ledger.Journal.last_read_time=
2279 Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $
2280 Data.Either.rights [jnl])
2282 [ Format.Ledger.Journal.nil
2283 { Format.Ledger.Journal.transactions = Transaction.from_List
2285 { Transaction.dates=
2288 (Time.fromGregorian 2000 01 01)
2289 (Time.TimeOfDay 0 0 0))
2292 , Transaction.description="1° description"
2293 , Transaction.postings = Posting.from_List
2295 { Posting.account = ["A","B","C"]
2296 , Posting.amounts = Data.Map.fromList
2298 { Amount.quantity = 1
2299 , Amount.style = Amount.Style.nil
2300 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2301 , Amount.Style.unit_spaced = Just False
2306 , Posting.sourcepos = P.newPos "" 2 1
2309 { Posting.account = ["a","b","c"]
2310 , Posting.sourcepos = P.newPos "" 3 1
2313 , Transaction.sourcepos = P.newPos "" 1 1
2316 { Transaction.dates=
2319 (Time.fromGregorian 2000 01 02)
2320 (Time.TimeOfDay 0 0 0))
2323 , Transaction.description="2° description"
2324 , Transaction.postings = Posting.from_List
2326 { Posting.account = ["A","B","C"]
2327 , Posting.amounts = Data.Map.fromList
2329 { Amount.quantity = 1
2330 , Amount.style = Amount.Style.nil
2331 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2332 , Amount.Style.unit_spaced = Just False
2337 , Posting.sourcepos = P.newPos "" 5 1
2340 { Posting.account = ["x","y","z"]
2341 , Posting.sourcepos = P.newPos "" 6 1
2344 , Transaction.sourcepos = P.newPos "" 4 1
2351 , "Write" ~: TestList
2352 [ "account" ~: TestList
2354 ((Format.Ledger.Write.show $
2355 Format.Ledger.Write.account Posting.Type_Regular
2360 ((Format.Ledger.Write.show $
2361 Format.Ledger.Write.account Posting.Type_Regular
2366 ((Format.Ledger.Write.show $
2367 Format.Ledger.Write.account Posting.Type_Regular
2372 ((Format.Ledger.Write.show $
2373 Format.Ledger.Write.account Posting.Type_Virtual
2378 ((Format.Ledger.Write.show $
2379 Format.Ledger.Write.account Posting.Type_Virtual_Balanced
2384 , "amount" ~: TestList
2386 ((Format.Ledger.Write.show $
2387 Format.Ledger.Write.amount
2392 ((Format.Ledger.Write.show $
2393 Format.Ledger.Write.amount
2395 { Amount.style = Amount.Style.nil
2396 { Amount.Style.precision = 2 }
2401 ((Format.Ledger.Write.show $
2402 Format.Ledger.Write.amount
2404 { Amount.quantity = Decimal 0 123
2409 ((Format.Ledger.Write.show $
2410 Format.Ledger.Write.amount
2412 { Amount.quantity = Decimal 0 (- 123)
2416 , "12.3 @ prec=0" ~:
2417 ((Format.Ledger.Write.show $
2418 Format.Ledger.Write.amount
2420 { Amount.quantity = Decimal 1 123
2421 , Amount.style = Amount.Style.nil
2422 { Amount.Style.fractioning = Just '.'
2427 , "12.5 @ prec=0" ~:
2428 ((Format.Ledger.Write.show $
2429 Format.Ledger.Write.amount
2431 { Amount.quantity = Decimal 1 125
2432 , Amount.style = Amount.Style.nil
2433 { Amount.Style.fractioning = Just '.'
2438 , "12.3 @ prec=1" ~:
2439 ((Format.Ledger.Write.show $
2440 Format.Ledger.Write.amount
2442 { Amount.quantity = Decimal 1 123
2443 , Amount.style = Amount.Style.nil
2444 { Amount.Style.fractioning = Just '.'
2445 , Amount.Style.precision = 1
2450 , "1,234.56 @ prec=2" ~:
2451 ((Format.Ledger.Write.show $
2452 Format.Ledger.Write.amount
2454 { Amount.quantity = Decimal 2 123456
2455 , Amount.style = Amount.Style.nil
2456 { Amount.Style.fractioning = Just '.'
2457 , Amount.Style.precision = 2
2458 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2463 , "123,456,789,01,2.3456789 @ prec=7" ~:
2464 ((Format.Ledger.Write.show $
2465 Format.Ledger.Write.amount
2467 { Amount.quantity = Decimal 7 1234567890123456789
2468 , Amount.style = Amount.Style.nil
2469 { Amount.Style.fractioning = Just '.'
2470 , Amount.Style.precision = 7
2471 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2475 "123,456,789,01,2.3456789")
2476 , "1234567.8,90,123,456,789 @ prec=12" ~:
2477 ((Format.Ledger.Write.show $
2478 Format.Ledger.Write.amount
2480 { Amount.quantity = Decimal 12 1234567890123456789
2481 , Amount.style = Amount.Style.nil
2482 { Amount.Style.fractioning = Just '.'
2483 , Amount.Style.precision = 12
2484 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2488 "1234567.8,90,123,456,789")
2489 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2490 ((Format.Ledger.Write.show $
2491 Format.Ledger.Write.amount
2493 { Amount.quantity = Decimal 7 1234567890123456789
2494 , Amount.style = Amount.Style.nil
2495 { Amount.Style.fractioning = Just '.'
2496 , Amount.Style.precision = 7
2497 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2501 "1,2,3,4,5,6,7,89,012.3456789")
2502 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2503 ((Format.Ledger.Write.show $
2504 Format.Ledger.Write.amount
2506 { Amount.quantity = Decimal 12 1234567890123456789
2507 , Amount.style = Amount.Style.nil
2508 { Amount.Style.fractioning = Just '.'
2509 , Amount.Style.precision = 12
2510 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2514 "1234567.890,12,3,4,5,6,7,8,9")
2516 , "amount_length" ~: TestList
2518 ((Format.Ledger.Write.amount_length
2523 ((Format.Ledger.Write.amount_length
2525 { Amount.style = Amount.Style.nil
2526 { Amount.Style.precision = 2 }
2531 ((Format.Ledger.Write.amount_length
2533 { Amount.quantity = Decimal 0 123
2538 ((Format.Ledger.Write.amount_length
2540 { Amount.quantity = Decimal 0 (- 123)
2544 , "12.3 @ prec=0" ~:
2545 ((Format.Ledger.Write.amount_length
2547 { Amount.quantity = Decimal 1 123
2548 , Amount.style = Amount.Style.nil
2549 { Amount.Style.fractioning = Just '.'
2554 , "12.5 @ prec=0" ~:
2555 ((Format.Ledger.Write.amount_length
2557 { Amount.quantity = Decimal 1 125
2558 , Amount.style = Amount.Style.nil
2559 { Amount.Style.fractioning = Just '.'
2564 , "12.3 @ prec=1" ~:
2565 ((Format.Ledger.Write.amount_length
2567 { Amount.quantity = Decimal 1 123
2568 , Amount.style = Amount.Style.nil
2569 { Amount.Style.fractioning = Just '.'
2570 , Amount.Style.precision = 1
2575 , "1,234.56 @ prec=2" ~:
2576 ((Format.Ledger.Write.amount_length
2578 { Amount.quantity = Decimal 2 123456
2579 , Amount.style = Amount.Style.nil
2580 { Amount.Style.fractioning = Just '.'
2581 , Amount.Style.precision = 2
2582 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2587 , "123,456,789,01,2.3456789 @ prec=7" ~:
2588 ((Format.Ledger.Write.amount_length
2590 { Amount.quantity = Decimal 7 1234567890123456789
2591 , Amount.style = Amount.Style.nil
2592 { Amount.Style.fractioning = Just '.'
2593 , Amount.Style.precision = 7
2594 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2599 , "1234567.8,90,123,456,789 @ prec=12" ~:
2600 ((Format.Ledger.Write.amount_length
2602 { Amount.quantity = Decimal 12 1234567890123456789
2603 , Amount.style = Amount.Style.nil
2604 { Amount.Style.fractioning = Just '.'
2605 , Amount.Style.precision = 12
2606 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2611 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2612 ((Format.Ledger.Write.amount_length
2614 { Amount.quantity = Decimal 7 1234567890123456789
2615 , Amount.style = Amount.Style.nil
2616 { Amount.Style.fractioning = Just '.'
2617 , Amount.Style.precision = 7
2618 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2623 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2624 ((Format.Ledger.Write.amount_length
2626 { Amount.quantity = Decimal 12 1234567890123456789
2627 , Amount.style = Amount.Style.nil
2628 { Amount.Style.fractioning = Just '.'
2629 , Amount.Style.precision = 12
2630 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2636 , "date" ~: TestList
2638 ((Format.Ledger.Write.show $
2639 Format.Ledger.Write.date
2643 , "2000/01/01 12:34:51 CET" ~:
2644 (Format.Ledger.Write.show $
2645 Format.Ledger.Write.date $
2648 (Time.fromGregorian 2000 01 01)
2649 (Time.TimeOfDay 12 34 51))
2650 (Time.TimeZone 60 False "CET"))
2652 "2000/01/01 12:34:51 CET"
2653 , "2000/01/01 12:34:51 +0100" ~:
2654 (Format.Ledger.Write.show $
2655 Format.Ledger.Write.date $
2658 (Time.fromGregorian 2000 01 01)
2659 (Time.TimeOfDay 12 34 51))
2660 (Time.TimeZone 60 False ""))
2662 "2000/01/01 12:34:51 +0100"
2663 , "2000/01/01 01:02:03" ~:
2664 (Format.Ledger.Write.show $
2665 Format.Ledger.Write.date $
2668 (Time.fromGregorian 2000 01 01)
2669 (Time.TimeOfDay 1 2 3))
2672 "2000/01/01 01:02:03"
2674 (Format.Ledger.Write.show $
2675 Format.Ledger.Write.date $
2678 (Time.fromGregorian 0 01 01)
2679 (Time.TimeOfDay 1 2 0))
2684 (Format.Ledger.Write.show $
2685 Format.Ledger.Write.date $
2688 (Time.fromGregorian 0 01 01)
2689 (Time.TimeOfDay 1 0 0))
2694 (Format.Ledger.Write.show $
2695 Format.Ledger.Write.date $
2698 (Time.fromGregorian 0 01 01)
2699 (Time.TimeOfDay 0 1 0))
2704 (Format.Ledger.Write.show $
2705 Format.Ledger.Write.date $
2708 (Time.fromGregorian 0 01 01)
2709 (Time.TimeOfDay 0 0 0))
2714 , "transaction" ~: TestList
2716 ((Format.Ledger.Write.show $
2717 Format.Ledger.Write.transaction
2721 , "2000/01/01 some description\\n\\ta:b:c\\n\\t\\t; first comment\\n\\t\\t; second comment\\n\\t\\t; third comment\\n\\tA:B:C $1" ~:
2722 ((Format.Ledger.Write.show $
2723 Format.Ledger.Write.transaction $
2725 { Transaction.dates=
2728 (Time.fromGregorian 2000 01 01)
2729 (Time.TimeOfDay 0 0 0))
2732 , Transaction.description="some description"
2733 , Transaction.postings = Posting.from_List
2735 { Posting.account = ["A","B","C"]
2736 , Posting.amounts = Data.Map.fromList
2738 { Amount.quantity = 1
2739 , Amount.style = Amount.Style.nil
2740 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2741 , Amount.Style.unit_spaced = Just False
2748 { Posting.account = ["a","b","c"]
2749 , Posting.comments = ["first comment","second comment","third comment"]
2754 "2000/01/01 some description\n\ta:b:c\n\t\t; first comment\n\t\t; second comment\n\t\t; third comment\n\tA:B:C $1")
2755 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
2756 ((Format.Ledger.Write.show $
2757 Format.Ledger.Write.transaction $
2759 { Transaction.dates=
2762 (Time.fromGregorian 2000 01 01)
2763 (Time.TimeOfDay 0 0 0))
2766 , Transaction.description="some description"
2767 , Transaction.postings = Posting.from_List
2769 { Posting.account = ["A","B","C"]
2770 , Posting.amounts = Data.Map.fromList
2772 { Amount.quantity = 1
2773 , Amount.style = Amount.Style.nil
2774 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2775 , Amount.Style.unit_spaced = Just False
2782 { Posting.account = ["AA","BB","CC"]
2783 , Posting.amounts = Data.Map.fromList
2785 { Amount.quantity = 123
2786 , Amount.style = Amount.Style.nil
2787 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2788 , Amount.Style.unit_spaced = Just False
2797 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")