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.Arrow ((***))
11 import Control.Monad.IO.Class (liftIO)
12 import Data.Decimal (DecimalRaw(..))
13 import qualified Data.Either
14 import qualified Data.List
15 import Data.List.NonEmpty (NonEmpty(..))
16 import qualified Data.Map.Strict as Data.Map
17 import Data.Text (Text)
18 import qualified Data.Time.Calendar as Time
19 import qualified Data.Time.LocalTime as Time
20 import qualified Text.Parsec as P
21 import qualified Text.Parsec.Pos as P
22 -- import qualified Text.PrettyPrint.Leijen.Text as PP
24 import qualified Hcompta.Model.Account as Account
25 import qualified Hcompta.Model.Amount as Amount
26 import qualified Hcompta.Model.Amount.Style as Amount.Style
27 import qualified Hcompta.Model.Date as Date
28 import qualified Hcompta.Model.Transaction as Transaction
29 import qualified Hcompta.Model.Transaction.Posting as Posting
30 import qualified Hcompta.Calc.Balance as Calc.Balance
31 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
32 import qualified Hcompta.Format.Ledger.Journal as Format.Ledger.Journal
33 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
34 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
35 import qualified Hcompta.Lib.Parsec as P
36 import qualified Hcompta.Lib.Foldable as Lib.Foldable
38 --instance Eq Text.Parsec.ParseError where
39 -- (==) = const (const False)
42 main = defaultMain $ hUnitTestToTests test_Hcompta
48 [ "TreeMap" ~: TestList
49 [ "insert" ~: TestList
51 (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty)
53 (Lib.TreeMap.TreeMap $
55 [ ((0::Int), Lib.TreeMap.leaf ())
58 (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty)
60 (Lib.TreeMap.TreeMap $
62 [ ((0::Int), Lib.TreeMap.Node
63 { Lib.TreeMap.node_value = Nothing
64 , Lib.TreeMap.node_size = 1
65 , Lib.TreeMap.node_descendants =
66 Lib.TreeMap.singleton ((1::Int):|[]) ()
73 , "map_by_depth_first" ~: TestList
76 , "flatten" ~: TestList
77 [ "[0, 0/1, 0/1/2]" ~:
78 (Lib.TreeMap.flatten id $
79 Lib.TreeMap.from_List const
91 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
92 (Lib.TreeMap.flatten id $
93 Lib.TreeMap.from_List const
102 , ((11:|2:33:[]), ())
115 , ((11:|2:33:[]), ())
119 , "Foldable" ~: TestList
120 [ "accumLeftsAndFoldrRights" ~: TestList
122 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
127 ((take 1 *** take 0) $
128 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
129 ( repeat (Left [0]) ))
132 , "Right:Left:Right:Left" ~:
133 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
134 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
136 ([1, 0], ["2", "1", "0"])
137 , "Right:Left:Right:repeat Left" ~:
138 ((take 1 *** take 2) $
139 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
140 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
146 , "Model" ~: TestList
147 [ "Account" ~: TestList
148 [ "foldr" ~: TestList
150 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
152 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
154 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
156 , "ascending" ~: TestList
158 Account.ascending ("A":|[]) ~?= Nothing
160 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
162 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
165 , "Amount" ~: TestList
170 { Amount.quantity = Decimal 0 1
171 , Amount.style = Amount.Style.nil
172 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
177 { Amount.quantity = Decimal 0 1
178 , Amount.style = Amount.Style.nil
179 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
185 { Amount.quantity = Decimal 0 2
186 , Amount.style = Amount.Style.nil
187 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
192 , "from_List" ~: TestList
193 [ "from_List [$1, 1$] = $2" ~:
196 { Amount.quantity = Decimal 0 1
197 , Amount.style = Amount.Style.nil
198 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
203 { Amount.quantity = Decimal 0 1
204 , Amount.style = Amount.Style.nil
205 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
213 { Amount.quantity = Decimal 0 2
214 , Amount.style = Amount.Style.nil
215 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
224 [ "Balance" ~: TestList
225 [ "posting" ~: TestList
226 [ "[A+$1] = A+$1 & $+1" ~:
227 (Calc.Balance.posting
228 (Posting.nil ("A":|[]))
229 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
234 { Calc.Balance.by_account =
235 Lib.TreeMap.from_List const
236 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
237 , Calc.Balance.by_unit =
239 Data.List.map Calc.Balance.assoc_unit_sum $
240 [ Calc.Balance.Unit_Sum
241 { Calc.Balance.amount = Amount.usd $ 1
242 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
247 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
249 (flip Calc.Balance.posting)
251 [ (Posting.nil ("A":|[]))
252 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
254 , (Posting.nil ("A":|[]))
255 { Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
260 { Calc.Balance.by_account =
261 Lib.TreeMap.from_List const
262 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ]) ]
263 , Calc.Balance.by_unit =
265 Data.List.map Calc.Balance.assoc_unit_sum $
266 [ Calc.Balance.Unit_Sum
267 { Calc.Balance.amount = Amount.usd $ 0
268 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
273 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
275 (flip Calc.Balance.posting)
277 [ (Posting.nil ("A":|[]))
278 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
280 , (Posting.nil ("A":|[]))
281 { Posting.amounts=Amount.from_List [ Amount.eur $ -1 ]
286 { Calc.Balance.by_account =
287 Lib.TreeMap.from_List const
288 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
289 , Calc.Balance.by_unit =
291 Data.List.map Calc.Balance.assoc_unit_sum $
292 [ Calc.Balance.Unit_Sum
293 { Calc.Balance.amount = Amount.usd $ 1
294 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
297 , Calc.Balance.Unit_Sum
298 { Calc.Balance.amount = Amount.eur $ -1
299 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
304 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
306 (flip Calc.Balance.posting)
308 [ (Posting.nil ("A":|[]))
309 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
311 , (Posting.nil ("B":|[]))
312 { Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
317 { Calc.Balance.by_account =
318 Lib.TreeMap.from_List const
319 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
320 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
322 , Calc.Balance.by_unit =
324 Data.List.map Calc.Balance.assoc_unit_sum $
325 [ Calc.Balance.Unit_Sum
326 { Calc.Balance.amount = Amount.usd $ 0
327 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
334 (flip Calc.Balance.posting)
336 [ (Posting.nil ("A":|[]))
337 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
339 , (Posting.nil ("B":|[]))
340 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
345 { Calc.Balance.by_account =
346 Lib.TreeMap.from_List const
347 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
348 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
350 , Calc.Balance.by_unit =
352 Data.List.map Calc.Balance.assoc_unit_sum $
353 [ Calc.Balance.Unit_Sum
354 { Calc.Balance.amount = Amount.usd $ 2
355 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
360 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
362 (flip Calc.Balance.posting)
364 [ (Posting.nil ("A":|[]))
365 { Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
367 , (Posting.nil ("A":|[]))
368 { Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
373 { Calc.Balance.by_account =
374 Lib.TreeMap.from_List const
375 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
377 , Calc.Balance.by_unit =
379 Data.List.map Calc.Balance.assoc_unit_sum $
380 [ Calc.Balance.Unit_Sum
381 { Calc.Balance.amount = Amount.usd $ 0
382 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
385 , Calc.Balance.Unit_Sum
386 { Calc.Balance.amount = Amount.eur $ 0
387 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
392 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
394 (flip Calc.Balance.posting)
396 [ (Posting.nil ("A":|[]))
397 { Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
399 , (Posting.nil ("B":|[]))
400 { Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
405 { Calc.Balance.by_account =
406 Lib.TreeMap.from_List const
407 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
408 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
410 , Calc.Balance.by_unit =
412 Data.List.map Calc.Balance.assoc_unit_sum $
413 [ Calc.Balance.Unit_Sum
414 { Calc.Balance.amount = Amount.usd $ 0
415 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
418 , Calc.Balance.Unit_Sum
419 { Calc.Balance.amount = Amount.eur $ 0
420 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
423 , Calc.Balance.Unit_Sum
424 { Calc.Balance.amount = Amount.gbp $ 0
425 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
431 , "union" ~: TestList
438 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
440 (Calc.Balance.Balance
441 { Calc.Balance.by_account =
442 Lib.TreeMap.from_List const
443 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
444 , Calc.Balance.by_unit =
446 Data.List.map Calc.Balance.assoc_unit_sum $
447 [ Calc.Balance.Unit_Sum
448 { Calc.Balance.amount = Amount.usd $ 1
449 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
454 (Calc.Balance.Balance
455 { Calc.Balance.by_account =
456 Lib.TreeMap.from_List const
457 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
458 , Calc.Balance.by_unit =
460 Data.List.map Calc.Balance.assoc_unit_sum $
461 [ Calc.Balance.Unit_Sum
462 { Calc.Balance.amount = Amount.usd $ 1
463 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
470 { Calc.Balance.by_account =
471 Lib.TreeMap.from_List const
472 [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
473 , Calc.Balance.by_unit =
475 Data.List.map Calc.Balance.assoc_unit_sum $
476 [ Calc.Balance.Unit_Sum
477 { Calc.Balance.amount = Amount.usd $ 2
478 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
483 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
485 (Calc.Balance.Balance
486 { Calc.Balance.by_account =
487 Lib.TreeMap.from_List const
488 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
489 , Calc.Balance.by_unit =
491 Data.List.map Calc.Balance.assoc_unit_sum $
492 [ Calc.Balance.Unit_Sum
493 { Calc.Balance.amount = Amount.usd $ 1
494 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
499 (Calc.Balance.Balance
500 { Calc.Balance.by_account =
501 Lib.TreeMap.from_List const
502 [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
503 , Calc.Balance.by_unit =
505 Data.List.map Calc.Balance.assoc_unit_sum $
506 [ Calc.Balance.Unit_Sum
507 { Calc.Balance.amount = Amount.usd $ 1
508 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
515 { Calc.Balance.by_account =
516 Lib.TreeMap.from_List const
517 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
518 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
519 , Calc.Balance.by_unit =
521 Data.List.map Calc.Balance.assoc_unit_sum $
522 [ Calc.Balance.Unit_Sum
523 { Calc.Balance.amount = Amount.usd $ 2
524 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
529 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
531 (Calc.Balance.Balance
532 { Calc.Balance.by_account =
533 Lib.TreeMap.from_List const
534 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
535 , Calc.Balance.by_unit =
537 Data.List.map Calc.Balance.assoc_unit_sum $
538 [ Calc.Balance.Unit_Sum
539 { Calc.Balance.amount = Amount.usd $ 1
540 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
545 (Calc.Balance.Balance
546 { Calc.Balance.by_account =
547 Lib.TreeMap.from_List const
548 [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
549 , Calc.Balance.by_unit =
551 Data.List.map Calc.Balance.assoc_unit_sum $
552 [ Calc.Balance.Unit_Sum
553 { Calc.Balance.amount = Amount.eur $ 1
554 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
561 { Calc.Balance.by_account =
562 Lib.TreeMap.from_List const
563 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
564 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
565 , Calc.Balance.by_unit =
567 Data.List.map Calc.Balance.assoc_unit_sum $
568 [ Calc.Balance.Unit_Sum
569 { Calc.Balance.amount = Amount.usd $ 1
570 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
573 , Calc.Balance.Unit_Sum
574 { Calc.Balance.amount = Amount.eur $ 1
575 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
581 , "expanded" ~: TestList
582 [ "nil_By_Account" ~:
583 Calc.Balance.expanded
584 Calc.Balance.nil_By_Account
588 Calc.Balance.expanded
589 (Lib.TreeMap.from_List const
590 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
592 (Lib.TreeMap.from_List const
593 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
594 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
595 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
598 , "A/A+$1 = A+$1 A/A+$1" ~:
599 Calc.Balance.expanded
600 (Lib.TreeMap.from_List const
601 [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
603 (Lib.TreeMap.from_List const
604 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
605 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
606 , Calc.Balance.exclusive = Amount.from_List []
608 , ("A":|["A"], Calc.Balance.Account_Sum_Expanded
609 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
610 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
613 , "A/B+$1 = A+$1 A/B+$1" ~:
614 Calc.Balance.expanded
615 (Lib.TreeMap.from_List const
616 [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
618 (Lib.TreeMap.from_List const
619 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
620 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
621 , Calc.Balance.exclusive = Amount.from_List []
623 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
624 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
625 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
628 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
629 Calc.Balance.expanded
630 (Lib.TreeMap.from_List const
631 [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
633 (Lib.TreeMap.from_List const
634 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
635 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
636 , Calc.Balance.exclusive = Amount.from_List []
638 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
639 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
640 , Calc.Balance.exclusive = Amount.from_List []
642 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
643 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
644 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
647 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
648 Calc.Balance.expanded
649 (Lib.TreeMap.from_List const
650 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
651 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
654 (Lib.TreeMap.from_List const
655 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
656 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
657 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
659 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
660 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
661 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
664 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
665 Calc.Balance.expanded
666 (Lib.TreeMap.from_List const
667 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
668 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
669 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
672 (Lib.TreeMap.from_List const
673 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
674 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
675 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
677 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
678 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
679 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
681 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
682 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
683 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
686 , "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" ~:
687 Calc.Balance.expanded
688 (Lib.TreeMap.from_List const
689 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
690 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
691 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
692 , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
695 (Lib.TreeMap.from_List const
696 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
697 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 4 ]
698 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
700 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
701 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
702 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
704 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
705 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
706 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
708 , ("A":|["B", "C", "D"], Calc.Balance.Account_Sum_Expanded
709 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
710 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
713 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
714 Calc.Balance.expanded
715 (Lib.TreeMap.from_List const
716 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
717 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
718 , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
719 , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ])
722 (Lib.TreeMap.from_List const
723 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
724 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
725 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
727 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
728 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
729 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
731 , ("A":|["BB"], Calc.Balance.Account_Sum_Expanded
732 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
733 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
735 , ("AA":|[], Calc.Balance.Account_Sum_Expanded
736 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
737 , Calc.Balance.exclusive = Amount.from_List []
739 , ("AA":|["B"], Calc.Balance.Account_Sum_Expanded
740 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
741 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
745 , "deviation" ~: TestList
747 (Calc.Balance.deviation $
749 { Calc.Balance.by_account =
750 Lib.TreeMap.from_List const
751 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
752 , ("B":|[], Amount.from_List [])
754 , Calc.Balance.by_unit =
756 Data.List.map Calc.Balance.assoc_unit_sum $
757 [ Calc.Balance.Unit_Sum
758 { Calc.Balance.amount = Amount.usd $ 1
759 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
765 (Calc.Balance.Deviation $
767 Data.List.map Calc.Balance.assoc_unit_sum $
768 [ Calc.Balance.Unit_Sum
769 { Calc.Balance.amount = Amount.usd $ 1
770 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
774 , "{A+$1 B+$1, $2}" ~:
775 (Calc.Balance.deviation $
777 { Calc.Balance.by_account =
778 Lib.TreeMap.from_List const
779 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
780 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
782 , Calc.Balance.by_unit =
784 Data.List.map Calc.Balance.assoc_unit_sum $
785 [ Calc.Balance.Unit_Sum
786 { Calc.Balance.amount = Amount.usd $ 2
787 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
795 (Calc.Balance.Deviation $
797 Data.List.map Calc.Balance.assoc_unit_sum $
798 [ Calc.Balance.Unit_Sum
799 { Calc.Balance.amount = Amount.usd $ 2
800 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
806 , "is_equilibrium_inferrable" ~: TestList
807 [ "nil" ~: TestCase $
809 Calc.Balance.is_equilibrium_inferrable $
810 Calc.Balance.deviation $
812 , "{A+$0, $+0}" ~: TestCase $
814 Calc.Balance.is_equilibrium_inferrable $
815 Calc.Balance.deviation $
817 { Calc.Balance.by_account =
818 Lib.TreeMap.from_List const
819 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
821 , Calc.Balance.by_unit =
823 Data.List.map Calc.Balance.assoc_unit_sum $
824 [ Calc.Balance.Unit_Sum
825 { Calc.Balance.amount = Amount.usd $ 0
826 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
831 , "{A+$1, $+1}" ~: TestCase $
833 Calc.Balance.is_equilibrium_inferrable $
834 Calc.Balance.deviation $
836 { Calc.Balance.by_account =
837 Lib.TreeMap.from_List const
838 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
840 , Calc.Balance.by_unit =
842 Data.List.map Calc.Balance.assoc_unit_sum $
843 [ Calc.Balance.Unit_Sum
844 { Calc.Balance.amount = Amount.usd $ 1
845 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
850 , "{A+$0+€0, $0 €+0}" ~: TestCase $
852 Calc.Balance.is_equilibrium_inferrable $
853 Calc.Balance.deviation $
855 { Calc.Balance.by_account =
856 Lib.TreeMap.from_List const
857 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
859 , Calc.Balance.by_unit =
861 Data.List.map Calc.Balance.assoc_unit_sum $
862 [ Calc.Balance.Unit_Sum
863 { Calc.Balance.amount = Amount.usd $ 0
864 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
867 , Calc.Balance.Unit_Sum
868 { Calc.Balance.amount = Amount.eur $ 0
869 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
874 , "{A+$1, B-$1, $+0}" ~: TestCase $
876 Calc.Balance.is_equilibrium_inferrable $
877 Calc.Balance.deviation $
879 { Calc.Balance.by_account =
880 Lib.TreeMap.from_List const
881 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
882 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
884 , Calc.Balance.by_unit =
886 Data.List.map Calc.Balance.assoc_unit_sum $
887 [ Calc.Balance.Unit_Sum
888 { Calc.Balance.amount = Amount.usd $ 0
889 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
894 , "{A+$1 B, $+1}" ~: TestCase $
896 Calc.Balance.is_equilibrium_inferrable $
897 Calc.Balance.deviation $
899 { Calc.Balance.by_account =
900 Lib.TreeMap.from_List const
901 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
902 , ("B":|[], Amount.from_List [])
904 , Calc.Balance.by_unit =
906 Data.List.map Calc.Balance.assoc_unit_sum $
907 [ Calc.Balance.Unit_Sum
908 { Calc.Balance.amount = Amount.usd $ 1
909 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
914 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
916 Calc.Balance.is_equilibrium_inferrable $
917 Calc.Balance.deviation $
919 { Calc.Balance.by_account =
920 Lib.TreeMap.from_List const
921 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
922 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
924 , Calc.Balance.by_unit =
926 Data.List.map Calc.Balance.assoc_unit_sum $
927 [ Calc.Balance.Unit_Sum
928 { Calc.Balance.amount = Amount.usd $ 1
929 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
932 , Calc.Balance.Unit_Sum
933 { Calc.Balance.amount = Amount.eur $ 1
934 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
939 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
941 Calc.Balance.is_equilibrium_inferrable $
942 Calc.Balance.deviation $
944 { Calc.Balance.by_account =
945 Lib.TreeMap.from_List const
946 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
947 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
949 , Calc.Balance.by_unit =
951 Data.List.map Calc.Balance.assoc_unit_sum $
952 [ Calc.Balance.Unit_Sum
953 { Calc.Balance.amount = Amount.usd $ 0
954 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
957 , Calc.Balance.Unit_Sum
958 { Calc.Balance.amount = Amount.eur $ 1
959 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
964 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
966 Calc.Balance.is_equilibrium_inferrable $
967 Calc.Balance.deviation $
969 { Calc.Balance.by_account =
970 Lib.TreeMap.from_List const
971 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
972 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
974 , Calc.Balance.by_unit =
976 Data.List.map Calc.Balance.assoc_unit_sum $
977 [ Calc.Balance.Unit_Sum
978 { Calc.Balance.amount = Amount.usd $ 0
979 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
982 , Calc.Balance.Unit_Sum
983 { Calc.Balance.amount = Amount.eur $ 0
984 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
987 , Calc.Balance.Unit_Sum
988 { Calc.Balance.amount = Amount.gbp $ 0
989 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
995 , "infer_equilibrium" ~: TestList
997 (snd $ Calc.Balance.infer_equilibrium $
999 [ (Posting.nil ("A":|[]))
1000 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] }
1001 , (Posting.nil ("B":|[]))
1002 { Posting.amounts=Amount.from_List [] }
1007 [ (Posting.nil ("A":|[]))
1008 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] }
1009 , (Posting.nil ("B":|[]))
1010 { Posting.amounts=Amount.from_List [ Amount.usd $ -1 ] }
1013 (snd $ Calc.Balance.infer_equilibrium $
1015 [ (Posting.nil ("A":|[]))
1016 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] }
1017 , (Posting.nil ("B":|[]))
1018 { Posting.amounts=Amount.from_List [ Amount.eur $ -1 ] }
1023 [ (Posting.nil ("A":|[]))
1024 { Posting.amounts=Amount.from_List [ Amount.eur $ 1 ] }
1025 , (Posting.nil ("A":|[]))
1026 { Posting.amounts=Amount.from_List [ Amount.usd $ 1] }
1027 , (Posting.nil ("B":|[]))
1028 { Posting.amounts=Amount.from_List [ Amount.usd $ -1 ] }
1029 , (Posting.nil ("B":|[]))
1030 { Posting.amounts=Amount.from_List [ Amount.eur $ -1 ] }
1033 (snd $ Calc.Balance.infer_equilibrium $
1035 [ (Posting.nil ("A":|[]))
1036 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] }
1037 , (Posting.nil ("B":|[]))
1038 { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ] }
1042 [ Calc.Balance.Unit_Sum
1043 { Calc.Balance.amount = Amount.usd $ 2
1044 , Calc.Balance.accounts = Data.Map.fromList []}
1049 , "Format" ~: TestList
1050 [ "Ledger" ~: TestList
1051 [ "Read" ~: TestList
1052 [ "account_name" ~: TestList
1054 (Data.Either.rights $
1056 (Format.Ledger.Read.account_name <* P.eof)
1061 (Data.Either.rights $
1063 (Format.Ledger.Read.account_name <* P.eof)
1068 (Data.Either.rights $
1070 (Format.Ledger.Read.account_name <* P.eof)
1071 () "" ("AA"::Text)])
1075 (Data.Either.rights $
1077 (Format.Ledger.Read.account_name <* P.eof)
1082 (Data.Either.rights $
1084 (Format.Ledger.Read.account_name <* P.eof)
1089 (Data.Either.rights $
1091 (Format.Ledger.Read.account_name <* P.eof)
1092 () "" ("A:"::Text)])
1096 (Data.Either.rights $
1098 (Format.Ledger.Read.account_name <* P.eof)
1099 () "" (":A"::Text)])
1103 (Data.Either.rights $
1105 (Format.Ledger.Read.account_name <* P.eof)
1106 () "" ("A "::Text)])
1110 (Data.Either.rights $
1112 (Format.Ledger.Read.account_name)
1113 () "" ("A "::Text)])
1117 (Data.Either.rights $
1119 (Format.Ledger.Read.account_name <* P.eof)
1120 () "" ("A A"::Text)])
1124 (Data.Either.rights $
1126 (Format.Ledger.Read.account_name <* P.eof)
1127 () "" ("A "::Text)])
1131 (Data.Either.rights $
1133 (Format.Ledger.Read.account_name <* P.eof)
1134 () "" ("A \n"::Text)])
1138 (Data.Either.rights $
1140 (Format.Ledger.Read.account_name <* P.eof)
1141 () "" ("(A)A"::Text)])
1145 (Data.Either.rights $
1147 (Format.Ledger.Read.account_name <* P.eof)
1148 () "" ("( )A"::Text)])
1152 (Data.Either.rights $
1154 (Format.Ledger.Read.account_name <* P.eof)
1155 () "" ("(A) A"::Text)])
1159 (Data.Either.rights $
1161 (Format.Ledger.Read.account_name <* P.eof)
1162 () "" ("[ ]A"::Text)])
1166 (Data.Either.rights $
1168 (Format.Ledger.Read.account_name <* P.eof)
1169 () "" ("(A) "::Text)])
1173 (Data.Either.rights $
1175 (Format.Ledger.Read.account_name <* P.eof)
1176 () "" ("(A)"::Text)])
1180 (Data.Either.rights $
1182 (Format.Ledger.Read.account_name <* P.eof)
1183 () "" ("A(A)"::Text)])
1187 (Data.Either.rights $
1189 (Format.Ledger.Read.account_name <* P.eof)
1190 () "" ("[A]A"::Text)])
1194 (Data.Either.rights $
1196 (Format.Ledger.Read.account_name <* P.eof)
1197 () "" ("[A] A"::Text)])
1201 (Data.Either.rights $
1203 (Format.Ledger.Read.account_name <* P.eof)
1204 () "" ("[A] "::Text)])
1208 (Data.Either.rights $
1210 (Format.Ledger.Read.account_name <* P.eof)
1211 () "" ("[A]"::Text)])
1215 , "account" ~: TestList
1217 (Data.Either.rights $
1219 (Format.Ledger.Read.account <* P.eof)
1224 (Data.Either.rights $
1226 (Format.Ledger.Read.account <* P.eof)
1231 (Data.Either.rights $
1233 (Format.Ledger.Read.account <* P.eof)
1234 () "" ("A:"::Text)])
1238 (Data.Either.rights $
1240 (Format.Ledger.Read.account <* P.eof)
1241 () "" (":A"::Text)])
1245 (Data.Either.rights $
1247 (Format.Ledger.Read.account <* P.eof)
1248 () "" ("A "::Text)])
1252 (Data.Either.rights $
1254 (Format.Ledger.Read.account <* P.eof)
1255 () "" (" A"::Text)])
1259 (Data.Either.rights $
1261 (Format.Ledger.Read.account <* P.eof)
1262 () "" ("A:B"::Text)])
1266 (Data.Either.rights $
1268 (Format.Ledger.Read.account <* P.eof)
1269 () "" ("A:B:C"::Text)])
1272 , "\"Aa:Bbb:Cccc\"" ~:
1273 (Data.Either.rights $
1275 (Format.Ledger.Read.account <* P.eof)
1276 () "" ("Aa:Bbb:Cccc"::Text)])
1278 ["Aa":|["Bbb", "Cccc"]]
1279 , "\"A a : B b b : C c c c\"" ~:
1280 (Data.Either.rights $
1282 (Format.Ledger.Read.account <* P.eof)
1283 () "" ("A a : B b b : C c c c"::Text)])
1285 ["A a ":|[" B b b ", " C c c c"]]
1287 (Data.Either.rights $
1289 (Format.Ledger.Read.account <* P.eof)
1290 () "" ("A: :C"::Text)])
1294 (Data.Either.rights $
1296 (Format.Ledger.Read.account <* P.eof)
1297 () "" ("A::C"::Text)])
1301 (Data.Either.rights $
1303 (Format.Ledger.Read.account <* P.eof)
1304 () "" ("A:B:(C)"::Text)])
1308 , "posting_type" ~: TestList
1310 Format.Ledger.Read.posting_type
1313 (Posting.Type_Regular, "A":|[])
1315 Format.Ledger.Read.posting_type
1318 (Posting.Type_Regular, "(":|[])
1320 Format.Ledger.Read.posting_type
1323 (Posting.Type_Regular, ")":|[])
1325 Format.Ledger.Read.posting_type
1328 (Posting.Type_Regular, "()":|[])
1330 Format.Ledger.Read.posting_type
1333 (Posting.Type_Regular, "( )":|[])
1335 Format.Ledger.Read.posting_type
1338 (Posting.Type_Virtual, "A":|[])
1340 Format.Ledger.Read.posting_type
1343 (Posting.Type_Virtual, "A":|["B", "C"])
1345 Format.Ledger.Read.posting_type
1348 (Posting.Type_Regular, "A":|["B", "C"])
1350 Format.Ledger.Read.posting_type
1353 (Posting.Type_Regular, "(A)":|["B", "C"])
1355 Format.Ledger.Read.posting_type
1358 (Posting.Type_Regular, "A":|["(B)", "C"])
1360 Format.Ledger.Read.posting_type
1363 (Posting.Type_Regular, "A":|["B", "(C)"])
1365 Format.Ledger.Read.posting_type
1368 (Posting.Type_Regular, "[":|[])
1370 Format.Ledger.Read.posting_type
1373 (Posting.Type_Regular, "]":|[])
1375 Format.Ledger.Read.posting_type
1378 (Posting.Type_Regular, "[]":|[])
1380 Format.Ledger.Read.posting_type
1383 (Posting.Type_Regular, "[ ]":|[])
1385 Format.Ledger.Read.posting_type
1388 (Posting.Type_Virtual_Balanced, "A":|[])
1390 Format.Ledger.Read.posting_type
1393 (Posting.Type_Virtual_Balanced, "A":|["B", "C"])
1395 Format.Ledger.Read.posting_type
1398 (Posting.Type_Regular, "A":|["B", "C"])
1400 Format.Ledger.Read.posting_type
1403 (Posting.Type_Regular, "[A]":|["B", "C"])
1405 Format.Ledger.Read.posting_type
1408 (Posting.Type_Regular, "A":|["[B]", "C"])
1410 Format.Ledger.Read.posting_type
1413 (Posting.Type_Regular, "A":|["B", "[C]"])
1415 , "amount" ~: TestList
1417 (Data.Either.rights $
1419 (Format.Ledger.Read.amount <* P.eof)
1423 , "\"0\" = Right 0" ~:
1424 (Data.Either.rights $
1426 (Format.Ledger.Read.amount <* P.eof)
1430 { Amount.quantity = Decimal 0 0
1432 , "\"00\" = Right 0" ~:
1433 (Data.Either.rights $
1435 (Format.Ledger.Read.amount <* P.eof)
1436 () "" ("00"::Text)])
1439 { Amount.quantity = Decimal 0 0
1441 , "\"0.\" = Right 0." ~:
1442 (Data.Either.rights $
1444 (Format.Ledger.Read.amount <* P.eof)
1445 () "" ("0."::Text)])
1448 { Amount.quantity = Decimal 0 0
1451 { Amount.Style.fractioning = Just '.'
1454 , "\".0\" = Right 0.0" ~:
1455 (Data.Either.rights $
1457 (Format.Ledger.Read.amount <* P.eof)
1458 () "" (".0"::Text)])
1461 { Amount.quantity = Decimal 0 0
1464 { Amount.Style.fractioning = Just '.'
1465 , Amount.Style.precision = 1
1468 , "\"0,\" = Right 0," ~:
1469 (Data.Either.rights $
1471 (Format.Ledger.Read.amount <* P.eof)
1472 () "" ("0,"::Text)])
1475 { Amount.quantity = Decimal 0 0
1478 { Amount.Style.fractioning = Just ','
1481 , "\",0\" = Right 0,0" ~:
1482 (Data.Either.rights $
1484 (Format.Ledger.Read.amount <* P.eof)
1485 () "" (",0"::Text)])
1488 { Amount.quantity = Decimal 0 0
1491 { Amount.Style.fractioning = Just ','
1492 , Amount.Style.precision = 1
1495 , "\"0_\" = Left" ~:
1496 (Data.Either.rights $
1498 (Format.Ledger.Read.amount <* P.eof)
1499 () "" ("0_"::Text)])
1502 , "\"_0\" = Left" ~:
1503 (Data.Either.rights $
1505 (Format.Ledger.Read.amount <* P.eof)
1506 () "" ("_0"::Text)])
1509 , "\"0.0\" = Right 0.0" ~:
1510 (Data.Either.rights $
1512 (Format.Ledger.Read.amount <* P.eof)
1513 () "" ("0.0"::Text)])
1516 { Amount.quantity = Decimal 0 0
1519 { Amount.Style.fractioning = Just '.'
1520 , Amount.Style.precision = 1
1523 , "\"00.00\" = Right 0.00" ~:
1524 (Data.Either.rights $
1526 (Format.Ledger.Read.amount <* P.eof)
1527 () "" ("00.00"::Text)])
1530 { Amount.quantity = Decimal 0 0
1533 { Amount.Style.fractioning = Just '.'
1534 , Amount.Style.precision = 2
1537 , "\"0,0\" = Right 0,0" ~:
1538 (Data.Either.rights $
1540 (Format.Ledger.Read.amount <* P.eof)
1541 () "" ("0,0"::Text)])
1544 { Amount.quantity = Decimal 0 0
1547 { Amount.Style.fractioning = Just ','
1548 , Amount.Style.precision = 1
1551 , "\"00,00\" = Right 0,00" ~:
1552 (Data.Either.rights $
1554 (Format.Ledger.Read.amount <* P.eof)
1555 () "" ("00,00"::Text)])
1558 { Amount.quantity = Decimal 0 0
1561 { Amount.Style.fractioning = Just ','
1562 , Amount.Style.precision = 2
1565 , "\"0_0\" = Right 0" ~:
1566 (Data.Either.rights $
1568 (Format.Ledger.Read.amount <* P.eof)
1569 () "" ("0_0"::Text)])
1572 { Amount.quantity = Decimal 0 0
1575 { Amount.Style.fractioning = Nothing
1576 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1577 , Amount.Style.precision = 0
1580 , "\"00_00\" = Right 0" ~:
1581 (Data.Either.rights $
1583 (Format.Ledger.Read.amount <* P.eof)
1584 () "" ("00_00"::Text)])
1587 { Amount.quantity = Decimal 0 0
1590 { Amount.Style.fractioning = Nothing
1591 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1592 , Amount.Style.precision = 0
1595 , "\"0,000.00\" = Right 0,000.00" ~:
1596 (Data.Either.rights $
1598 (Format.Ledger.Read.amount <* P.eof)
1599 () "" ("0,000.00"::Text)])
1602 { Amount.quantity = Decimal 0 0
1605 { Amount.Style.fractioning = Just '.'
1606 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1607 , Amount.Style.precision = 2
1610 , "\"0.000,00\" = Right 0.000,00" ~:
1611 (Data.Either.rights $
1613 (Format.Ledger.Read.amount)
1614 () "" ("0.000,00"::Text)])
1617 { Amount.quantity = Decimal 0 0
1620 { Amount.Style.fractioning = Just ','
1621 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1622 , Amount.Style.precision = 2
1625 , "\"1,000.00\" = Right 1,000.00" ~:
1626 (Data.Either.rights $
1628 (Format.Ledger.Read.amount <* P.eof)
1629 () "" ("1,000.00"::Text)])
1632 { Amount.quantity = Decimal 0 1000
1635 { Amount.Style.fractioning = Just '.'
1636 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1637 , Amount.Style.precision = 2
1640 , "\"1.000,00\" = Right 1.000,00" ~:
1641 (Data.Either.rights $
1643 (Format.Ledger.Read.amount)
1644 () "" ("1.000,00"::Text)])
1647 { Amount.quantity = Decimal 0 1000
1650 { Amount.Style.fractioning = Just ','
1651 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1652 , Amount.Style.precision = 2
1655 , "\"1,000.00.\" = Left" ~:
1656 (Data.Either.rights $
1658 (Format.Ledger.Read.amount)
1659 () "" ("1,000.00."::Text)])
1662 , "\"1.000,00,\" = Left" ~:
1663 (Data.Either.rights $
1665 (Format.Ledger.Read.amount)
1666 () "" ("1.000,00,"::Text)])
1669 , "\"1,000.00_\" = Left" ~:
1670 (Data.Either.rights $
1672 (Format.Ledger.Read.amount)
1673 () "" ("1,000.00_"::Text)])
1676 , "\"12\" = Right 12" ~:
1677 (Data.Either.rights $
1679 (Format.Ledger.Read.amount <* P.eof)
1680 () "" ("123"::Text)])
1683 { Amount.quantity = Decimal 0 123
1685 , "\"1.2\" = Right 1.2" ~:
1686 (Data.Either.rights $
1688 (Format.Ledger.Read.amount <* P.eof)
1689 () "" ("1.2"::Text)])
1692 { Amount.quantity = Decimal 1 12
1695 { Amount.Style.fractioning = Just '.'
1696 , Amount.Style.precision = 1
1699 , "\"1,2\" = Right 1,2" ~:
1700 (Data.Either.rights $
1702 (Format.Ledger.Read.amount <* P.eof)
1703 () "" ("1,2"::Text)])
1706 { Amount.quantity = Decimal 1 12
1709 { Amount.Style.fractioning = Just ','
1710 , Amount.Style.precision = 1
1713 , "\"12.23\" = Right 12.23" ~:
1714 (Data.Either.rights $
1716 (Format.Ledger.Read.amount <* P.eof)
1717 () "" ("12.34"::Text)])
1720 { Amount.quantity = Decimal 2 1234
1723 { Amount.Style.fractioning = Just '.'
1724 , Amount.Style.precision = 2
1727 , "\"12,23\" = Right 12,23" ~:
1728 (Data.Either.rights $
1730 (Format.Ledger.Read.amount <* P.eof)
1731 () "" ("12,34"::Text)])
1734 { Amount.quantity = Decimal 2 1234
1737 { Amount.Style.fractioning = Just ','
1738 , Amount.Style.precision = 2
1741 , "\"1_2\" = Right 1_2" ~:
1742 (Data.Either.rights $
1744 (Format.Ledger.Read.amount <* P.eof)
1745 () "" ("1_2"::Text)])
1748 { Amount.quantity = Decimal 0 12
1751 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1752 , Amount.Style.precision = 0
1755 , "\"1_23\" = Right 1_23" ~:
1756 (Data.Either.rights $
1758 (Format.Ledger.Read.amount <* P.eof)
1759 () "" ("1_23"::Text)])
1762 { Amount.quantity = Decimal 0 123
1765 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1766 , Amount.Style.precision = 0
1769 , "\"1_23_456\" = Right 1_23_456" ~:
1770 (Data.Either.rights $
1772 (Format.Ledger.Read.amount <* P.eof)
1773 () "" ("1_23_456"::Text)])
1776 { Amount.quantity = Decimal 0 123456
1779 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1780 , Amount.Style.precision = 0
1783 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1784 (Data.Either.rights $
1786 (Format.Ledger.Read.amount <* P.eof)
1787 () "" ("1_23_456.7890_12345_678901"::Text)])
1790 { Amount.quantity = Decimal 15 123456789012345678901
1793 { Amount.Style.fractioning = Just '.'
1794 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1795 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1796 , Amount.Style.precision = 15
1799 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1800 (Data.Either.rights $
1802 (Format.Ledger.Read.amount <* P.eof)
1803 () "" ("123456_78901_2345.678_90_1"::Text)])
1806 { Amount.quantity = Decimal 6 123456789012345678901
1809 { Amount.Style.fractioning = Just '.'
1810 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1811 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1812 , Amount.Style.precision = 6
1815 , "\"$1\" = Right $1" ~:
1816 (Data.Either.rights $
1818 (Format.Ledger.Read.amount <* P.eof)
1819 () "" ("$1"::Text)])
1822 { Amount.quantity = Decimal 0 1
1825 { Amount.Style.fractioning = Nothing
1826 , Amount.Style.grouping_integral = Nothing
1827 , Amount.Style.grouping_fractional = Nothing
1828 , Amount.Style.precision = 0
1829 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1830 , Amount.Style.unit_spaced = Just False
1834 , "\"1$\" = Right 1$" ~:
1835 (Data.Either.rights $
1837 (Format.Ledger.Read.amount <* P.eof)
1838 () "" ("1$"::Text)])
1841 { Amount.quantity = Decimal 0 1
1844 { Amount.Style.fractioning = Nothing
1845 , Amount.Style.grouping_integral = Nothing
1846 , Amount.Style.grouping_fractional = Nothing
1847 , Amount.Style.precision = 0
1848 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1849 , Amount.Style.unit_spaced = Just False
1853 , "\"$ 1\" = Right $ 1" ~:
1854 (Data.Either.rights $
1856 (Format.Ledger.Read.amount <* P.eof)
1857 () "" ("$ 1"::Text)])
1860 { Amount.quantity = Decimal 0 1
1863 { Amount.Style.fractioning = Nothing
1864 , Amount.Style.grouping_integral = Nothing
1865 , Amount.Style.grouping_fractional = Nothing
1866 , Amount.Style.precision = 0
1867 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1868 , Amount.Style.unit_spaced = Just True
1872 , "\"1 $\" = Right 1 $" ~:
1873 (Data.Either.rights $
1875 (Format.Ledger.Read.amount <* P.eof)
1876 () "" ("1 $"::Text)])
1879 { Amount.quantity = Decimal 0 1
1882 { Amount.Style.fractioning = Nothing
1883 , Amount.Style.grouping_integral = Nothing
1884 , Amount.Style.grouping_fractional = Nothing
1885 , Amount.Style.precision = 0
1886 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1887 , Amount.Style.unit_spaced = Just True
1891 , "\"-$1\" = Right $-1" ~:
1892 (Data.Either.rights $
1894 (Format.Ledger.Read.amount <* P.eof)
1895 () "" ("-$1"::Text)])
1898 { Amount.quantity = Decimal 0 (-1)
1901 { Amount.Style.fractioning = Nothing
1902 , Amount.Style.grouping_integral = Nothing
1903 , Amount.Style.grouping_fractional = Nothing
1904 , Amount.Style.precision = 0
1905 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1906 , Amount.Style.unit_spaced = Just False
1910 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1911 (Data.Either.rights $
1913 (Format.Ledger.Read.amount <* P.eof)
1914 () "" ("\"4 2\"1"::Text)])
1917 { Amount.quantity = Decimal 0 1
1920 { Amount.Style.fractioning = Nothing
1921 , Amount.Style.grouping_integral = Nothing
1922 , Amount.Style.grouping_fractional = Nothing
1923 , Amount.Style.precision = 0
1924 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1925 , Amount.Style.unit_spaced = Just False
1927 , Amount.unit = "4 2"
1929 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1930 (Data.Either.rights $
1932 (Format.Ledger.Read.amount <* P.eof)
1933 () "" ("1\"4 2\""::Text)])
1936 { Amount.quantity = Decimal 0 1
1939 { Amount.Style.fractioning = Nothing
1940 , Amount.Style.grouping_integral = Nothing
1941 , Amount.Style.grouping_fractional = Nothing
1942 , Amount.Style.precision = 0
1943 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1944 , Amount.Style.unit_spaced = Just False
1946 , Amount.unit = "4 2"
1948 , "\"$1.000,00\" = Right $1.000,00" ~:
1949 (Data.Either.rights $
1951 (Format.Ledger.Read.amount <* P.eof)
1952 () "" ("$1.000,00"::Text)])
1955 { Amount.quantity = Decimal 0 1000
1958 { Amount.Style.fractioning = Just ','
1959 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1960 , Amount.Style.grouping_fractional = Nothing
1961 , Amount.Style.precision = 2
1962 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1963 , Amount.Style.unit_spaced = Just False
1967 , "\"1.000,00$\" = Right 1.000,00$" ~:
1968 (Data.Either.rights $
1970 (Format.Ledger.Read.amount <* P.eof)
1971 () "" ("1.000,00$"::Text)])
1974 { Amount.quantity = Decimal 0 1000
1977 { Amount.Style.fractioning = Just ','
1978 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1979 , Amount.Style.grouping_fractional = Nothing
1980 , Amount.Style.precision = 2
1981 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1982 , Amount.Style.unit_spaced = Just False
1987 , "comment" ~: TestList
1988 [ "; some comment = Right \" some comment\"" ~:
1989 (Data.Either.rights $
1991 (Format.Ledger.Read.comment <* P.eof)
1992 () "" ("; some comment"::Text)])
1995 , "; some comment \\n = Right \" some comment \"" ~:
1996 (Data.Either.rights $
1998 (Format.Ledger.Read.comment <* P.newline <* P.eof)
1999 () "" ("; some comment \n"::Text)])
2001 [ " some comment " ]
2002 , "; some comment \\r\\n = Right \" some comment \"" ~:
2003 (Data.Either.rights $
2005 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
2006 () "" ("; some comment \r\n"::Text)])
2008 [ " some comment " ]
2010 , "comments" ~: TestList
2011 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
2012 (Data.Either.rights $
2014 (Format.Ledger.Read.comments <* P.eof)
2015 () "" ("; some comment\n ; some other comment"::Text)])
2017 [ [" some comment", " some other comment"] ]
2018 , "; some comment \\n = Right \" some comment \"" ~:
2019 (Data.Either.rights $
2021 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
2022 () "" ("; some comment \n"::Text)])
2024 [ [" some comment "] ]
2026 , "date" ~: TestList
2028 (Data.Either.rights $
2030 (Format.Ledger.Read.date Nothing <* P.eof)
2031 () "" ("2000/01/01"::Text)])
2035 (Time.fromGregorian 2000 01 01)
2036 (Time.TimeOfDay 0 0 0))
2038 , "2000/01/01 some text" ~:
2039 (Data.Either.rights $
2041 (Format.Ledger.Read.date Nothing)
2042 () "" ("2000/01/01 some text"::Text)])
2046 (Time.fromGregorian 2000 01 01)
2047 (Time.TimeOfDay 0 0 0))
2049 , "2000/01/01 12:34" ~:
2050 (Data.Either.rights $
2052 (Format.Ledger.Read.date Nothing <* P.eof)
2053 () "" ("2000/01/01 12:34"::Text)])
2057 (Time.fromGregorian 2000 01 01)
2058 (Time.TimeOfDay 12 34 0))
2060 , "2000/01/01 12:34:56" ~:
2061 (Data.Either.rights $
2063 (Format.Ledger.Read.date Nothing <* P.eof)
2064 () "" ("2000/01/01 12:34:56"::Text)])
2068 (Time.fromGregorian 2000 01 01)
2069 (Time.TimeOfDay 12 34 56))
2071 , "2000/01/01 12:34 CET" ~:
2072 (Data.Either.rights $
2074 (Format.Ledger.Read.date Nothing <* P.eof)
2075 () "" ("2000/01/01 12:34 CET"::Text)])
2079 (Time.fromGregorian 2000 01 01)
2080 (Time.TimeOfDay 12 34 0))
2081 (Time.TimeZone 60 True "CET")]
2082 , "2000/01/01 12:34 +0130" ~:
2083 (Data.Either.rights $
2085 (Format.Ledger.Read.date Nothing <* P.eof)
2086 () "" ("2000/01/01 12:34 +0130"::Text)])
2090 (Time.fromGregorian 2000 01 01)
2091 (Time.TimeOfDay 12 34 0))
2092 (Time.TimeZone 90 False "+0130")]
2093 , "2000/01/01 12:34:56 CET" ~:
2094 (Data.Either.rights $
2096 (Format.Ledger.Read.date Nothing <* P.eof)
2097 () "" ("2000/01/01 12:34:56 CET"::Text)])
2101 (Time.fromGregorian 2000 01 01)
2102 (Time.TimeOfDay 12 34 56))
2103 (Time.TimeZone 60 True "CET")]
2105 (Data.Either.rights $
2107 (Format.Ledger.Read.date Nothing <* P.eof)
2108 () "" ("2001/02/29"::Text)])
2112 (Data.Either.rights $
2114 (Format.Ledger.Read.date (Just 2000) <* P.eof)
2115 () "" ("01/01"::Text)])
2119 (Time.fromGregorian 2000 01 01)
2120 (Time.TimeOfDay 0 0 0))
2123 , "tag_value" ~: TestList
2125 (Data.Either.rights $
2127 (Format.Ledger.Read.tag_value <* P.eof)
2132 (Data.Either.rights $
2134 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
2135 () "" (",\n"::Text)])
2139 (Data.Either.rights $
2141 (Format.Ledger.Read.tag_value <* P.eof)
2142 () "" (",x"::Text)])
2146 (Data.Either.rights $
2148 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
2149 () "" (",x:"::Text)])
2153 (Data.Either.rights $
2155 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
2156 () "" ("v, v, n:"::Text)])
2162 (Data.Either.rights $
2164 (Format.Ledger.Read.tag <* P.eof)
2165 () "" ("Name:"::Text)])
2169 (Data.Either.rights $
2171 (Format.Ledger.Read.tag <* P.eof)
2172 () "" ("Name:Value"::Text)])
2175 , "Name:Value\\n" ~:
2176 (Data.Either.rights $
2178 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
2179 () "" ("Name:Value\n"::Text)])
2183 (Data.Either.rights $
2185 (Format.Ledger.Read.tag <* P.eof)
2186 () "" ("Name:Val ue"::Text)])
2188 [("Name", "Val ue")]
2190 (Data.Either.rights $
2192 (Format.Ledger.Read.tag <* P.eof)
2193 () "" ("Name:,"::Text)])
2197 (Data.Either.rights $
2199 (Format.Ledger.Read.tag <* P.eof)
2200 () "" ("Name:Val,ue"::Text)])
2202 [("Name", "Val,ue")]
2204 (Data.Either.rights $
2206 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
2207 () "" ("Name:Val,ue:"::Text)])
2211 , "tags" ~: TestList
2213 (Data.Either.rights $
2215 (Format.Ledger.Read.tags <* P.eof)
2216 () "" ("Name:"::Text)])
2223 (Data.Either.rights $
2225 (Format.Ledger.Read.tags <* P.eof)
2226 () "" ("Name:,"::Text)])
2233 (Data.Either.rights $
2235 (Format.Ledger.Read.tags <* P.eof)
2236 () "" ("Name:,Name:"::Text)])
2239 [ ("Name", ["", ""])
2243 (Data.Either.rights $
2245 (Format.Ledger.Read.tags <* P.eof)
2246 () "" ("Name:,Name2:"::Text)])
2253 , "Name: , Name2:" ~:
2254 (Data.Either.rights $
2256 (Format.Ledger.Read.tags <* P.eof)
2257 () "" ("Name: , Name2:"::Text)])
2264 , "Name:,Name2:,Name3:" ~:
2265 (Data.Either.rights $
2267 (Format.Ledger.Read.tags <* P.eof)
2268 () "" ("Name:,Name2:,Name3:"::Text)])
2276 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
2277 (Data.Either.rights $
2279 (Format.Ledger.Read.tags <* P.eof)
2280 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
2283 [ ("Name", ["Val ue"])
2284 , ("Name2", ["V a l u e"])
2285 , ("Name3", ["V al ue"])
2289 , "posting" ~: TestList
2290 [ " A:B:C = Right A:B:C" ~:
2291 (Data.Either.rights $
2293 (Format.Ledger.Read.posting <* P.eof)
2294 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
2296 [ ( (Posting.nil ("A":|["B", "C"]))
2297 { Posting.sourcepos = P.newPos "" 1 1
2299 , Posting.Type_Regular
2302 , " !A:B:C = Right !A:B:C" ~:
2303 (Data.List.map fst $
2304 Data.Either.rights $
2306 (Format.Ledger.Read.posting <* P.eof)
2307 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
2309 [ (Posting.nil ("A":|["B", "C"]))
2310 { Posting.sourcepos = P.newPos "" 1 1
2311 , Posting.status = True
2314 , " *A:B:C = Right *A:B:C" ~:
2315 (Data.List.map fst $
2316 Data.Either.rights $
2318 (Format.Ledger.Read.posting <* P.eof)
2319 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
2321 [ (Posting.nil ("A":|["B", "C"]))
2322 { Posting.amounts = Data.Map.fromList []
2323 , Posting.comments = []
2324 , Posting.dates = []
2325 , Posting.status = True
2326 , Posting.sourcepos = P.newPos "" 1 1
2327 , Posting.tags = Data.Map.fromList []
2330 , " A:B:C $1 = Right A:B:C $1" ~:
2331 (Data.List.map fst $
2332 Data.Either.rights $
2334 (Format.Ledger.Read.posting <* P.eof)
2335 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
2337 [ (Posting.nil ("A":|["B","C $1"]))
2338 { Posting.sourcepos = P.newPos "" 1 1
2341 , " A:B:C $1 = Right A:B:C $1" ~:
2342 (Data.List.map fst $
2343 Data.Either.rights $
2345 (Format.Ledger.Read.posting <* P.eof)
2346 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
2348 [ (Posting.nil ("A":|["B", "C"]))
2349 { Posting.amounts = Data.Map.fromList
2351 { Amount.quantity = 1
2352 , Amount.style = Amount.Style.nil
2353 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2354 , Amount.Style.unit_spaced = Just False
2359 , Posting.sourcepos = P.newPos "" 1 1
2362 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
2363 (Data.List.map fst $
2364 Data.Either.rights $
2366 (Format.Ledger.Read.posting <* P.eof)
2367 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
2369 [ (Posting.nil ("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 { Amount.quantity = 1
2381 , Amount.style = Amount.Style.nil
2382 { Amount.Style.unit_side = Just Amount.Style.Side_Right
2383 , Amount.Style.unit_spaced = Just False
2388 , Posting.sourcepos = P.newPos "" 1 1
2391 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
2392 (Data.List.map fst $
2393 Data.Either.rights $
2395 (Format.Ledger.Read.posting <* P.eof)
2396 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
2398 [ (Posting.nil ("A":|["B", "C"]))
2399 { Posting.amounts = Data.Map.fromList
2401 { Amount.quantity = 2
2402 , Amount.style = Amount.Style.nil
2403 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2404 , Amount.Style.unit_spaced = Just False
2409 , Posting.sourcepos = P.newPos "" 1 1
2412 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
2413 (Data.List.map fst $
2414 Data.Either.rights $
2416 (Format.Ledger.Read.posting <* P.eof)
2417 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
2419 [ (Posting.nil ("A":|["B", "C"]))
2420 { Posting.amounts = Data.Map.fromList
2422 { Amount.quantity = 3
2423 , Amount.style = Amount.Style.nil
2424 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2425 , Amount.Style.unit_spaced = Just False
2430 , Posting.sourcepos = P.newPos "" 1 1
2433 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
2434 (Data.List.map fst $
2435 Data.Either.rights $
2437 (Format.Ledger.Read.posting <* P.eof)
2438 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
2440 [ (Posting.nil ("A":|["B", "C"]))
2441 { Posting.amounts = Data.Map.fromList []
2442 , Posting.comments = [" some comment"]
2443 , Posting.sourcepos = P.newPos "" 1 1
2446 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
2447 (Data.List.map fst $
2448 Data.Either.rights $
2450 (Format.Ledger.Read.posting <* P.eof)
2451 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
2453 [ (Posting.nil ("A":|["B", "C"]))
2454 { Posting.amounts = Data.Map.fromList []
2455 , Posting.comments = [" some comment", " some other comment"]
2456 , Posting.sourcepos = P.newPos "" 1 1
2459 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
2460 (Data.List.map fst $
2461 Data.Either.rights $
2463 (Format.Ledger.Read.posting)
2464 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
2466 [ (Posting.nil ("A":|["B", "C"]))
2467 { Posting.amounts = Data.Map.fromList
2469 { Amount.quantity = 1
2470 , Amount.style = Amount.Style.nil
2471 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2472 , Amount.Style.unit_spaced = Just False
2477 , Posting.comments = [" some comment"]
2478 , Posting.sourcepos = P.newPos "" 1 1
2481 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
2482 (Data.List.map fst $
2483 Data.Either.rights $
2485 (Format.Ledger.Read.posting <* P.eof)
2486 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
2488 [ (Posting.nil ("A":|["B", "C"]))
2489 { Posting.comments = [" N:V"]
2490 , Posting.sourcepos = P.newPos "" 1 1
2491 , Posting.tags = Data.Map.fromList
2496 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2497 (Data.List.map fst $
2498 Data.Either.rights $
2500 (Format.Ledger.Read.posting <* P.eof)
2501 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2503 [ (Posting.nil ("A":|["B", "C"]))
2504 { Posting.comments = [" some comment N:V"]
2505 , Posting.sourcepos = P.newPos "" 1 1
2506 , Posting.tags = Data.Map.fromList
2511 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2512 (Data.List.map fst $
2513 Data.Either.rights $
2515 (Format.Ledger.Read.posting )
2516 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2518 [ (Posting.nil ("A":|["B", "C"]))
2519 { Posting.comments = [" some comment N:V v, N2:V2 v2"]
2520 , Posting.sourcepos = P.newPos "" 1 1
2521 , Posting.tags = Data.Map.fromList
2527 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2528 (Data.List.map fst $
2529 Data.Either.rights $
2531 (Format.Ledger.Read.posting <* P.eof)
2532 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2534 [ (Posting.nil ("A":|["B", "C"]))
2535 { Posting.comments = [" N:V", " N:V2"]
2536 , Posting.sourcepos = P.newPos "" 1 1
2537 , Posting.tags = Data.Map.fromList
2538 [ ("N", ["V", "V2"])
2542 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2543 (Data.List.map fst $
2544 Data.Either.rights $
2546 (Format.Ledger.Read.posting <* P.eof)
2547 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2549 [ (Posting.nil ("A":|["B", "C"]))
2550 { Posting.comments = [" N:V", " N2:V"]
2551 , Posting.sourcepos = P.newPos "" 1 1
2552 , Posting.tags = Data.Map.fromList
2558 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2559 (Data.List.map fst $
2560 Data.Either.rights $
2562 (Format.Ledger.Read.posting <* P.eof)
2563 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2565 [ (Posting.nil ("A":|["B", "C"]))
2566 { Posting.comments = [" date:2001/01/01"]
2570 (Time.fromGregorian 2001 01 01)
2571 (Time.TimeOfDay 0 0 0))
2574 , Posting.sourcepos = P.newPos "" 1 1
2575 , Posting.tags = Data.Map.fromList
2576 [ ("date", ["2001/01/01"])
2580 , " (A:B:C) = Right (A:B:C)" ~:
2581 (Data.Either.rights $
2583 (Format.Ledger.Read.posting <* P.eof)
2584 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
2586 [ ( (Posting.nil ("A":|["B", "C"]))
2587 { Posting.sourcepos = P.newPos "" 1 1
2589 , Posting.Type_Virtual
2592 , " [A:B:C] = Right [A:B:C]" ~:
2593 (Data.Either.rights $
2595 (Format.Ledger.Read.posting <* P.eof)
2596 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
2598 [ ( (Posting.nil ("A":|["B", "C"]))
2599 { Posting.sourcepos = P.newPos "" 1 1
2601 , Posting.Type_Virtual_Balanced
2605 , "transaction" ~: TestList
2606 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
2607 (Data.Either.rights $
2608 [P.runParser_with_Error
2609 (Format.Ledger.Read.transaction <* P.eof)
2610 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
2613 { Transaction.dates=
2616 (Time.fromGregorian 2000 01 01)
2617 (Time.TimeOfDay 0 0 0))
2620 , Transaction.description="some description"
2621 , Transaction.postings = Posting.from_List
2622 [ (Posting.nil ("A":|["B", "C"]))
2623 { Posting.amounts = Data.Map.fromList
2625 { Amount.quantity = 1
2626 , Amount.style = Amount.Style.nil
2627 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2628 , Amount.Style.unit_spaced = Just False
2633 , Posting.sourcepos = P.newPos "" 2 1
2635 , (Posting.nil ("a":|["b", "c"]))
2636 { Posting.sourcepos = P.newPos "" 3 1
2639 , Transaction.sourcepos = P.newPos "" 1 1
2642 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
2643 (Data.Either.rights $
2644 [P.runParser_with_Error
2645 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
2646 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
2649 { Transaction.dates=
2652 (Time.fromGregorian 2000 01 01)
2653 (Time.TimeOfDay 0 0 0))
2656 , Transaction.description="some description"
2657 , Transaction.postings = Posting.from_List
2658 [ (Posting.nil ("A":|["B", "C"]))
2659 { Posting.amounts = Data.Map.fromList
2661 { Amount.quantity = 1
2662 , Amount.style = Amount.Style.nil
2663 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2664 , Amount.Style.unit_spaced = Just False
2669 , Posting.sourcepos = P.newPos "" 2 1
2671 , (Posting.nil ("a":|["b", "c"]))
2672 { Posting.sourcepos = P.newPos "" 3 1
2675 , Transaction.sourcepos = P.newPos "" 1 1
2678 , "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" ~:
2679 (Data.Either.rights $
2680 [P.runParser_with_Error
2681 (Format.Ledger.Read.transaction <* P.eof)
2682 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)])
2685 { Transaction.comments_after =
2687 , " some other;comment"
2689 , " some last comment"
2691 , Transaction.dates=
2694 (Time.fromGregorian 2000 01 01)
2695 (Time.TimeOfDay 0 0 0))
2698 , Transaction.description="some description"
2699 , Transaction.postings = Posting.from_List
2700 [ (Posting.nil ("A":|["B", "C"]))
2701 { Posting.amounts = Data.Map.fromList
2703 { Amount.quantity = 1
2704 , Amount.style = Amount.Style.nil
2705 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2706 , Amount.Style.unit_spaced = Just False
2711 , Posting.sourcepos = P.newPos "" 5 1
2713 , (Posting.nil ("a":|["b", "c"]))
2714 { Posting.sourcepos = P.newPos "" 6 1
2715 , Posting.tags = Data.Map.fromList []
2718 , Transaction.sourcepos = P.newPos "" 1 1
2719 , Transaction.tags = Data.Map.fromList
2725 , "journal" ~: TestList
2726 [ "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
2728 P.runParserT_with_Error
2729 (Format.Ledger.Read.journal "" {-<* P.eof-})
2730 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)
2732 (\j -> j{Format.Ledger.Journal.last_read_time=
2733 Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $
2734 Data.Either.rights [jnl])
2736 [ Format.Ledger.Journal.nil
2737 { Format.Ledger.Journal.transactions = Transaction.from_List
2739 { Transaction.dates=
2742 (Time.fromGregorian 2000 01 01)
2743 (Time.TimeOfDay 0 0 0))
2746 , Transaction.description="1° description"
2747 , Transaction.postings = Posting.from_List
2748 [ (Posting.nil ("A":|["B", "C"]))
2749 { Posting.amounts = Data.Map.fromList
2751 { Amount.quantity = 1
2752 , Amount.style = Amount.Style.nil
2753 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2754 , Amount.Style.unit_spaced = Just False
2759 , Posting.sourcepos = P.newPos "" 2 1
2761 , (Posting.nil ("a":|["b", "c"]))
2762 { Posting.sourcepos = P.newPos "" 3 1
2765 , Transaction.sourcepos = P.newPos "" 1 1
2768 { Transaction.dates=
2771 (Time.fromGregorian 2000 01 02)
2772 (Time.TimeOfDay 0 0 0))
2775 , Transaction.description="2° description"
2776 , Transaction.postings = Posting.from_List
2777 [ (Posting.nil ("A":|["B", "C"]))
2778 { Posting.amounts = Data.Map.fromList
2780 { Amount.quantity = 1
2781 , Amount.style = Amount.Style.nil
2782 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2783 , Amount.Style.unit_spaced = Just False
2788 , Posting.sourcepos = P.newPos "" 5 1
2790 , (Posting.nil ("x":|["y", "z"]))
2791 { Posting.sourcepos = P.newPos "" 6 1
2794 , Transaction.sourcepos = P.newPos "" 4 1
2801 , "Write" ~: TestList
2802 [ "account" ~: TestList
2804 ((Format.Ledger.Write.show False $
2805 Format.Ledger.Write.account Posting.Type_Regular $
2810 ((Format.Ledger.Write.show False $
2811 Format.Ledger.Write.account Posting.Type_Regular $
2816 ((Format.Ledger.Write.show False $
2817 Format.Ledger.Write.account Posting.Type_Virtual $
2822 ((Format.Ledger.Write.show False $
2823 Format.Ledger.Write.account Posting.Type_Virtual_Balanced $
2828 , "amount" ~: TestList
2830 ((Format.Ledger.Write.show False $
2831 Format.Ledger.Write.amount
2836 ((Format.Ledger.Write.show False $
2837 Format.Ledger.Write.amount
2839 { Amount.style = Amount.Style.nil
2840 { Amount.Style.precision = 2 }
2845 ((Format.Ledger.Write.show False $
2846 Format.Ledger.Write.amount
2848 { Amount.quantity = Decimal 0 123
2853 ((Format.Ledger.Write.show False $
2854 Format.Ledger.Write.amount
2856 { Amount.quantity = Decimal 0 (- 123)
2860 , "12.3 @ prec=0" ~:
2861 ((Format.Ledger.Write.show False $
2862 Format.Ledger.Write.amount
2864 { Amount.quantity = Decimal 1 123
2865 , Amount.style = Amount.Style.nil
2866 { Amount.Style.fractioning = Just '.'
2871 , "12.5 @ prec=0" ~:
2872 ((Format.Ledger.Write.show False $
2873 Format.Ledger.Write.amount
2875 { Amount.quantity = Decimal 1 125
2876 , Amount.style = Amount.Style.nil
2877 { Amount.Style.fractioning = Just '.'
2882 , "12.3 @ prec=1" ~:
2883 ((Format.Ledger.Write.show False $
2884 Format.Ledger.Write.amount
2886 { Amount.quantity = Decimal 1 123
2887 , Amount.style = Amount.Style.nil
2888 { Amount.Style.fractioning = Just '.'
2889 , Amount.Style.precision = 1
2894 , "1,234.56 @ prec=2" ~:
2895 ((Format.Ledger.Write.show False $
2896 Format.Ledger.Write.amount
2898 { Amount.quantity = Decimal 2 123456
2899 , Amount.style = Amount.Style.nil
2900 { Amount.Style.fractioning = Just '.'
2901 , Amount.Style.precision = 2
2902 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2907 , "123,456,789,01,2.3456789 @ prec=7" ~:
2908 ((Format.Ledger.Write.show False $
2909 Format.Ledger.Write.amount
2911 { Amount.quantity = Decimal 7 1234567890123456789
2912 , Amount.style = Amount.Style.nil
2913 { Amount.Style.fractioning = Just '.'
2914 , Amount.Style.precision = 7
2915 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2919 "123,456,789,01,2.3456789")
2920 , "1234567.8,90,123,456,789 @ prec=12" ~:
2921 ((Format.Ledger.Write.show False $
2922 Format.Ledger.Write.amount
2924 { Amount.quantity = Decimal 12 1234567890123456789
2925 , Amount.style = Amount.Style.nil
2926 { Amount.Style.fractioning = Just '.'
2927 , Amount.Style.precision = 12
2928 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2932 "1234567.8,90,123,456,789")
2933 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2934 ((Format.Ledger.Write.show False $
2935 Format.Ledger.Write.amount
2937 { Amount.quantity = Decimal 7 1234567890123456789
2938 , Amount.style = Amount.Style.nil
2939 { Amount.Style.fractioning = Just '.'
2940 , Amount.Style.precision = 7
2941 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2945 "1,2,3,4,5,6,7,89,012.3456789")
2946 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2947 ((Format.Ledger.Write.show False $
2948 Format.Ledger.Write.amount
2950 { Amount.quantity = Decimal 12 1234567890123456789
2951 , Amount.style = Amount.Style.nil
2952 { Amount.Style.fractioning = Just '.'
2953 , Amount.Style.precision = 12
2954 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2958 "1234567.890,12,3,4,5,6,7,8,9")
2960 , "amount_length" ~: TestList
2962 ((Format.Ledger.Write.amount_length
2967 ((Format.Ledger.Write.amount_length
2969 { Amount.style = Amount.Style.nil
2970 { Amount.Style.precision = 2 }
2975 ((Format.Ledger.Write.amount_length
2977 { Amount.quantity = Decimal 0 123
2982 ((Format.Ledger.Write.amount_length
2984 { Amount.quantity = Decimal 0 (- 123)
2988 , "12.3 @ prec=0" ~:
2989 ((Format.Ledger.Write.amount_length
2991 { Amount.quantity = Decimal 1 123
2992 , Amount.style = Amount.Style.nil
2993 { Amount.Style.fractioning = Just '.'
2998 , "12.5 @ prec=0" ~:
2999 ((Format.Ledger.Write.amount_length
3001 { Amount.quantity = Decimal 1 125
3002 , Amount.style = Amount.Style.nil
3003 { Amount.Style.fractioning = Just '.'
3008 , "12.3 @ prec=1" ~:
3009 ((Format.Ledger.Write.amount_length
3011 { Amount.quantity = Decimal 1 123
3012 , Amount.style = Amount.Style.nil
3013 { Amount.Style.fractioning = Just '.'
3014 , Amount.Style.precision = 1
3019 , "1,234.56 @ prec=2" ~:
3020 ((Format.Ledger.Write.amount_length
3022 { Amount.quantity = Decimal 2 123456
3023 , Amount.style = Amount.Style.nil
3024 { Amount.Style.fractioning = Just '.'
3025 , Amount.Style.precision = 2
3026 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
3031 , "123,456,789,01,2.3456789 @ prec=7" ~:
3032 ((Format.Ledger.Write.amount_length
3034 { Amount.quantity = Decimal 7 1234567890123456789
3035 , Amount.style = Amount.Style.nil
3036 { Amount.Style.fractioning = Just '.'
3037 , Amount.Style.precision = 7
3038 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3043 , "1234567.8,90,123,456,789 @ prec=12" ~:
3044 ((Format.Ledger.Write.amount_length
3046 { Amount.quantity = Decimal 12 1234567890123456789
3047 , Amount.style = Amount.Style.nil
3048 { Amount.Style.fractioning = Just '.'
3049 , Amount.Style.precision = 12
3050 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3055 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
3056 ((Format.Ledger.Write.amount_length
3058 { Amount.quantity = Decimal 7 1234567890123456789
3059 , Amount.style = Amount.Style.nil
3060 { Amount.Style.fractioning = Just '.'
3061 , Amount.Style.precision = 7
3062 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3067 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
3068 ((Format.Ledger.Write.amount_length
3070 { Amount.quantity = Decimal 12 1234567890123456789
3071 , Amount.style = Amount.Style.nil
3072 { Amount.Style.fractioning = Just '.'
3073 , Amount.Style.precision = 12
3074 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3080 , "date" ~: TestList
3082 ((Format.Ledger.Write.show False $
3083 Format.Ledger.Write.date
3087 , "2000/01/01 12:34:51 CET" ~:
3088 (Format.Ledger.Write.show False $
3089 Format.Ledger.Write.date $
3092 (Time.fromGregorian 2000 01 01)
3093 (Time.TimeOfDay 12 34 51))
3094 (Time.TimeZone 60 False "CET"))
3096 "2000/01/01 12:34:51 CET"
3097 , "2000/01/01 12:34:51 +0100" ~:
3098 (Format.Ledger.Write.show False $
3099 Format.Ledger.Write.date $
3102 (Time.fromGregorian 2000 01 01)
3103 (Time.TimeOfDay 12 34 51))
3104 (Time.TimeZone 60 False ""))
3106 "2000/01/01 12:34:51 +0100"
3107 , "2000/01/01 01:02:03" ~:
3108 (Format.Ledger.Write.show False $
3109 Format.Ledger.Write.date $
3112 (Time.fromGregorian 2000 01 01)
3113 (Time.TimeOfDay 1 2 3))
3116 "2000/01/01 01:02:03"
3118 (Format.Ledger.Write.show False $
3119 Format.Ledger.Write.date $
3122 (Time.fromGregorian 0 01 01)
3123 (Time.TimeOfDay 1 2 0))
3128 (Format.Ledger.Write.show False $
3129 Format.Ledger.Write.date $
3132 (Time.fromGregorian 0 01 01)
3133 (Time.TimeOfDay 1 0 0))
3138 (Format.Ledger.Write.show False $
3139 Format.Ledger.Write.date $
3142 (Time.fromGregorian 0 01 01)
3143 (Time.TimeOfDay 0 1 0))
3148 (Format.Ledger.Write.show False $
3149 Format.Ledger.Write.date $
3152 (Time.fromGregorian 0 01 01)
3153 (Time.TimeOfDay 0 0 0))
3158 , "transaction" ~: TestList
3160 ((Format.Ledger.Write.show False $
3161 Format.Ledger.Write.transaction
3165 , "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" ~:
3166 ((Format.Ledger.Write.show False $
3167 Format.Ledger.Write.transaction $
3169 { Transaction.dates=
3172 (Time.fromGregorian 2000 01 01)
3173 (Time.TimeOfDay 0 0 0))
3176 , Transaction.description="some description"
3177 , Transaction.postings = Posting.from_List
3178 [ (Posting.nil ("A":|["B", "C"]))
3179 { Posting.amounts = Data.Map.fromList
3181 { Amount.quantity = 1
3182 , Amount.style = Amount.Style.nil
3183 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3184 , Amount.Style.unit_spaced = Just False
3190 , (Posting.nil ("a":|["b", "c"]))
3191 { Posting.comments = ["first comment","second comment","third comment"]
3196 "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")
3197 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
3198 ((Format.Ledger.Write.show False $
3199 Format.Ledger.Write.transaction $
3201 { Transaction.dates=
3204 (Time.fromGregorian 2000 01 01)
3205 (Time.TimeOfDay 0 0 0))
3208 , Transaction.description="some description"
3209 , Transaction.postings = Posting.from_List
3210 [ (Posting.nil ("A":|["B", "C"]))
3211 { Posting.amounts = Data.Map.fromList
3213 { Amount.quantity = 1
3214 , Amount.style = Amount.Style.nil
3215 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3216 , Amount.Style.unit_spaced = Just False
3222 , (Posting.nil ("AA":|["BB", "CC"]))
3223 { Posting.amounts = Data.Map.fromList
3225 { Amount.quantity = 123
3226 , Amount.style = Amount.Style.nil
3227 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3228 , Amount.Style.unit_spaced = Just False
3237 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")