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_unit_sum $
141 [ Calc.Balance.Unit_Sum
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_unit_sum $
169 [ Calc.Balance.Unit_Sum
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_unit_sum $
197 [ Calc.Balance.Unit_Sum
198 { Calc.Balance.amount = Amount.usd $ 1
199 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
202 , Calc.Balance.Unit_Sum
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_unit_sum $
232 [ Calc.Balance.Unit_Sum
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_unit_sum $
261 [ Calc.Balance.Unit_Sum
262 { Calc.Balance.amount = Amount.usd $ 0
263 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
266 , Calc.Balance.Unit_Sum
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_unit_sum $
296 [ Calc.Balance.Unit_Sum
297 { Calc.Balance.amount = Amount.usd $ 0
298 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
301 , Calc.Balance.Unit_Sum
302 { Calc.Balance.amount = Amount.eur $ 0
303 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
306 , Calc.Balance.Unit_Sum
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_unit_sum $
330 [ Calc.Balance.Unit_Sum
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_unit_sum $
344 [ Calc.Balance.Unit_Sum
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_unit_sum $
359 [ Calc.Balance.Unit_Sum
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_unit_sum $
375 [ Calc.Balance.Unit_Sum
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_unit_sum $
389 [ Calc.Balance.Unit_Sum
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_unit_sum $
405 [ Calc.Balance.Unit_Sum
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_unit_sum $
421 [ Calc.Balance.Unit_Sum
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_unit_sum $
435 [ Calc.Balance.Unit_Sum
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_unit_sum $
451 [ Calc.Balance.Unit_Sum
452 { Calc.Balance.amount = Amount.usd $ 1
453 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
456 , Calc.Balance.Unit_Sum
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_equilibrable" ~: TestList
575 [ "nil" ~: TestCase $
577 Calc.Balance.is_equilibrable $
578 Calc.Balance.equilibre $
580 , "{A+$0, $+0}" ~: TestCase $
582 Calc.Balance.is_equilibrable $
583 Calc.Balance.equilibre $
585 { Calc.Balance.by_account =
587 [ (["A"], Amount.from_List [ Amount.usd $ 0 ])
589 , Calc.Balance.by_unit =
591 Data.List.map Calc.Balance.assoc_unit_sum $
592 [ Calc.Balance.Unit_Sum
593 { Calc.Balance.amount = Amount.usd $ 0
594 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
599 , "{A+$1, $+1}" ~: TestCase $
601 Calc.Balance.is_equilibrable $
602 Calc.Balance.equilibre $
604 { Calc.Balance.by_account =
606 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
608 , Calc.Balance.by_unit =
610 Data.List.map Calc.Balance.assoc_unit_sum $
611 [ Calc.Balance.Unit_Sum
612 { Calc.Balance.amount = Amount.usd $ 1
613 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
618 , "{A+$0+€0, $0 €+0}" ~: TestCase $
620 Calc.Balance.is_equilibrable $
621 Calc.Balance.equilibre $
623 { Calc.Balance.by_account =
625 [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
627 , Calc.Balance.by_unit =
629 Data.List.map Calc.Balance.assoc_unit_sum $
630 [ Calc.Balance.Unit_Sum
631 { Calc.Balance.amount = Amount.usd $ 0
632 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
635 , Calc.Balance.Unit_Sum
636 { Calc.Balance.amount = Amount.eur $ 0
637 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
642 , "{A+$1, B-$1, $+0}" ~: TestCase $
644 Calc.Balance.is_equilibrable $
645 Calc.Balance.equilibre $
647 { Calc.Balance.by_account =
649 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
650 , (["B"], Amount.from_List [ Amount.usd $ -1 ])
652 , Calc.Balance.by_unit =
654 Data.List.map Calc.Balance.assoc_unit_sum $
655 [ Calc.Balance.Unit_Sum
656 { Calc.Balance.amount = Amount.usd $ 0
657 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
662 , "{A+$1 B, $+1}" ~: TestCase $
664 Calc.Balance.is_equilibrable $
665 Calc.Balance.equilibre $
667 { Calc.Balance.by_account =
669 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
670 , (["B"], Amount.from_List [])
672 , Calc.Balance.by_unit =
674 Data.List.map Calc.Balance.assoc_unit_sum $
675 [ Calc.Balance.Unit_Sum
676 { Calc.Balance.amount = Amount.usd $ 1
677 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
682 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
684 Calc.Balance.is_equilibrable $
685 Calc.Balance.equilibre $
687 { Calc.Balance.by_account =
689 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
690 , (["B"], Amount.from_List [ Amount.eur $ 1 ])
692 , Calc.Balance.by_unit =
694 Data.List.map Calc.Balance.assoc_unit_sum $
695 [ Calc.Balance.Unit_Sum
696 { Calc.Balance.amount = Amount.usd $ 1
697 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
700 , Calc.Balance.Unit_Sum
701 { Calc.Balance.amount = Amount.eur $ 1
702 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
707 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
709 Calc.Balance.is_equilibrable $
710 Calc.Balance.equilibre $
712 { Calc.Balance.by_account =
714 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
715 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
717 , Calc.Balance.by_unit =
719 Data.List.map Calc.Balance.assoc_unit_sum $
720 [ Calc.Balance.Unit_Sum
721 { Calc.Balance.amount = Amount.usd $ 0
722 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
725 , Calc.Balance.Unit_Sum
726 { Calc.Balance.amount = Amount.eur $ 1
727 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
732 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
734 Calc.Balance.is_equilibrable $
735 Calc.Balance.equilibre $
737 { Calc.Balance.by_account =
739 [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
740 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
742 , Calc.Balance.by_unit =
744 Data.List.map Calc.Balance.assoc_unit_sum $
745 [ Calc.Balance.Unit_Sum
746 { Calc.Balance.amount = Amount.usd $ 0
747 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
750 , Calc.Balance.Unit_Sum
751 { Calc.Balance.amount = Amount.eur $ 0
752 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
755 , Calc.Balance.Unit_Sum
756 { Calc.Balance.amount = Amount.gbp $ 0
757 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
765 , "Format" ~: TestList
766 [ "Ledger" ~: TestList
768 [ "account_name" ~: TestList
770 (Data.Either.rights $
772 (Format.Ledger.Read.account_name <* P.eof)
776 , "\"A\" = Right \"A\"" ~:
777 (Data.Either.rights $
779 (Format.Ledger.Read.account_name <* P.eof)
783 , "\"AA\" = Right \"AA\"" ~:
784 (Data.Either.rights $
786 (Format.Ledger.Read.account_name <* P.eof)
791 (Data.Either.rights $
793 (Format.Ledger.Read.account_name <* P.eof)
798 (Data.Either.rights $
800 (Format.Ledger.Read.account_name <* P.eof)
805 (Data.Either.rights $
807 (Format.Ledger.Read.account_name <* P.eof)
812 (Data.Either.rights $
814 (Format.Ledger.Read.account_name <* P.eof)
819 (Data.Either.rights $
821 (Format.Ledger.Read.account_name <* P.eof)
825 , "\"A \" ^= Right" ~:
826 (Data.Either.rights $
828 (Format.Ledger.Read.account_name)
832 , "\"A A\" = Right \"A A\"" ~:
833 (Data.Either.rights $
835 (Format.Ledger.Read.account_name <* P.eof)
836 () "" ("A A"::Text)])
840 (Data.Either.rights $
842 (Format.Ledger.Read.account_name <* P.eof)
846 , "\"A \\n\" = Left" ~:
847 (Data.Either.rights $
849 (Format.Ledger.Read.account_name <* P.eof)
850 () "" ("A \n"::Text)])
853 , "\"(A)A\" = Right \"(A)A\"" ~:
854 (Data.Either.rights $
856 (Format.Ledger.Read.account_name <* P.eof)
857 () "" ("(A)A"::Text)])
860 , "\"( )A\" = Right \"( )A\"" ~:
861 (Data.Either.rights $
863 (Format.Ledger.Read.account_name <* P.eof)
864 () "" ("( )A"::Text)])
867 , "\"(A) A\" = Right \"(A) A\"" ~:
868 (Data.Either.rights $
870 (Format.Ledger.Read.account_name <* P.eof)
871 () "" ("(A) A"::Text)])
874 , "\"[ ]A\" = Right \"[ ]A\"" ~:
875 (Data.Either.rights $
877 (Format.Ledger.Read.account_name <* P.eof)
878 () "" ("[ ]A"::Text)])
881 , "\"(A) \" = Left" ~:
882 (Data.Either.rights $
884 (Format.Ledger.Read.account_name <* P.eof)
885 () "" ("(A) "::Text)])
888 , "\"(A)\" = Left" ~:
889 (Data.Either.rights $
891 (Format.Ledger.Read.account_name <* P.eof)
892 () "" ("(A)"::Text)])
895 , "\"[A]A\" = Right \"(A)A\"" ~:
896 (Data.Either.rights $
898 (Format.Ledger.Read.account_name <* P.eof)
899 () "" ("[A]A"::Text)])
902 , "\"[A] A\" = Right \"[A] A\"" ~:
903 (Data.Either.rights $
905 (Format.Ledger.Read.account_name <* P.eof)
906 () "" ("[A] A"::Text)])
909 , "\"[A] \" = Left" ~:
910 (Data.Either.rights $
912 (Format.Ledger.Read.account_name <* P.eof)
913 () "" ("[A] "::Text)])
916 , "\"[A]\" = Left" ~:
917 (Data.Either.rights $
919 (Format.Ledger.Read.account_name <* P.eof)
920 () "" ("[A]"::Text)])
924 , "account" ~: TestList
926 (Data.Either.rights $
928 (Format.Ledger.Read.account <* P.eof)
932 , "\"A\" = Right [\"A\"]" ~:
933 (Data.Either.rights $
935 (Format.Ledger.Read.account <* P.eof)
940 (Data.Either.rights $
942 (Format.Ledger.Read.account <* P.eof)
947 (Data.Either.rights $
949 (Format.Ledger.Read.account <* P.eof)
954 (Data.Either.rights $
956 (Format.Ledger.Read.account <* P.eof)
961 (Data.Either.rights $
963 (Format.Ledger.Read.account <* P.eof)
967 , "\"A:B\" = Right [\"A\", \"B\"]" ~:
968 (Data.Either.rights $
970 (Format.Ledger.Read.account <* P.eof)
971 () "" ("A:B"::Text)])
974 , "\"A:B:C\" = Right [\"A\", \"B\", \"C\"]" ~:
975 (Data.Either.rights $
977 (Format.Ledger.Read.account <* P.eof)
978 () "" ("A:B:C"::Text)])
981 , "\"Aa:Bbb:Cccc\" = Right [\"Aa\", \"Bbb\", \":Cccc\"]" ~:
982 (Data.Either.rights $
984 (Format.Ledger.Read.account <* P.eof)
985 () "" ("Aa:Bbb:Cccc"::Text)])
987 [["Aa", "Bbb", "Cccc"]]
988 , "\"A a : B b b : C c c c\" = Right [\"A a \", \" B b b \", \": C c c c\"]" ~:
989 (Data.Either.rights $
991 (Format.Ledger.Read.account <* P.eof)
992 () "" ("A a : B b b : C c c c"::Text)])
994 [["A a ", " B b b ", " C c c c"]]
995 , "\"A: :C\" = Right [\"A\", \" \", \"C\"]" ~:
996 (Data.Either.rights $
998 (Format.Ledger.Read.account <* P.eof)
999 () "" ("A: :C"::Text)])
1002 , "\"A::C\" = Left" ~:
1003 (Data.Either.rights $
1005 (Format.Ledger.Read.account <* P.eof)
1006 () "" ("A::C"::Text)])
1010 , "amount" ~: TestList
1012 (Data.Either.rights $
1014 (Format.Ledger.Read.amount <* P.eof)
1018 , "\"0\" = Right 0" ~:
1019 (Data.Either.rights $
1021 (Format.Ledger.Read.amount <* P.eof)
1025 { Amount.quantity = Decimal 0 0
1027 , "\"00\" = Right 0" ~:
1028 (Data.Either.rights $
1030 (Format.Ledger.Read.amount <* P.eof)
1031 () "" ("00"::Text)])
1034 { Amount.quantity = Decimal 0 0
1036 , "\"0.\" = Right 0." ~:
1037 (Data.Either.rights $
1039 (Format.Ledger.Read.amount <* P.eof)
1040 () "" ("0."::Text)])
1043 { Amount.quantity = Decimal 0 0
1046 { Amount.Style.fractioning = Just '.'
1049 , "\".0\" = Right 0.0" ~:
1050 (Data.Either.rights $
1052 (Format.Ledger.Read.amount <* P.eof)
1053 () "" (".0"::Text)])
1056 { Amount.quantity = Decimal 0 0
1059 { Amount.Style.fractioning = Just '.'
1060 , Amount.Style.precision = 1
1063 , "\"0,\" = Right 0," ~:
1064 (Data.Either.rights $
1066 (Format.Ledger.Read.amount <* P.eof)
1067 () "" ("0,"::Text)])
1070 { Amount.quantity = Decimal 0 0
1073 { Amount.Style.fractioning = Just ','
1076 , "\",0\" = Right 0,0" ~:
1077 (Data.Either.rights $
1079 (Format.Ledger.Read.amount <* P.eof)
1080 () "" (",0"::Text)])
1083 { Amount.quantity = Decimal 0 0
1086 { Amount.Style.fractioning = Just ','
1087 , Amount.Style.precision = 1
1090 , "\"0_\" = Left" ~:
1091 (Data.Either.rights $
1093 (Format.Ledger.Read.amount <* P.eof)
1094 () "" ("0_"::Text)])
1097 , "\"_0\" = Left" ~:
1098 (Data.Either.rights $
1100 (Format.Ledger.Read.amount <* P.eof)
1101 () "" ("_0"::Text)])
1104 , "\"0.0\" = Right 0.0" ~:
1105 (Data.Either.rights $
1107 (Format.Ledger.Read.amount <* P.eof)
1108 () "" ("0.0"::Text)])
1111 { Amount.quantity = Decimal 0 0
1114 { Amount.Style.fractioning = Just '.'
1115 , Amount.Style.precision = 1
1118 , "\"00.00\" = Right 0.00" ~:
1119 (Data.Either.rights $
1121 (Format.Ledger.Read.amount <* P.eof)
1122 () "" ("00.00"::Text)])
1125 { Amount.quantity = Decimal 0 0
1128 { Amount.Style.fractioning = Just '.'
1129 , Amount.Style.precision = 2
1132 , "\"0,0\" = Right 0,0" ~:
1133 (Data.Either.rights $
1135 (Format.Ledger.Read.amount <* P.eof)
1136 () "" ("0,0"::Text)])
1139 { Amount.quantity = Decimal 0 0
1142 { Amount.Style.fractioning = Just ','
1143 , Amount.Style.precision = 1
1146 , "\"00,00\" = Right 0,00" ~:
1147 (Data.Either.rights $
1149 (Format.Ledger.Read.amount <* P.eof)
1150 () "" ("00,00"::Text)])
1153 { Amount.quantity = Decimal 0 0
1156 { Amount.Style.fractioning = Just ','
1157 , Amount.Style.precision = 2
1160 , "\"0_0\" = Right 0" ~:
1161 (Data.Either.rights $
1163 (Format.Ledger.Read.amount <* P.eof)
1164 () "" ("0_0"::Text)])
1167 { Amount.quantity = Decimal 0 0
1170 { Amount.Style.fractioning = Nothing
1171 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1172 , Amount.Style.precision = 0
1175 , "\"00_00\" = Right 0" ~:
1176 (Data.Either.rights $
1178 (Format.Ledger.Read.amount <* P.eof)
1179 () "" ("00_00"::Text)])
1182 { Amount.quantity = Decimal 0 0
1185 { Amount.Style.fractioning = Nothing
1186 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1187 , Amount.Style.precision = 0
1190 , "\"0,000.00\" = Right 0,000.00" ~:
1191 (Data.Either.rights $
1193 (Format.Ledger.Read.amount <* P.eof)
1194 () "" ("0,000.00"::Text)])
1197 { Amount.quantity = Decimal 0 0
1200 { Amount.Style.fractioning = Just '.'
1201 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1202 , Amount.Style.precision = 2
1205 , "\"0.000,00\" = Right 0.000,00" ~:
1206 (Data.Either.rights $
1208 (Format.Ledger.Read.amount)
1209 () "" ("0.000,00"::Text)])
1212 { Amount.quantity = Decimal 0 0
1215 { Amount.Style.fractioning = Just ','
1216 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1217 , Amount.Style.precision = 2
1220 , "\"1,000.00\" = Right 1,000.00" ~:
1221 (Data.Either.rights $
1223 (Format.Ledger.Read.amount <* P.eof)
1224 () "" ("1,000.00"::Text)])
1227 { Amount.quantity = Decimal 0 1000
1230 { Amount.Style.fractioning = Just '.'
1231 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1232 , Amount.Style.precision = 2
1235 , "\"1.000,00\" = Right 1.000,00" ~:
1236 (Data.Either.rights $
1238 (Format.Ledger.Read.amount)
1239 () "" ("1.000,00"::Text)])
1242 { Amount.quantity = Decimal 0 1000
1245 { Amount.Style.fractioning = Just ','
1246 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1247 , Amount.Style.precision = 2
1250 , "\"1,000.00.\" = Left" ~:
1251 (Data.Either.rights $
1253 (Format.Ledger.Read.amount)
1254 () "" ("1,000.00."::Text)])
1257 , "\"1.000,00,\" = Left" ~:
1258 (Data.Either.rights $
1260 (Format.Ledger.Read.amount)
1261 () "" ("1.000,00,"::Text)])
1264 , "\"1,000.00_\" = Left" ~:
1265 (Data.Either.rights $
1267 (Format.Ledger.Read.amount)
1268 () "" ("1,000.00_"::Text)])
1271 , "\"12\" = Right 12" ~:
1272 (Data.Either.rights $
1274 (Format.Ledger.Read.amount <* P.eof)
1275 () "" ("123"::Text)])
1278 { Amount.quantity = Decimal 0 123
1280 , "\"1.2\" = Right 1.2" ~:
1281 (Data.Either.rights $
1283 (Format.Ledger.Read.amount <* P.eof)
1284 () "" ("1.2"::Text)])
1287 { Amount.quantity = Decimal 1 12
1290 { Amount.Style.fractioning = Just '.'
1291 , Amount.Style.precision = 1
1294 , "\"1,2\" = Right 1,2" ~:
1295 (Data.Either.rights $
1297 (Format.Ledger.Read.amount <* P.eof)
1298 () "" ("1,2"::Text)])
1301 { Amount.quantity = Decimal 1 12
1304 { Amount.Style.fractioning = Just ','
1305 , Amount.Style.precision = 1
1308 , "\"12.23\" = Right 12.23" ~:
1309 (Data.Either.rights $
1311 (Format.Ledger.Read.amount <* P.eof)
1312 () "" ("12.34"::Text)])
1315 { Amount.quantity = Decimal 2 1234
1318 { Amount.Style.fractioning = Just '.'
1319 , Amount.Style.precision = 2
1322 , "\"12,23\" = Right 12,23" ~:
1323 (Data.Either.rights $
1325 (Format.Ledger.Read.amount <* P.eof)
1326 () "" ("12,34"::Text)])
1329 { Amount.quantity = Decimal 2 1234
1332 { Amount.Style.fractioning = Just ','
1333 , Amount.Style.precision = 2
1336 , "\"1_2\" = Right 1_2" ~:
1337 (Data.Either.rights $
1339 (Format.Ledger.Read.amount <* P.eof)
1340 () "" ("1_2"::Text)])
1343 { Amount.quantity = Decimal 0 12
1346 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1347 , Amount.Style.precision = 0
1350 , "\"1_23\" = Right 1_23" ~:
1351 (Data.Either.rights $
1353 (Format.Ledger.Read.amount <* P.eof)
1354 () "" ("1_23"::Text)])
1357 { Amount.quantity = Decimal 0 123
1360 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1361 , Amount.Style.precision = 0
1364 , "\"1_23_456\" = Right 1_23_456" ~:
1365 (Data.Either.rights $
1367 (Format.Ledger.Read.amount <* P.eof)
1368 () "" ("1_23_456"::Text)])
1371 { Amount.quantity = Decimal 0 123456
1374 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1375 , Amount.Style.precision = 0
1378 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1379 (Data.Either.rights $
1381 (Format.Ledger.Read.amount <* P.eof)
1382 () "" ("1_23_456.7890_12345_678901"::Text)])
1385 { Amount.quantity = Decimal 15 123456789012345678901
1388 { Amount.Style.fractioning = Just '.'
1389 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1390 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1391 , Amount.Style.precision = 15
1394 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1395 (Data.Either.rights $
1397 (Format.Ledger.Read.amount <* P.eof)
1398 () "" ("123456_78901_2345.678_90_1"::Text)])
1401 { Amount.quantity = Decimal 6 123456789012345678901
1404 { Amount.Style.fractioning = Just '.'
1405 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1406 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1407 , Amount.Style.precision = 6
1410 , "\"$1\" = Right $1" ~:
1411 (Data.Either.rights $
1413 (Format.Ledger.Read.amount <* P.eof)
1414 () "" ("$1"::Text)])
1417 { Amount.quantity = Decimal 0 1
1420 { Amount.Style.fractioning = Nothing
1421 , Amount.Style.grouping_integral = Nothing
1422 , Amount.Style.grouping_fractional = Nothing
1423 , Amount.Style.precision = 0
1424 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1425 , Amount.Style.unit_spaced = Just False
1429 , "\"1$\" = Right 1$" ~:
1430 (Data.Either.rights $
1432 (Format.Ledger.Read.amount <* P.eof)
1433 () "" ("1$"::Text)])
1436 { Amount.quantity = Decimal 0 1
1439 { Amount.Style.fractioning = Nothing
1440 , Amount.Style.grouping_integral = Nothing
1441 , Amount.Style.grouping_fractional = Nothing
1442 , Amount.Style.precision = 0
1443 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1444 , Amount.Style.unit_spaced = Just False
1448 , "\"$ 1\" = Right $ 1" ~:
1449 (Data.Either.rights $
1451 (Format.Ledger.Read.amount <* P.eof)
1452 () "" ("$ 1"::Text)])
1455 { Amount.quantity = Decimal 0 1
1458 { Amount.Style.fractioning = Nothing
1459 , Amount.Style.grouping_integral = Nothing
1460 , Amount.Style.grouping_fractional = Nothing
1461 , Amount.Style.precision = 0
1462 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1463 , Amount.Style.unit_spaced = Just True
1467 , "\"1 $\" = Right 1 $" ~:
1468 (Data.Either.rights $
1470 (Format.Ledger.Read.amount <* P.eof)
1471 () "" ("1 $"::Text)])
1474 { Amount.quantity = Decimal 0 1
1477 { Amount.Style.fractioning = Nothing
1478 , Amount.Style.grouping_integral = Nothing
1479 , Amount.Style.grouping_fractional = Nothing
1480 , Amount.Style.precision = 0
1481 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1482 , Amount.Style.unit_spaced = Just True
1486 , "\"-$1\" = Right $-1" ~:
1487 (Data.Either.rights $
1489 (Format.Ledger.Read.amount <* P.eof)
1490 () "" ("-$1"::Text)])
1493 { Amount.quantity = Decimal 0 (-1)
1496 { Amount.Style.fractioning = Nothing
1497 , Amount.Style.grouping_integral = Nothing
1498 , Amount.Style.grouping_fractional = Nothing
1499 , Amount.Style.precision = 0
1500 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1501 , Amount.Style.unit_spaced = Just False
1505 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1506 (Data.Either.rights $
1508 (Format.Ledger.Read.amount <* P.eof)
1509 () "" ("\"4 2\"1"::Text)])
1512 { Amount.quantity = Decimal 0 1
1515 { Amount.Style.fractioning = Nothing
1516 , Amount.Style.grouping_integral = Nothing
1517 , Amount.Style.grouping_fractional = Nothing
1518 , Amount.Style.precision = 0
1519 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1520 , Amount.Style.unit_spaced = Just False
1522 , Amount.unit = "4 2"
1524 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1525 (Data.Either.rights $
1527 (Format.Ledger.Read.amount <* P.eof)
1528 () "" ("1\"4 2\""::Text)])
1531 { Amount.quantity = Decimal 0 1
1534 { Amount.Style.fractioning = Nothing
1535 , Amount.Style.grouping_integral = Nothing
1536 , Amount.Style.grouping_fractional = Nothing
1537 , Amount.Style.precision = 0
1538 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1539 , Amount.Style.unit_spaced = Just False
1541 , Amount.unit = "4 2"
1543 , "\"$1.000,00\" = Right $1.000,00" ~:
1544 (Data.Either.rights $
1546 (Format.Ledger.Read.amount <* P.eof)
1547 () "" ("$1.000,00"::Text)])
1550 { Amount.quantity = Decimal 0 1000
1553 { Amount.Style.fractioning = Just ','
1554 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1555 , Amount.Style.grouping_fractional = Nothing
1556 , Amount.Style.precision = 2
1557 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1558 , Amount.Style.unit_spaced = Just False
1562 , "\"1.000,00$\" = Right 1.000,00$" ~:
1563 (Data.Either.rights $
1565 (Format.Ledger.Read.amount <* P.eof)
1566 () "" ("1.000,00$"::Text)])
1569 { Amount.quantity = Decimal 0 1000
1572 { Amount.Style.fractioning = Just ','
1573 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1574 , Amount.Style.grouping_fractional = Nothing
1575 , Amount.Style.precision = 2
1576 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1577 , Amount.Style.unit_spaced = Just False
1582 , "comment" ~: TestList
1583 [ "; some comment = Right \" some comment\"" ~:
1584 (Data.Either.rights $
1586 (Format.Ledger.Read.comment <* P.eof)
1587 () "" ("; some comment"::Text)])
1590 , "; some comment \\n = Right \" some comment \"" ~:
1591 (Data.Either.rights $
1593 (Format.Ledger.Read.comment <* P.newline <* P.eof)
1594 () "" ("; some comment \n"::Text)])
1596 [ " some comment " ]
1597 , "; some comment \\r\\n = Right \" some comment \"" ~:
1598 (Data.Either.rights $
1600 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
1601 () "" ("; some comment \r\n"::Text)])
1603 [ " some comment " ]
1605 , "comments" ~: TestList
1606 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
1607 (Data.Either.rights $
1609 (Format.Ledger.Read.comments <* P.eof)
1610 () "" ("; some comment\n ; some other comment"::Text)])
1612 [ [" some comment", " some other comment"] ]
1613 , "; some comment \\n = Right \" some comment \"" ~:
1614 (Data.Either.rights $
1616 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
1617 () "" ("; some comment \n"::Text)])
1619 [ [" some comment "] ]
1621 , "date" ~: TestList
1623 (Data.Either.rights $
1625 (Format.Ledger.Read.date Nothing <* P.eof)
1626 () "" ("2000/01/01"::Text)])
1630 (Time.fromGregorian 2000 01 01)
1631 (Time.TimeOfDay 0 0 0))
1633 , "2000/01/01 some text" ~:
1634 (Data.Either.rights $
1636 (Format.Ledger.Read.date Nothing)
1637 () "" ("2000/01/01 some text"::Text)])
1641 (Time.fromGregorian 2000 01 01)
1642 (Time.TimeOfDay 0 0 0))
1644 , "2000/01/01 12:34" ~:
1645 (Data.Either.rights $
1647 (Format.Ledger.Read.date Nothing <* P.eof)
1648 () "" ("2000/01/01 12:34"::Text)])
1652 (Time.fromGregorian 2000 01 01)
1653 (Time.TimeOfDay 12 34 0))
1655 , "2000/01/01 12:34:56" ~:
1656 (Data.Either.rights $
1658 (Format.Ledger.Read.date Nothing <* P.eof)
1659 () "" ("2000/01/01 12:34:56"::Text)])
1663 (Time.fromGregorian 2000 01 01)
1664 (Time.TimeOfDay 12 34 56))
1666 , "2000/01/01 12:34 CET" ~:
1667 (Data.Either.rights $
1669 (Format.Ledger.Read.date Nothing <* P.eof)
1670 () "" ("2000/01/01 12:34 CET"::Text)])
1674 (Time.fromGregorian 2000 01 01)
1675 (Time.TimeOfDay 12 34 0))
1676 (Time.TimeZone 60 True "CET")]
1677 , "2000/01/01 12:34 +0130" ~:
1678 (Data.Either.rights $
1680 (Format.Ledger.Read.date Nothing <* P.eof)
1681 () "" ("2000/01/01 12:34 +0130"::Text)])
1685 (Time.fromGregorian 2000 01 01)
1686 (Time.TimeOfDay 12 34 0))
1687 (Time.TimeZone 90 False "+0130")]
1688 , "2000/01/01 12:34:56 CET" ~:
1689 (Data.Either.rights $
1691 (Format.Ledger.Read.date Nothing <* P.eof)
1692 () "" ("2000/01/01 12:34:56 CET"::Text)])
1696 (Time.fromGregorian 2000 01 01)
1697 (Time.TimeOfDay 12 34 56))
1698 (Time.TimeZone 60 True "CET")]
1700 (Data.Either.rights $
1702 (Format.Ledger.Read.date Nothing <* P.eof)
1703 () "" ("2001/02/29"::Text)])
1707 (Data.Either.rights $
1709 (Format.Ledger.Read.date (Just 2000) <* P.eof)
1710 () "" ("01/01"::Text)])
1714 (Time.fromGregorian 2000 01 01)
1715 (Time.TimeOfDay 0 0 0))
1718 , "tag_value" ~: TestList
1720 (Data.Either.rights $
1722 (Format.Ledger.Read.tag_value <* P.eof)
1727 (Data.Either.rights $
1729 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
1730 () "" (",\n"::Text)])
1734 (Data.Either.rights $
1736 (Format.Ledger.Read.tag_value <* P.eof)
1737 () "" (",x"::Text)])
1741 (Data.Either.rights $
1743 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
1744 () "" (",x:"::Text)])
1748 (Data.Either.rights $
1750 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
1751 () "" ("v, v, n:"::Text)])
1757 (Data.Either.rights $
1759 (Format.Ledger.Read.tag <* P.eof)
1760 () "" ("Name:"::Text)])
1764 (Data.Either.rights $
1766 (Format.Ledger.Read.tag <* P.eof)
1767 () "" ("Name:Value"::Text)])
1770 , "Name:Value\\n" ~:
1771 (Data.Either.rights $
1773 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
1774 () "" ("Name:Value\n"::Text)])
1778 (Data.Either.rights $
1780 (Format.Ledger.Read.tag <* P.eof)
1781 () "" ("Name:Val ue"::Text)])
1783 [("Name", "Val ue")]
1785 (Data.Either.rights $
1787 (Format.Ledger.Read.tag <* P.eof)
1788 () "" ("Name:,"::Text)])
1792 (Data.Either.rights $
1794 (Format.Ledger.Read.tag <* P.eof)
1795 () "" ("Name:Val,ue"::Text)])
1797 [("Name", "Val,ue")]
1799 (Data.Either.rights $
1801 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
1802 () "" ("Name:Val,ue:"::Text)])
1806 , "tags" ~: TestList
1808 (Data.Either.rights $
1810 (Format.Ledger.Read.tags <* P.eof)
1811 () "" ("Name:"::Text)])
1818 (Data.Either.rights $
1820 (Format.Ledger.Read.tags <* P.eof)
1821 () "" ("Name:,"::Text)])
1828 (Data.Either.rights $
1830 (Format.Ledger.Read.tags <* P.eof)
1831 () "" ("Name:,Name:"::Text)])
1834 [ ("Name", ["", ""])
1838 (Data.Either.rights $
1840 (Format.Ledger.Read.tags <* P.eof)
1841 () "" ("Name:,Name2:"::Text)])
1848 , "Name: , Name2:" ~:
1849 (Data.Either.rights $
1851 (Format.Ledger.Read.tags <* P.eof)
1852 () "" ("Name: , Name2:"::Text)])
1859 , "Name:,Name2:,Name3:" ~:
1860 (Data.Either.rights $
1862 (Format.Ledger.Read.tags <* P.eof)
1863 () "" ("Name:,Name2:,Name3:"::Text)])
1871 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
1872 (Data.Either.rights $
1874 (Format.Ledger.Read.tags <* P.eof)
1875 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
1878 [ ("Name", ["Val ue"])
1879 , ("Name2", ["V a l u e"])
1880 , ("Name3", ["V al ue"])
1884 , "posting" ~: TestList
1885 [ " A:B:C = Right A:B:C" ~:
1886 (Data.Either.rights $
1888 (Format.Ledger.Read.posting <* P.eof)
1889 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
1892 { Posting.account = ["A","B","C"]
1893 , Posting.sourcepos = P.newPos "" 1 1
1895 , Posting.Type_Regular
1898 , " !A:B:C = Right !A:B:C" ~:
1899 (Data.List.map fst $
1900 Data.Either.rights $
1902 (Format.Ledger.Read.posting <* P.eof)
1903 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
1906 { Posting.account = ["A","B","C"]
1907 , Posting.sourcepos = P.newPos "" 1 1
1908 , Posting.status = True
1911 , " *A:B:C = Right *A:B:C" ~:
1912 (Data.List.map fst $
1913 Data.Either.rights $
1915 (Format.Ledger.Read.posting <* P.eof)
1916 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
1919 { Posting.account = ["A","B","C"]
1920 , Posting.amounts = Data.Map.fromList []
1921 , Posting.comments = []
1922 , Posting.dates = []
1923 , Posting.status = True
1924 , Posting.sourcepos = P.newPos "" 1 1
1925 , Posting.tags = Data.Map.fromList []
1928 , " A:B:C $1 = Right A:B:C $1" ~:
1929 (Data.List.map fst $
1930 Data.Either.rights $
1932 (Format.Ledger.Read.posting <* P.eof)
1933 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1936 { Posting.account = ["A","B","C $1"]
1937 , Posting.sourcepos = P.newPos "" 1 1
1940 , " A:B:C $1 = Right A:B:C $1" ~:
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"::Text)])
1948 { Posting.account = ["A","B","C"]
1949 , Posting.amounts = Data.Map.fromList
1951 { Amount.quantity = 1
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 $1 + 1€ = Right A:B:C $1 + 1€" ~:
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 $1 + 1€"::Text)])
1970 { Posting.account = ["A","B","C"]
1971 , Posting.amounts = Data.Map.fromList
1973 { Amount.quantity = 1
1974 , Amount.style = Amount.Style.nil
1975 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1976 , Amount.Style.unit_spaced = Just False
1981 { Amount.quantity = 1
1982 , Amount.style = Amount.Style.nil
1983 { Amount.Style.unit_side = Just Amount.Style.Side_Right
1984 , Amount.Style.unit_spaced = Just False
1989 , Posting.sourcepos = P.newPos "" 1 1
1992 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
1993 (Data.List.map fst $
1994 Data.Either.rights $
1996 (Format.Ledger.Read.posting <* P.eof)
1997 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
2000 { Posting.account = ["A","B","C"]
2001 , Posting.amounts = Data.Map.fromList
2003 { Amount.quantity = 2
2004 , Amount.style = Amount.Style.nil
2005 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2006 , Amount.Style.unit_spaced = Just False
2011 , Posting.sourcepos = P.newPos "" 1 1
2014 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
2015 (Data.List.map fst $
2016 Data.Either.rights $
2018 (Format.Ledger.Read.posting <* P.eof)
2019 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
2022 { Posting.account = ["A","B","C"]
2023 , Posting.amounts = Data.Map.fromList
2025 { Amount.quantity = 3
2026 , Amount.style = Amount.Style.nil
2027 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2028 , Amount.Style.unit_spaced = Just False
2033 , Posting.sourcepos = P.newPos "" 1 1
2036 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
2037 (Data.List.map fst $
2038 Data.Either.rights $
2040 (Format.Ledger.Read.posting <* P.eof)
2041 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
2044 { Posting.account = ["A","B","C"]
2045 , Posting.amounts = Data.Map.fromList []
2046 , Posting.comments = [" some comment"]
2047 , Posting.sourcepos = P.newPos "" 1 1
2050 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
2051 (Data.List.map fst $
2052 Data.Either.rights $
2054 (Format.Ledger.Read.posting <* P.eof)
2055 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
2058 { Posting.account = ["A","B","C"]
2059 , Posting.amounts = Data.Map.fromList []
2060 , Posting.comments = [" some comment", " some other comment"]
2061 , Posting.sourcepos = P.newPos "" 1 1
2064 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
2065 (Data.List.map fst $
2066 Data.Either.rights $
2068 (Format.Ledger.Read.posting)
2069 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
2072 { Posting.account = ["A","B","C"]
2073 , Posting.amounts = Data.Map.fromList
2075 { Amount.quantity = 1
2076 , Amount.style = Amount.Style.nil
2077 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2078 , Amount.Style.unit_spaced = Just False
2083 , Posting.comments = [" some comment"]
2084 , Posting.sourcepos = P.newPos "" 1 1
2087 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
2088 (Data.List.map fst $
2089 Data.Either.rights $
2091 (Format.Ledger.Read.posting <* P.eof)
2092 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
2095 { Posting.account = ["A","B","C"]
2096 , Posting.comments = [" N:V"]
2097 , Posting.sourcepos = P.newPos "" 1 1
2098 , Posting.tags = Data.Map.fromList
2103 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2104 (Data.List.map fst $
2105 Data.Either.rights $
2107 (Format.Ledger.Read.posting <* P.eof)
2108 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2111 { Posting.account = ["A","B","C"]
2112 , Posting.comments = [" some comment N:V"]
2113 , Posting.sourcepos = P.newPos "" 1 1
2114 , Posting.tags = Data.Map.fromList
2119 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2120 (Data.List.map fst $
2121 Data.Either.rights $
2123 (Format.Ledger.Read.posting )
2124 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2127 { Posting.account = ["A","B","C"]
2128 , Posting.comments = [" some comment N:V v, N2:V2 v2"]
2129 , Posting.sourcepos = P.newPos "" 1 1
2130 , Posting.tags = Data.Map.fromList
2136 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2137 (Data.List.map fst $
2138 Data.Either.rights $
2140 (Format.Ledger.Read.posting <* P.eof)
2141 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2144 { Posting.account = ["A","B","C"]
2145 , Posting.comments = [" N:V", " N:V2"]
2146 , Posting.sourcepos = P.newPos "" 1 1
2147 , Posting.tags = Data.Map.fromList
2148 [ ("N", ["V", "V2"])
2152 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2153 (Data.List.map fst $
2154 Data.Either.rights $
2156 (Format.Ledger.Read.posting <* P.eof)
2157 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2160 { Posting.account = ["A","B","C"]
2161 , Posting.comments = [" N:V", " N2:V"]
2162 , Posting.sourcepos = P.newPos "" 1 1
2163 , Posting.tags = Data.Map.fromList
2169 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2170 (Data.List.map fst $
2171 Data.Either.rights $
2173 (Format.Ledger.Read.posting <* P.eof)
2174 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2177 { Posting.account = ["A","B","C"]
2178 , Posting.comments = [" date:2001/01/01"]
2182 (Time.fromGregorian 2001 01 01)
2183 (Time.TimeOfDay 0 0 0))
2186 , Posting.sourcepos = P.newPos "" 1 1
2187 , Posting.tags = Data.Map.fromList
2188 [ ("date", ["2001/01/01"])
2192 , " (A:B:C) = Right (A:B:C)" ~:
2193 (Data.Either.rights $
2195 (Format.Ledger.Read.posting <* P.eof)
2196 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
2199 { Posting.account = ["A","B","C"]
2200 , Posting.sourcepos = P.newPos "" 1 1
2202 , Posting.Type_Virtual
2205 , " [A:B:C] = Right [A:B:C]" ~:
2206 (Data.Either.rights $
2208 (Format.Ledger.Read.posting <* P.eof)
2209 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
2212 { Posting.account = ["A","B","C"]
2213 , Posting.sourcepos = P.newPos "" 1 1
2215 , Posting.Type_Virtual_Balanced
2219 , "transaction" ~: TestList
2220 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
2221 (Data.Either.rights $
2223 (Format.Ledger.Read.transaction <* P.eof)
2224 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
2227 { Transaction.dates=
2230 (Time.fromGregorian 2000 01 01)
2231 (Time.TimeOfDay 0 0 0))
2234 , Transaction.description="some description"
2235 , Transaction.postings = Posting.from_List
2237 { Posting.account = ["A","B","C"]
2238 , Posting.amounts = Data.Map.fromList
2240 { Amount.quantity = 1
2241 , Amount.style = Amount.Style.nil
2242 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2243 , Amount.Style.unit_spaced = Just False
2248 , Posting.sourcepos = P.newPos "" 2 1
2251 { Posting.account = ["a","b","c"]
2252 , Posting.sourcepos = P.newPos "" 3 1
2255 , Transaction.sourcepos = P.newPos "" 1 1
2258 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
2259 (Data.Either.rights $
2261 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
2262 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
2265 { Transaction.dates=
2268 (Time.fromGregorian 2000 01 01)
2269 (Time.TimeOfDay 0 0 0))
2272 , Transaction.description="some description"
2273 , Transaction.postings = Posting.from_List
2275 { Posting.account = ["A","B","C"]
2276 , Posting.amounts = Data.Map.fromList
2278 { Amount.quantity = 1
2279 , Amount.style = Amount.Style.nil
2280 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2281 , Amount.Style.unit_spaced = Just False
2286 , Posting.sourcepos = P.newPos "" 2 1
2289 { Posting.account = ["a","b","c"]
2290 , Posting.sourcepos = P.newPos "" 3 1
2293 , Transaction.sourcepos = P.newPos "" 1 1
2296 , "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" ~:
2297 (Data.Either.rights $
2299 (Format.Ledger.Read.transaction <* P.eof)
2300 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)])
2303 { Transaction.comments_after =
2305 , " some other;comment"
2307 , " some last comment"
2309 , Transaction.dates=
2312 (Time.fromGregorian 2000 01 01)
2313 (Time.TimeOfDay 0 0 0))
2316 , Transaction.description="some description"
2317 , Transaction.postings = Posting.from_List
2319 { Posting.account = ["A","B","C"]
2320 , Posting.amounts = Data.Map.fromList
2322 { Amount.quantity = 1
2323 , Amount.style = Amount.Style.nil
2324 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2325 , Amount.Style.unit_spaced = Just False
2330 , Posting.sourcepos = P.newPos "" 5 1
2333 { Posting.account = ["a","b","c"]
2334 , Posting.sourcepos = P.newPos "" 6 1
2335 , Posting.tags = Data.Map.fromList []
2338 , Transaction.sourcepos = P.newPos "" 1 1
2339 , Transaction.tags = Data.Map.fromList
2345 , "journal" ~: TestList
2346 [ "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
2349 (Format.Ledger.Read.journal "" {-<* P.eof-})
2350 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)
2352 (\j -> j{Format.Ledger.Journal.last_read_time=
2353 Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $
2354 Data.Either.rights [jnl])
2356 [ Format.Ledger.Journal.nil
2357 { Format.Ledger.Journal.transactions = Transaction.from_List
2359 { Transaction.dates=
2362 (Time.fromGregorian 2000 01 01)
2363 (Time.TimeOfDay 0 0 0))
2366 , Transaction.description="1° description"
2367 , Transaction.postings = Posting.from_List
2369 { Posting.account = ["A","B","C"]
2370 , Posting.amounts = Data.Map.fromList
2372 { Amount.quantity = 1
2373 , Amount.style = Amount.Style.nil
2374 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2375 , Amount.Style.unit_spaced = Just False
2380 , Posting.sourcepos = P.newPos "" 2 1
2383 { Posting.account = ["a","b","c"]
2384 , Posting.sourcepos = P.newPos "" 3 1
2387 , Transaction.sourcepos = P.newPos "" 1 1
2390 { Transaction.dates=
2393 (Time.fromGregorian 2000 01 02)
2394 (Time.TimeOfDay 0 0 0))
2397 , Transaction.description="2° description"
2398 , Transaction.postings = Posting.from_List
2400 { Posting.account = ["A","B","C"]
2401 , Posting.amounts = Data.Map.fromList
2403 { Amount.quantity = 1
2404 , Amount.style = Amount.Style.nil
2405 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2406 , Amount.Style.unit_spaced = Just False
2411 , Posting.sourcepos = P.newPos "" 5 1
2414 { Posting.account = ["x","y","z"]
2415 , Posting.sourcepos = P.newPos "" 6 1
2418 , Transaction.sourcepos = P.newPos "" 4 1
2425 , "Write" ~: TestList
2426 [ "account" ~: TestList
2428 ((Format.Ledger.Write.show False $
2429 Format.Ledger.Write.account Posting.Type_Regular
2434 ((Format.Ledger.Write.show False $
2435 Format.Ledger.Write.account Posting.Type_Regular
2440 ((Format.Ledger.Write.show False $
2441 Format.Ledger.Write.account Posting.Type_Regular
2446 ((Format.Ledger.Write.show False $
2447 Format.Ledger.Write.account Posting.Type_Virtual
2452 ((Format.Ledger.Write.show False $
2453 Format.Ledger.Write.account Posting.Type_Virtual_Balanced
2458 , "amount" ~: TestList
2460 ((Format.Ledger.Write.show False $
2461 Format.Ledger.Write.amount
2466 ((Format.Ledger.Write.show False $
2467 Format.Ledger.Write.amount
2469 { Amount.style = Amount.Style.nil
2470 { Amount.Style.precision = 2 }
2475 ((Format.Ledger.Write.show False $
2476 Format.Ledger.Write.amount
2478 { Amount.quantity = Decimal 0 123
2483 ((Format.Ledger.Write.show False $
2484 Format.Ledger.Write.amount
2486 { Amount.quantity = Decimal 0 (- 123)
2490 , "12.3 @ prec=0" ~:
2491 ((Format.Ledger.Write.show False $
2492 Format.Ledger.Write.amount
2494 { Amount.quantity = Decimal 1 123
2495 , Amount.style = Amount.Style.nil
2496 { Amount.Style.fractioning = Just '.'
2501 , "12.5 @ prec=0" ~:
2502 ((Format.Ledger.Write.show False $
2503 Format.Ledger.Write.amount
2505 { Amount.quantity = Decimal 1 125
2506 , Amount.style = Amount.Style.nil
2507 { Amount.Style.fractioning = Just '.'
2512 , "12.3 @ prec=1" ~:
2513 ((Format.Ledger.Write.show False $
2514 Format.Ledger.Write.amount
2516 { Amount.quantity = Decimal 1 123
2517 , Amount.style = Amount.Style.nil
2518 { Amount.Style.fractioning = Just '.'
2519 , Amount.Style.precision = 1
2524 , "1,234.56 @ prec=2" ~:
2525 ((Format.Ledger.Write.show False $
2526 Format.Ledger.Write.amount
2528 { Amount.quantity = Decimal 2 123456
2529 , Amount.style = Amount.Style.nil
2530 { Amount.Style.fractioning = Just '.'
2531 , Amount.Style.precision = 2
2532 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2537 , "123,456,789,01,2.3456789 @ prec=7" ~:
2538 ((Format.Ledger.Write.show False $
2539 Format.Ledger.Write.amount
2541 { Amount.quantity = Decimal 7 1234567890123456789
2542 , Amount.style = Amount.Style.nil
2543 { Amount.Style.fractioning = Just '.'
2544 , Amount.Style.precision = 7
2545 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2549 "123,456,789,01,2.3456789")
2550 , "1234567.8,90,123,456,789 @ prec=12" ~:
2551 ((Format.Ledger.Write.show False $
2552 Format.Ledger.Write.amount
2554 { Amount.quantity = Decimal 12 1234567890123456789
2555 , Amount.style = Amount.Style.nil
2556 { Amount.Style.fractioning = Just '.'
2557 , Amount.Style.precision = 12
2558 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2562 "1234567.8,90,123,456,789")
2563 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2564 ((Format.Ledger.Write.show False $
2565 Format.Ledger.Write.amount
2567 { Amount.quantity = Decimal 7 1234567890123456789
2568 , Amount.style = Amount.Style.nil
2569 { Amount.Style.fractioning = Just '.'
2570 , Amount.Style.precision = 7
2571 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2575 "1,2,3,4,5,6,7,89,012.3456789")
2576 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2577 ((Format.Ledger.Write.show False $
2578 Format.Ledger.Write.amount
2580 { Amount.quantity = Decimal 12 1234567890123456789
2581 , Amount.style = Amount.Style.nil
2582 { Amount.Style.fractioning = Just '.'
2583 , Amount.Style.precision = 12
2584 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2588 "1234567.890,12,3,4,5,6,7,8,9")
2590 , "amount_length" ~: TestList
2592 ((Format.Ledger.Write.amount_length
2597 ((Format.Ledger.Write.amount_length
2599 { Amount.style = Amount.Style.nil
2600 { Amount.Style.precision = 2 }
2605 ((Format.Ledger.Write.amount_length
2607 { Amount.quantity = Decimal 0 123
2612 ((Format.Ledger.Write.amount_length
2614 { Amount.quantity = Decimal 0 (- 123)
2618 , "12.3 @ prec=0" ~:
2619 ((Format.Ledger.Write.amount_length
2621 { Amount.quantity = Decimal 1 123
2622 , Amount.style = Amount.Style.nil
2623 { Amount.Style.fractioning = Just '.'
2628 , "12.5 @ prec=0" ~:
2629 ((Format.Ledger.Write.amount_length
2631 { Amount.quantity = Decimal 1 125
2632 , Amount.style = Amount.Style.nil
2633 { Amount.Style.fractioning = Just '.'
2638 , "12.3 @ prec=1" ~:
2639 ((Format.Ledger.Write.amount_length
2641 { Amount.quantity = Decimal 1 123
2642 , Amount.style = Amount.Style.nil
2643 { Amount.Style.fractioning = Just '.'
2644 , Amount.Style.precision = 1
2649 , "1,234.56 @ prec=2" ~:
2650 ((Format.Ledger.Write.amount_length
2652 { Amount.quantity = Decimal 2 123456
2653 , Amount.style = Amount.Style.nil
2654 { Amount.Style.fractioning = Just '.'
2655 , Amount.Style.precision = 2
2656 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2661 , "123,456,789,01,2.3456789 @ prec=7" ~:
2662 ((Format.Ledger.Write.amount_length
2664 { Amount.quantity = Decimal 7 1234567890123456789
2665 , Amount.style = Amount.Style.nil
2666 { Amount.Style.fractioning = Just '.'
2667 , Amount.Style.precision = 7
2668 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2673 , "1234567.8,90,123,456,789 @ prec=12" ~:
2674 ((Format.Ledger.Write.amount_length
2676 { Amount.quantity = Decimal 12 1234567890123456789
2677 , Amount.style = Amount.Style.nil
2678 { Amount.Style.fractioning = Just '.'
2679 , Amount.Style.precision = 12
2680 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2685 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2686 ((Format.Ledger.Write.amount_length
2688 { Amount.quantity = Decimal 7 1234567890123456789
2689 , Amount.style = Amount.Style.nil
2690 { Amount.Style.fractioning = Just '.'
2691 , Amount.Style.precision = 7
2692 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2697 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2698 ((Format.Ledger.Write.amount_length
2700 { Amount.quantity = Decimal 12 1234567890123456789
2701 , Amount.style = Amount.Style.nil
2702 { Amount.Style.fractioning = Just '.'
2703 , Amount.Style.precision = 12
2704 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2710 , "date" ~: TestList
2712 ((Format.Ledger.Write.show False $
2713 Format.Ledger.Write.date
2717 , "2000/01/01 12:34:51 CET" ~:
2718 (Format.Ledger.Write.show False $
2719 Format.Ledger.Write.date $
2722 (Time.fromGregorian 2000 01 01)
2723 (Time.TimeOfDay 12 34 51))
2724 (Time.TimeZone 60 False "CET"))
2726 "2000/01/01 12:34:51 CET"
2727 , "2000/01/01 12:34:51 +0100" ~:
2728 (Format.Ledger.Write.show False $
2729 Format.Ledger.Write.date $
2732 (Time.fromGregorian 2000 01 01)
2733 (Time.TimeOfDay 12 34 51))
2734 (Time.TimeZone 60 False ""))
2736 "2000/01/01 12:34:51 +0100"
2737 , "2000/01/01 01:02:03" ~:
2738 (Format.Ledger.Write.show False $
2739 Format.Ledger.Write.date $
2742 (Time.fromGregorian 2000 01 01)
2743 (Time.TimeOfDay 1 2 3))
2746 "2000/01/01 01:02:03"
2748 (Format.Ledger.Write.show False $
2749 Format.Ledger.Write.date $
2752 (Time.fromGregorian 0 01 01)
2753 (Time.TimeOfDay 1 2 0))
2758 (Format.Ledger.Write.show False $
2759 Format.Ledger.Write.date $
2762 (Time.fromGregorian 0 01 01)
2763 (Time.TimeOfDay 1 0 0))
2768 (Format.Ledger.Write.show False $
2769 Format.Ledger.Write.date $
2772 (Time.fromGregorian 0 01 01)
2773 (Time.TimeOfDay 0 1 0))
2778 (Format.Ledger.Write.show False $
2779 Format.Ledger.Write.date $
2782 (Time.fromGregorian 0 01 01)
2783 (Time.TimeOfDay 0 0 0))
2788 , "transaction" ~: TestList
2790 ((Format.Ledger.Write.show False $
2791 Format.Ledger.Write.transaction
2795 , "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" ~:
2796 ((Format.Ledger.Write.show False $
2797 Format.Ledger.Write.transaction $
2799 { Transaction.dates=
2802 (Time.fromGregorian 2000 01 01)
2803 (Time.TimeOfDay 0 0 0))
2806 , Transaction.description="some description"
2807 , Transaction.postings = Posting.from_List
2809 { Posting.account = ["A","B","C"]
2810 , Posting.amounts = Data.Map.fromList
2812 { Amount.quantity = 1
2813 , Amount.style = Amount.Style.nil
2814 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2815 , Amount.Style.unit_spaced = Just False
2822 { Posting.account = ["a","b","c"]
2823 , Posting.comments = ["first comment","second comment","third comment"]
2828 "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")
2829 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
2830 ((Format.Ledger.Write.show False $
2831 Format.Ledger.Write.transaction $
2833 { Transaction.dates=
2836 (Time.fromGregorian 2000 01 01)
2837 (Time.TimeOfDay 0 0 0))
2840 , Transaction.description="some description"
2841 , Transaction.postings = Posting.from_List
2843 { Posting.account = ["A","B","C"]
2844 , Posting.amounts = Data.Map.fromList
2846 { Amount.quantity = 1
2847 , Amount.style = Amount.Style.nil
2848 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2849 , Amount.Style.unit_spaced = Just False
2856 { Posting.account = ["AA","BB","CC"]
2857 , Posting.amounts = Data.Map.fromList
2859 { Amount.quantity = 123
2860 , Amount.style = Amount.Style.nil
2861 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2862 , Amount.Style.unit_spaced = Just False
2871 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")