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 hiding (char, string)
21 import qualified Text.Parsec.Pos as P
22 -- import qualified Text.PrettyPrint.Leijen.Text as PP
24 import qualified Hcompta.Model.Account as Account
25 import 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.Calc.Balance as Calc.Balance
29 import qualified Hcompta.Format.Ledger as Format.Ledger
30 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
31 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
32 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
33 import qualified Hcompta.Lib.Parsec as P
34 import qualified Hcompta.Lib.Foldable as Lib.Foldable
36 --instance Eq Text.Parsec.ParseError where
37 -- (==) = const (const False)
40 main = defaultMain $ hUnitTestToTests test_Hcompta
46 [ "TreeMap" ~: TestList
47 [ "insert" ~: TestList
49 (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty)
51 (Lib.TreeMap.TreeMap $
53 [ ((0::Int), Lib.TreeMap.leaf ())
56 (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty)
58 (Lib.TreeMap.TreeMap $
60 [ ((0::Int), Lib.TreeMap.Node
61 { Lib.TreeMap.node_value = Nothing
62 , Lib.TreeMap.node_size = 1
63 , Lib.TreeMap.node_descendants =
64 Lib.TreeMap.singleton ((1::Int):|[]) ()
71 , "map_by_depth_first" ~: TestList
74 , "flatten" ~: TestList
75 [ "[0, 0/1, 0/1/2]" ~:
76 (Lib.TreeMap.flatten id $
77 Lib.TreeMap.from_List const
78 [ (((0::Integer):|[]), ())
89 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
90 (Lib.TreeMap.flatten id $
91 Lib.TreeMap.from_List const
100 , ((11:|2:33:[]), ())
105 [ (((1::Integer):|[]), ())
113 , ((11:|2:33:[]), ())
117 , "Foldable" ~: TestList
118 [ "accumLeftsAndFoldrRights" ~: TestList
120 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
123 (([(0::Integer)], [(""::String)]))
125 ((take 1 *** take 0) $
126 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
127 ( repeat (Left [0]) ))
129 ([(0::Integer)], ([]::[String]))
130 , "Right:Left:Right:Left" ~:
131 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
132 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
134 (([1, 0]::[Integer]), (["2", "1", "0"]::[String]))
135 , "Right:Left:Right:repeat Left" ~:
136 ((take 1 *** take 2) $
137 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
138 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
140 (([1]::[Integer]), (["2", "1"]::[String]))
144 , "Model" ~: TestList
145 [ "Account" ~: TestList
146 [ "foldr" ~: TestList
148 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
150 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
152 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
154 , "ascending" ~: TestList
156 Account.ascending ("A":|[]) ~?= Nothing
158 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
160 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
163 , "Amount" ~: TestList
168 { Amount.quantity = Decimal 0 1
169 , Amount.style = Amount.Style.nil
170 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
175 { Amount.quantity = Decimal 0 1
176 , Amount.style = Amount.Style.nil
177 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
183 { Amount.quantity = Decimal 0 2
184 , Amount.style = Amount.Style.nil
185 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
190 , "from_List" ~: TestList
191 [ "from_List [$1, 1$] = $2" ~:
194 { Amount.quantity = Decimal 0 1
195 , Amount.style = Amount.Style.nil
196 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
201 { Amount.quantity = Decimal 0 1
202 , Amount.style = Amount.Style.nil
203 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
211 { Amount.quantity = Decimal 0 2
212 , Amount.style = Amount.Style.nil
213 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
222 [ "Balance" ~: TestList
223 [ "posting" ~: TestList
224 [ "[A+$1] = A+$1 & $+1" ~:
225 (Calc.Balance.posting
226 (Format.Ledger.posting ("A":|[]))
227 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
229 Calc.Balance.balance)
232 { Calc.Balance.balance_by_account =
233 Lib.TreeMap.from_List const
234 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
235 , Calc.Balance.balance_by_unit =
237 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
238 [ Calc.Balance.Unit_Sum
239 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
240 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
245 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
247 (flip Calc.Balance.posting)
249 [ (Format.Ledger.posting ("A":|[]))
250 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
252 , (Format.Ledger.posting ("A":|[]))
253 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
258 { Calc.Balance.balance_by_account =
259 Lib.TreeMap.from_List const
260 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ]) ]
261 , Calc.Balance.balance_by_unit =
263 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
264 [ Calc.Balance.Unit_Sum
265 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
266 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
271 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
273 (flip Calc.Balance.posting)
275 [ (Format.Ledger.posting ("A":|[]))
276 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
278 , (Format.Ledger.posting ("A":|[]))
279 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ]
284 { Calc.Balance.balance_by_account =
285 Lib.TreeMap.from_List const
286 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
287 , Calc.Balance.balance_by_unit =
289 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
290 [ Calc.Balance.Unit_Sum
291 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
292 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
295 , Calc.Balance.Unit_Sum
296 { Calc.Balance.unit_sum_amount = Amount.eur $ -1
297 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
302 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
304 (flip Calc.Balance.posting)
306 [ (Format.Ledger.posting ("A":|[]))
307 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
309 , (Format.Ledger.posting ("B":|[]))
310 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
315 { Calc.Balance.balance_by_account =
316 Lib.TreeMap.from_List const
317 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
318 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
320 , Calc.Balance.balance_by_unit =
322 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
323 [ Calc.Balance.Unit_Sum
324 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
325 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
332 (flip Calc.Balance.posting)
334 [ (Format.Ledger.posting ("A":|[]))
335 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
337 , (Format.Ledger.posting ("B":|[]))
338 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
343 { Calc.Balance.balance_by_account =
344 Lib.TreeMap.from_List const
345 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
346 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
348 , Calc.Balance.balance_by_unit =
350 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
351 [ Calc.Balance.Unit_Sum
352 { Calc.Balance.unit_sum_amount = Amount.usd $ 2
353 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
358 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
360 (flip Calc.Balance.posting)
362 [ (Format.Ledger.posting ("A":|[]))
363 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
365 , (Format.Ledger.posting ("A":|[]))
366 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
371 { Calc.Balance.balance_by_account =
372 Lib.TreeMap.from_List const
373 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
375 , Calc.Balance.balance_by_unit =
377 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
378 [ Calc.Balance.Unit_Sum
379 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
380 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
383 , Calc.Balance.Unit_Sum
384 { Calc.Balance.unit_sum_amount = Amount.eur $ 0
385 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
390 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
392 (flip Calc.Balance.posting)
394 [ (Format.Ledger.posting ("A":|[]))
395 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
397 , (Format.Ledger.posting ("B":|[]))
398 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
403 { Calc.Balance.balance_by_account =
404 Lib.TreeMap.from_List const
405 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
406 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
408 , Calc.Balance.balance_by_unit =
410 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
411 [ Calc.Balance.Unit_Sum
412 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
413 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
416 , Calc.Balance.Unit_Sum
417 { Calc.Balance.unit_sum_amount = Amount.eur $ 0
418 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
421 , Calc.Balance.Unit_Sum
422 { Calc.Balance.unit_sum_amount = Amount.gbp $ 0
423 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
429 , "union" ~: TestList
435 (Calc.Balance.balance::Calc.Balance.Balance Int String)
436 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
438 (Calc.Balance.Balance
439 { Calc.Balance.balance_by_account =
440 Lib.TreeMap.from_List const
441 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
442 , Calc.Balance.balance_by_unit =
444 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
445 [ Calc.Balance.Unit_Sum
446 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
447 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
452 (Calc.Balance.Balance
453 { Calc.Balance.balance_by_account =
454 Lib.TreeMap.from_List const
455 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
456 , Calc.Balance.balance_by_unit =
458 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
459 [ Calc.Balance.Unit_Sum
460 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
461 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
468 { Calc.Balance.balance_by_account =
469 Lib.TreeMap.from_List const
470 [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
471 , Calc.Balance.balance_by_unit =
473 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
474 [ Calc.Balance.Unit_Sum
475 { Calc.Balance.unit_sum_amount = Amount.usd $ 2
476 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
481 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
483 (Calc.Balance.Balance
484 { Calc.Balance.balance_by_account =
485 Lib.TreeMap.from_List const
486 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
487 , Calc.Balance.balance_by_unit =
489 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
490 [ Calc.Balance.Unit_Sum
491 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
492 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
497 (Calc.Balance.Balance
498 { Calc.Balance.balance_by_account =
499 Lib.TreeMap.from_List const
500 [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
501 , Calc.Balance.balance_by_unit =
503 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
504 [ Calc.Balance.Unit_Sum
505 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
506 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
513 { Calc.Balance.balance_by_account =
514 Lib.TreeMap.from_List const
515 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
516 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
517 , Calc.Balance.balance_by_unit =
519 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
520 [ Calc.Balance.Unit_Sum
521 { Calc.Balance.unit_sum_amount = Amount.usd $ 2
522 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
527 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
529 (Calc.Balance.Balance
530 { Calc.Balance.balance_by_account =
531 Lib.TreeMap.from_List const
532 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
533 , Calc.Balance.balance_by_unit =
535 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
536 [ Calc.Balance.Unit_Sum
537 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
538 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
543 (Calc.Balance.Balance
544 { Calc.Balance.balance_by_account =
545 Lib.TreeMap.from_List const
546 [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
547 , Calc.Balance.balance_by_unit =
549 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
550 [ Calc.Balance.Unit_Sum
551 { Calc.Balance.unit_sum_amount = Amount.eur $ 1
552 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
559 { Calc.Balance.balance_by_account =
560 Lib.TreeMap.from_List const
561 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
562 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
563 , Calc.Balance.balance_by_unit =
565 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
566 [ Calc.Balance.Unit_Sum
567 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
568 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
571 , Calc.Balance.Unit_Sum
572 { Calc.Balance.unit_sum_amount = Amount.eur $ 1
573 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
579 , "expanded" ~: TestList
580 [ "nil_By_Account" ~:
581 Calc.Balance.expanded
584 (Lib.TreeMap.empty::Calc.Balance.Expanded Int String)
586 Calc.Balance.expanded
587 (Lib.TreeMap.from_List const
588 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
590 (Lib.TreeMap.from_List const
591 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
592 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
593 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
596 , "A/A+$1 = A+$1 A/A+$1" ~:
597 Calc.Balance.expanded
598 (Lib.TreeMap.from_List const
599 [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
601 (Lib.TreeMap.from_List const
602 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
603 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
604 , Calc.Balance.exclusive = Amount.from_List []
606 , ("A":|["A"], Calc.Balance.Account_Sum_Expanded
607 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
608 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
611 , "A/B+$1 = A+$1 A/B+$1" ~:
612 Calc.Balance.expanded
613 (Lib.TreeMap.from_List const
614 [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
616 (Lib.TreeMap.from_List const
617 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
618 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
619 , Calc.Balance.exclusive = Amount.from_List []
621 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
622 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
623 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
626 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
627 Calc.Balance.expanded
628 (Lib.TreeMap.from_List const
629 [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
631 (Lib.TreeMap.from_List const
632 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
633 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
634 , Calc.Balance.exclusive = Amount.from_List []
636 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
637 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
638 , Calc.Balance.exclusive = Amount.from_List []
640 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
641 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
642 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
645 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
646 Calc.Balance.expanded
647 (Lib.TreeMap.from_List const
648 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
649 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
652 (Lib.TreeMap.from_List const
653 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
654 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
655 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
657 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
658 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
659 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
662 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
663 Calc.Balance.expanded
664 (Lib.TreeMap.from_List const
665 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
666 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
667 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
670 (Lib.TreeMap.from_List const
671 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
672 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
673 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
675 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
676 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
677 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
679 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
680 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
681 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
684 , "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" ~:
685 Calc.Balance.expanded
686 (Lib.TreeMap.from_List const
687 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
688 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
689 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
690 , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
693 (Lib.TreeMap.from_List const
694 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
695 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 4 ]
696 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
698 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
699 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
700 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
702 , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
703 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
704 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
706 , ("A":|["B", "C", "D"], Calc.Balance.Account_Sum_Expanded
707 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
708 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
711 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
712 Calc.Balance.expanded
713 (Lib.TreeMap.from_List const
714 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
715 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
716 , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
717 , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ])
720 (Lib.TreeMap.from_List const
721 [ ("A":|[], Calc.Balance.Account_Sum_Expanded
722 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
723 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
725 , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
726 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
727 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
729 , ("A":|["BB"], Calc.Balance.Account_Sum_Expanded
730 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
731 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
733 , ("AA":|[], Calc.Balance.Account_Sum_Expanded
734 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
735 , Calc.Balance.exclusive = Amount.from_List []
737 , ("AA":|["B"], Calc.Balance.Account_Sum_Expanded
738 { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
739 , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
743 , "deviation" ~: TestList
745 (Calc.Balance.deviation $
747 { Calc.Balance.balance_by_account =
748 Lib.TreeMap.from_List const
749 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
750 , ("B":|[], Amount.from_List [])
752 , Calc.Balance.balance_by_unit =
754 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
755 [ Calc.Balance.Unit_Sum
756 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
757 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
763 (Calc.Balance.Deviation $
765 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
766 [ Calc.Balance.Unit_Sum
767 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
768 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
772 , "{A+$1 B+$1, $2}" ~:
773 (Calc.Balance.deviation $
775 { Calc.Balance.balance_by_account =
776 Lib.TreeMap.from_List const
777 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
778 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
780 , Calc.Balance.balance_by_unit =
782 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
783 [ Calc.Balance.Unit_Sum
784 { Calc.Balance.unit_sum_amount = Amount.usd $ 2
785 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
793 (Calc.Balance.Deviation $
795 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
796 [ Calc.Balance.Unit_Sum
797 { Calc.Balance.unit_sum_amount = Amount.usd $ 2
798 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
804 , "is_equilibrium_inferrable" ~: TestList
805 [ "nil" ~: TestCase $
807 Calc.Balance.is_equilibrium_inferrable $
808 Calc.Balance.deviation $
809 (Calc.Balance.balance::Calc.Balance.Balance Amount.Amount Amount.Unit)
810 , "{A+$0, $+0}" ~: TestCase $
812 Calc.Balance.is_equilibrium_inferrable $
813 Calc.Balance.deviation $
815 { Calc.Balance.balance_by_account =
816 Lib.TreeMap.from_List const
817 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
819 , Calc.Balance.balance_by_unit =
821 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
822 [ Calc.Balance.Unit_Sum
823 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
824 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
829 , "{A+$1, $+1}" ~: TestCase $
831 Calc.Balance.is_equilibrium_inferrable $
832 Calc.Balance.deviation $
834 { Calc.Balance.balance_by_account =
835 Lib.TreeMap.from_List const
836 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
838 , Calc.Balance.balance_by_unit =
840 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
841 [ Calc.Balance.Unit_Sum
842 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
843 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
848 , "{A+$0+€0, $0 €+0}" ~: TestCase $
850 Calc.Balance.is_equilibrium_inferrable $
851 Calc.Balance.deviation $
853 { Calc.Balance.balance_by_account =
854 Lib.TreeMap.from_List const
855 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
857 , Calc.Balance.balance_by_unit =
859 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
860 [ Calc.Balance.Unit_Sum
861 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
862 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
865 , Calc.Balance.Unit_Sum
866 { Calc.Balance.unit_sum_amount = Amount.eur $ 0
867 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
872 , "{A+$1, B-$1, $+0}" ~: TestCase $
874 Calc.Balance.is_equilibrium_inferrable $
875 Calc.Balance.deviation $
877 { Calc.Balance.balance_by_account =
878 Lib.TreeMap.from_List const
879 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
880 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
882 , Calc.Balance.balance_by_unit =
884 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
885 [ Calc.Balance.Unit_Sum
886 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
887 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
892 , "{A+$1 B, $+1}" ~: TestCase $
894 Calc.Balance.is_equilibrium_inferrable $
895 Calc.Balance.deviation $
897 { Calc.Balance.balance_by_account =
898 Lib.TreeMap.from_List const
899 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
900 , ("B":|[], Amount.from_List [])
902 , Calc.Balance.balance_by_unit =
904 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
905 [ Calc.Balance.Unit_Sum
906 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
907 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
912 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
914 Calc.Balance.is_equilibrium_inferrable $
915 Calc.Balance.deviation $
917 { Calc.Balance.balance_by_account =
918 Lib.TreeMap.from_List const
919 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
920 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
922 , Calc.Balance.balance_by_unit =
924 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
925 [ Calc.Balance.Unit_Sum
926 { Calc.Balance.unit_sum_amount = Amount.usd $ 1
927 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
930 , Calc.Balance.Unit_Sum
931 { Calc.Balance.unit_sum_amount = Amount.eur $ 1
932 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
937 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
939 Calc.Balance.is_equilibrium_inferrable $
940 Calc.Balance.deviation $
942 { Calc.Balance.balance_by_account =
943 Lib.TreeMap.from_List const
944 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
945 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
947 , Calc.Balance.balance_by_unit =
949 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
950 [ Calc.Balance.Unit_Sum
951 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
952 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
955 , Calc.Balance.Unit_Sum
956 { Calc.Balance.unit_sum_amount = Amount.eur $ 1
957 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
962 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
964 Calc.Balance.is_equilibrium_inferrable $
965 Calc.Balance.deviation $
967 { Calc.Balance.balance_by_account =
968 Lib.TreeMap.from_List const
969 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
970 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
972 , Calc.Balance.balance_by_unit =
974 Data.List.map (\s -> (Amount.unit $ Calc.Balance.unit_sum_amount s, s))
975 [ Calc.Balance.Unit_Sum
976 { Calc.Balance.unit_sum_amount = Amount.usd $ 0
977 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
980 , Calc.Balance.Unit_Sum
981 { Calc.Balance.unit_sum_amount = Amount.eur $ 0
982 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
985 , Calc.Balance.Unit_Sum
986 { Calc.Balance.unit_sum_amount = Amount.gbp $ 0
987 , Calc.Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
993 , "infer_equilibrium" ~: TestList
995 (snd $ Calc.Balance.infer_equilibrium $
996 Format.Ledger.posting_by_Account
997 [ (Format.Ledger.posting ("A":|[]))
998 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
999 , (Format.Ledger.posting ("B":|[]))
1000 { Format.Ledger.posting_amounts=Amount.from_List [] }
1004 Format.Ledger.posting_by_Account
1005 [ (Format.Ledger.posting ("A":|[]))
1006 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1007 , (Format.Ledger.posting ("B":|[]))
1008 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] }
1011 (snd $ Calc.Balance.infer_equilibrium $
1012 Format.Ledger.posting_by_Account
1013 [ (Format.Ledger.posting ("A":|[]))
1014 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1015 , (Format.Ledger.posting ("B":|[]))
1016 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] }
1020 Format.Ledger.posting_by_Account
1021 [ (Format.Ledger.posting ("A":|[]))
1022 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ 1 ] }
1023 , (Format.Ledger.posting ("A":|[]))
1024 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1] }
1025 , (Format.Ledger.posting ("B":|[]))
1026 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] }
1027 , (Format.Ledger.posting ("B":|[]))
1028 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] }
1031 (snd $ Calc.Balance.infer_equilibrium $
1032 Format.Ledger.posting_by_Account
1033 [ (Format.Ledger.posting ("A":|[]))
1034 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1035 , (Format.Ledger.posting ("B":|[]))
1036 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
1040 [ Calc.Balance.Unit_Sum
1041 { Calc.Balance.unit_sum_amount = Amount.usd $ 2
1042 , Calc.Balance.unit_sum_accounts = Data.Map.fromList []}
1047 , "Format" ~: TestList
1048 [ "Ledger" ~: TestList
1049 [ "Read" ~: TestList
1050 [ "account_name" ~: TestList
1052 (Data.Either.rights $
1054 (Format.Ledger.Read.account_name <* P.eof)
1059 (Data.Either.rights $
1061 (Format.Ledger.Read.account_name <* P.eof)
1066 (Data.Either.rights $
1068 (Format.Ledger.Read.account_name <* P.eof)
1069 () "" ("AA"::Text)])
1073 (Data.Either.rights $
1075 (Format.Ledger.Read.account_name <* P.eof)
1080 (Data.Either.rights $
1082 (Format.Ledger.Read.account_name <* P.eof)
1087 (Data.Either.rights $
1089 (Format.Ledger.Read.account_name <* P.eof)
1090 () "" ("A:"::Text)])
1094 (Data.Either.rights $
1096 (Format.Ledger.Read.account_name <* P.eof)
1097 () "" (":A"::Text)])
1101 (Data.Either.rights $
1103 (Format.Ledger.Read.account_name <* P.eof)
1104 () "" ("A "::Text)])
1108 (Data.Either.rights $
1110 (Format.Ledger.Read.account_name)
1111 () "" ("A "::Text)])
1115 (Data.Either.rights $
1117 (Format.Ledger.Read.account_name <* P.eof)
1118 () "" ("A A"::Text)])
1122 (Data.Either.rights $
1124 (Format.Ledger.Read.account_name <* P.eof)
1125 () "" ("A "::Text)])
1129 (Data.Either.rights $
1131 (Format.Ledger.Read.account_name <* P.eof)
1132 () "" ("A \n"::Text)])
1136 (Data.Either.rights $
1138 (Format.Ledger.Read.account_name <* P.eof)
1139 () "" ("(A)A"::Text)])
1143 (Data.Either.rights $
1145 (Format.Ledger.Read.account_name <* P.eof)
1146 () "" ("( )A"::Text)])
1150 (Data.Either.rights $
1152 (Format.Ledger.Read.account_name <* P.eof)
1153 () "" ("(A) A"::Text)])
1157 (Data.Either.rights $
1159 (Format.Ledger.Read.account_name <* P.eof)
1160 () "" ("[ ]A"::Text)])
1164 (Data.Either.rights $
1166 (Format.Ledger.Read.account_name <* P.eof)
1167 () "" ("(A) "::Text)])
1171 (Data.Either.rights $
1173 (Format.Ledger.Read.account_name <* P.eof)
1174 () "" ("(A)"::Text)])
1178 (Data.Either.rights $
1180 (Format.Ledger.Read.account_name <* P.eof)
1181 () "" ("A(A)"::Text)])
1185 (Data.Either.rights $
1187 (Format.Ledger.Read.account_name <* P.eof)
1188 () "" ("[A]A"::Text)])
1192 (Data.Either.rights $
1194 (Format.Ledger.Read.account_name <* P.eof)
1195 () "" ("[A] A"::Text)])
1199 (Data.Either.rights $
1201 (Format.Ledger.Read.account_name <* P.eof)
1202 () "" ("[A] "::Text)])
1206 (Data.Either.rights $
1208 (Format.Ledger.Read.account_name <* P.eof)
1209 () "" ("[A]"::Text)])
1213 , "account" ~: TestList
1215 (Data.Either.rights $
1217 (Format.Ledger.Read.account <* P.eof)
1222 (Data.Either.rights $
1224 (Format.Ledger.Read.account <* P.eof)
1229 (Data.Either.rights $
1231 (Format.Ledger.Read.account <* P.eof)
1232 () "" ("A:"::Text)])
1236 (Data.Either.rights $
1238 (Format.Ledger.Read.account <* P.eof)
1239 () "" (":A"::Text)])
1243 (Data.Either.rights $
1245 (Format.Ledger.Read.account <* P.eof)
1246 () "" ("A "::Text)])
1250 (Data.Either.rights $
1252 (Format.Ledger.Read.account <* P.eof)
1253 () "" (" A"::Text)])
1257 (Data.Either.rights $
1259 (Format.Ledger.Read.account <* P.eof)
1260 () "" ("A:B"::Text)])
1264 (Data.Either.rights $
1266 (Format.Ledger.Read.account <* P.eof)
1267 () "" ("A:B:C"::Text)])
1270 , "\"Aa:Bbb:Cccc\"" ~:
1271 (Data.Either.rights $
1273 (Format.Ledger.Read.account <* P.eof)
1274 () "" ("Aa:Bbb:Cccc"::Text)])
1276 ["Aa":|["Bbb", "Cccc"]]
1277 , "\"A a : B b b : C c c c\"" ~:
1278 (Data.Either.rights $
1280 (Format.Ledger.Read.account <* P.eof)
1281 () "" ("A a : B b b : C c c c"::Text)])
1283 ["A a ":|[" B b b ", " C c c c"]]
1285 (Data.Either.rights $
1287 (Format.Ledger.Read.account <* P.eof)
1288 () "" ("A: :C"::Text)])
1292 (Data.Either.rights $
1294 (Format.Ledger.Read.account <* P.eof)
1295 () "" ("A::C"::Text)])
1299 (Data.Either.rights $
1301 (Format.Ledger.Read.account <* P.eof)
1302 () "" ("A:B:(C)"::Text)])
1306 , "posting_type" ~: TestList
1308 Format.Ledger.Read.posting_type
1311 (Format.Ledger.Posting_Type_Regular, "A":|[])
1313 Format.Ledger.Read.posting_type
1316 (Format.Ledger.Posting_Type_Regular, "(":|[])
1318 Format.Ledger.Read.posting_type
1321 (Format.Ledger.Posting_Type_Regular, ")":|[])
1323 Format.Ledger.Read.posting_type
1326 (Format.Ledger.Posting_Type_Regular, "()":|[])
1328 Format.Ledger.Read.posting_type
1331 (Format.Ledger.Posting_Type_Regular, "( )":|[])
1333 Format.Ledger.Read.posting_type
1336 (Format.Ledger.Posting_Type_Virtual, "A":|[])
1338 Format.Ledger.Read.posting_type
1341 (Format.Ledger.Posting_Type_Virtual, "A":|["B", "C"])
1343 Format.Ledger.Read.posting_type
1346 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
1348 Format.Ledger.Read.posting_type
1351 (Format.Ledger.Posting_Type_Regular, "(A)":|["B", "C"])
1353 Format.Ledger.Read.posting_type
1356 (Format.Ledger.Posting_Type_Regular, "A":|["(B)", "C"])
1358 Format.Ledger.Read.posting_type
1361 (Format.Ledger.Posting_Type_Regular, "A":|["B", "(C)"])
1363 Format.Ledger.Read.posting_type
1366 (Format.Ledger.Posting_Type_Regular, "[":|[])
1368 Format.Ledger.Read.posting_type
1371 (Format.Ledger.Posting_Type_Regular, "]":|[])
1373 Format.Ledger.Read.posting_type
1376 (Format.Ledger.Posting_Type_Regular, "[]":|[])
1378 Format.Ledger.Read.posting_type
1381 (Format.Ledger.Posting_Type_Regular, "[ ]":|[])
1383 Format.Ledger.Read.posting_type
1386 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|[])
1388 Format.Ledger.Read.posting_type
1391 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|["B", "C"])
1393 Format.Ledger.Read.posting_type
1396 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
1398 Format.Ledger.Read.posting_type
1401 (Format.Ledger.Posting_Type_Regular, "[A]":|["B", "C"])
1403 Format.Ledger.Read.posting_type
1406 (Format.Ledger.Posting_Type_Regular, "A":|["[B]", "C"])
1408 Format.Ledger.Read.posting_type
1411 (Format.Ledger.Posting_Type_Regular, "A":|["B", "[C]"])
1413 , "amount" ~: TestList
1415 (Data.Either.rights $
1417 (Format.Ledger.Read.amount <* P.eof)
1421 , "\"0\" = Right 0" ~:
1422 (Data.Either.rights $
1424 (Format.Ledger.Read.amount <* P.eof)
1428 { Amount.quantity = Decimal 0 0
1430 , "\"00\" = Right 0" ~:
1431 (Data.Either.rights $
1433 (Format.Ledger.Read.amount <* P.eof)
1434 () "" ("00"::Text)])
1437 { Amount.quantity = Decimal 0 0
1439 , "\"0.\" = Right 0." ~:
1440 (Data.Either.rights $
1442 (Format.Ledger.Read.amount <* P.eof)
1443 () "" ("0."::Text)])
1446 { Amount.quantity = Decimal 0 0
1449 { Amount.Style.fractioning = Just '.'
1452 , "\".0\" = Right 0.0" ~:
1453 (Data.Either.rights $
1455 (Format.Ledger.Read.amount <* P.eof)
1456 () "" (".0"::Text)])
1459 { Amount.quantity = Decimal 0 0
1462 { Amount.Style.fractioning = Just '.'
1463 , Amount.Style.precision = 1
1466 , "\"0,\" = Right 0," ~:
1467 (Data.Either.rights $
1469 (Format.Ledger.Read.amount <* P.eof)
1470 () "" ("0,"::Text)])
1473 { Amount.quantity = Decimal 0 0
1476 { Amount.Style.fractioning = Just ','
1479 , "\",0\" = Right 0,0" ~:
1480 (Data.Either.rights $
1482 (Format.Ledger.Read.amount <* P.eof)
1483 () "" (",0"::Text)])
1486 { Amount.quantity = Decimal 0 0
1489 { Amount.Style.fractioning = Just ','
1490 , Amount.Style.precision = 1
1493 , "\"0_\" = Left" ~:
1494 (Data.Either.rights $
1496 (Format.Ledger.Read.amount <* P.eof)
1497 () "" ("0_"::Text)])
1500 , "\"_0\" = Left" ~:
1501 (Data.Either.rights $
1503 (Format.Ledger.Read.amount <* P.eof)
1504 () "" ("_0"::Text)])
1507 , "\"0.0\" = Right 0.0" ~:
1508 (Data.Either.rights $
1510 (Format.Ledger.Read.amount <* P.eof)
1511 () "" ("0.0"::Text)])
1514 { Amount.quantity = Decimal 0 0
1517 { Amount.Style.fractioning = Just '.'
1518 , Amount.Style.precision = 1
1521 , "\"00.00\" = Right 0.00" ~:
1522 (Data.Either.rights $
1524 (Format.Ledger.Read.amount <* P.eof)
1525 () "" ("00.00"::Text)])
1528 { Amount.quantity = Decimal 0 0
1531 { Amount.Style.fractioning = Just '.'
1532 , Amount.Style.precision = 2
1535 , "\"0,0\" = Right 0,0" ~:
1536 (Data.Either.rights $
1538 (Format.Ledger.Read.amount <* P.eof)
1539 () "" ("0,0"::Text)])
1542 { Amount.quantity = Decimal 0 0
1545 { Amount.Style.fractioning = Just ','
1546 , Amount.Style.precision = 1
1549 , "\"00,00\" = Right 0,00" ~:
1550 (Data.Either.rights $
1552 (Format.Ledger.Read.amount <* P.eof)
1553 () "" ("00,00"::Text)])
1556 { Amount.quantity = Decimal 0 0
1559 { Amount.Style.fractioning = Just ','
1560 , Amount.Style.precision = 2
1563 , "\"0_0\" = Right 0" ~:
1564 (Data.Either.rights $
1566 (Format.Ledger.Read.amount <* P.eof)
1567 () "" ("0_0"::Text)])
1570 { Amount.quantity = Decimal 0 0
1573 { Amount.Style.fractioning = Nothing
1574 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1575 , Amount.Style.precision = 0
1578 , "\"00_00\" = Right 0" ~:
1579 (Data.Either.rights $
1581 (Format.Ledger.Read.amount <* P.eof)
1582 () "" ("00_00"::Text)])
1585 { Amount.quantity = Decimal 0 0
1588 { Amount.Style.fractioning = Nothing
1589 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1590 , Amount.Style.precision = 0
1593 , "\"0,000.00\" = Right 0,000.00" ~:
1594 (Data.Either.rights $
1596 (Format.Ledger.Read.amount <* P.eof)
1597 () "" ("0,000.00"::Text)])
1600 { Amount.quantity = Decimal 0 0
1603 { Amount.Style.fractioning = Just '.'
1604 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1605 , Amount.Style.precision = 2
1608 , "\"0.000,00\" = Right 0.000,00" ~:
1609 (Data.Either.rights $
1611 (Format.Ledger.Read.amount)
1612 () "" ("0.000,00"::Text)])
1615 { Amount.quantity = Decimal 0 0
1618 { Amount.Style.fractioning = Just ','
1619 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1620 , Amount.Style.precision = 2
1623 , "\"1,000.00\" = Right 1,000.00" ~:
1624 (Data.Either.rights $
1626 (Format.Ledger.Read.amount <* P.eof)
1627 () "" ("1,000.00"::Text)])
1630 { Amount.quantity = Decimal 0 1000
1633 { Amount.Style.fractioning = Just '.'
1634 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1635 , Amount.Style.precision = 2
1638 , "\"1.000,00\" = Right 1.000,00" ~:
1639 (Data.Either.rights $
1641 (Format.Ledger.Read.amount)
1642 () "" ("1.000,00"::Text)])
1645 { Amount.quantity = Decimal 0 1000
1648 { Amount.Style.fractioning = Just ','
1649 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1650 , Amount.Style.precision = 2
1653 , "\"1,000.00.\" = Left" ~:
1654 (Data.Either.rights $
1656 (Format.Ledger.Read.amount)
1657 () "" ("1,000.00."::Text)])
1660 , "\"1.000,00,\" = Left" ~:
1661 (Data.Either.rights $
1663 (Format.Ledger.Read.amount)
1664 () "" ("1.000,00,"::Text)])
1667 , "\"1,000.00_\" = Left" ~:
1668 (Data.Either.rights $
1670 (Format.Ledger.Read.amount)
1671 () "" ("1,000.00_"::Text)])
1674 , "\"12\" = Right 12" ~:
1675 (Data.Either.rights $
1677 (Format.Ledger.Read.amount <* P.eof)
1678 () "" ("123"::Text)])
1681 { Amount.quantity = Decimal 0 123
1683 , "\"1.2\" = Right 1.2" ~:
1684 (Data.Either.rights $
1686 (Format.Ledger.Read.amount <* P.eof)
1687 () "" ("1.2"::Text)])
1690 { Amount.quantity = Decimal 1 12
1693 { Amount.Style.fractioning = Just '.'
1694 , Amount.Style.precision = 1
1697 , "\"1,2\" = Right 1,2" ~:
1698 (Data.Either.rights $
1700 (Format.Ledger.Read.amount <* P.eof)
1701 () "" ("1,2"::Text)])
1704 { Amount.quantity = Decimal 1 12
1707 { Amount.Style.fractioning = Just ','
1708 , Amount.Style.precision = 1
1711 , "\"12.23\" = Right 12.23" ~:
1712 (Data.Either.rights $
1714 (Format.Ledger.Read.amount <* P.eof)
1715 () "" ("12.34"::Text)])
1718 { Amount.quantity = Decimal 2 1234
1721 { Amount.Style.fractioning = Just '.'
1722 , Amount.Style.precision = 2
1725 , "\"12,23\" = Right 12,23" ~:
1726 (Data.Either.rights $
1728 (Format.Ledger.Read.amount <* P.eof)
1729 () "" ("12,34"::Text)])
1732 { Amount.quantity = Decimal 2 1234
1735 { Amount.Style.fractioning = Just ','
1736 , Amount.Style.precision = 2
1739 , "\"1_2\" = Right 1_2" ~:
1740 (Data.Either.rights $
1742 (Format.Ledger.Read.amount <* P.eof)
1743 () "" ("1_2"::Text)])
1746 { Amount.quantity = Decimal 0 12
1749 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1750 , Amount.Style.precision = 0
1753 , "\"1_23\" = Right 1_23" ~:
1754 (Data.Either.rights $
1756 (Format.Ledger.Read.amount <* P.eof)
1757 () "" ("1_23"::Text)])
1760 { Amount.quantity = Decimal 0 123
1763 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1764 , Amount.Style.precision = 0
1767 , "\"1_23_456\" = Right 1_23_456" ~:
1768 (Data.Either.rights $
1770 (Format.Ledger.Read.amount <* P.eof)
1771 () "" ("1_23_456"::Text)])
1774 { Amount.quantity = Decimal 0 123456
1777 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1778 , Amount.Style.precision = 0
1781 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1782 (Data.Either.rights $
1784 (Format.Ledger.Read.amount <* P.eof)
1785 () "" ("1_23_456.7890_12345_678901"::Text)])
1788 { Amount.quantity = Decimal 15 123456789012345678901
1791 { Amount.Style.fractioning = Just '.'
1792 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1793 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1794 , Amount.Style.precision = 15
1797 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1798 (Data.Either.rights $
1800 (Format.Ledger.Read.amount <* P.eof)
1801 () "" ("123456_78901_2345.678_90_1"::Text)])
1804 { Amount.quantity = Decimal 6 123456789012345678901
1807 { Amount.Style.fractioning = Just '.'
1808 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1809 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1810 , Amount.Style.precision = 6
1813 , "\"$1\" = Right $1" ~:
1814 (Data.Either.rights $
1816 (Format.Ledger.Read.amount <* P.eof)
1817 () "" ("$1"::Text)])
1820 { Amount.quantity = Decimal 0 1
1823 { Amount.Style.fractioning = Nothing
1824 , Amount.Style.grouping_integral = Nothing
1825 , Amount.Style.grouping_fractional = Nothing
1826 , Amount.Style.precision = 0
1827 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1828 , Amount.Style.unit_spaced = Just False
1832 , "\"1$\" = Right 1$" ~:
1833 (Data.Either.rights $
1835 (Format.Ledger.Read.amount <* P.eof)
1836 () "" ("1$"::Text)])
1839 { Amount.quantity = Decimal 0 1
1842 { Amount.Style.fractioning = Nothing
1843 , Amount.Style.grouping_integral = Nothing
1844 , Amount.Style.grouping_fractional = Nothing
1845 , Amount.Style.precision = 0
1846 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1847 , Amount.Style.unit_spaced = Just False
1851 , "\"$ 1\" = Right $ 1" ~:
1852 (Data.Either.rights $
1854 (Format.Ledger.Read.amount <* P.eof)
1855 () "" ("$ 1"::Text)])
1858 { Amount.quantity = Decimal 0 1
1861 { Amount.Style.fractioning = Nothing
1862 , Amount.Style.grouping_integral = Nothing
1863 , Amount.Style.grouping_fractional = Nothing
1864 , Amount.Style.precision = 0
1865 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1866 , Amount.Style.unit_spaced = Just True
1870 , "\"1 $\" = Right 1 $" ~:
1871 (Data.Either.rights $
1873 (Format.Ledger.Read.amount <* P.eof)
1874 () "" ("1 $"::Text)])
1877 { Amount.quantity = Decimal 0 1
1880 { Amount.Style.fractioning = Nothing
1881 , Amount.Style.grouping_integral = Nothing
1882 , Amount.Style.grouping_fractional = Nothing
1883 , Amount.Style.precision = 0
1884 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1885 , Amount.Style.unit_spaced = Just True
1889 , "\"-$1\" = Right $-1" ~:
1890 (Data.Either.rights $
1892 (Format.Ledger.Read.amount <* P.eof)
1893 () "" ("-$1"::Text)])
1896 { Amount.quantity = Decimal 0 (-1)
1899 { Amount.Style.fractioning = Nothing
1900 , Amount.Style.grouping_integral = Nothing
1901 , Amount.Style.grouping_fractional = Nothing
1902 , Amount.Style.precision = 0
1903 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1904 , Amount.Style.unit_spaced = Just False
1908 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1909 (Data.Either.rights $
1911 (Format.Ledger.Read.amount <* P.eof)
1912 () "" ("\"4 2\"1"::Text)])
1915 { Amount.quantity = Decimal 0 1
1918 { Amount.Style.fractioning = Nothing
1919 , Amount.Style.grouping_integral = Nothing
1920 , Amount.Style.grouping_fractional = Nothing
1921 , Amount.Style.precision = 0
1922 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1923 , Amount.Style.unit_spaced = Just False
1925 , Amount.unit = "4 2"
1927 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1928 (Data.Either.rights $
1930 (Format.Ledger.Read.amount <* P.eof)
1931 () "" ("1\"4 2\""::Text)])
1934 { Amount.quantity = Decimal 0 1
1937 { Amount.Style.fractioning = Nothing
1938 , Amount.Style.grouping_integral = Nothing
1939 , Amount.Style.grouping_fractional = Nothing
1940 , Amount.Style.precision = 0
1941 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1942 , Amount.Style.unit_spaced = Just False
1944 , Amount.unit = "4 2"
1946 , "\"$1.000,00\" = Right $1.000,00" ~:
1947 (Data.Either.rights $
1949 (Format.Ledger.Read.amount <* P.eof)
1950 () "" ("$1.000,00"::Text)])
1953 { Amount.quantity = Decimal 0 1000
1956 { Amount.Style.fractioning = Just ','
1957 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1958 , Amount.Style.grouping_fractional = Nothing
1959 , Amount.Style.precision = 2
1960 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1961 , Amount.Style.unit_spaced = Just False
1965 , "\"1.000,00$\" = Right 1.000,00$" ~:
1966 (Data.Either.rights $
1968 (Format.Ledger.Read.amount <* P.eof)
1969 () "" ("1.000,00$"::Text)])
1972 { Amount.quantity = Decimal 0 1000
1975 { Amount.Style.fractioning = Just ','
1976 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1977 , Amount.Style.grouping_fractional = Nothing
1978 , Amount.Style.precision = 2
1979 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1980 , Amount.Style.unit_spaced = Just False
1985 , "comment" ~: TestList
1986 [ "; some comment = Right \" some comment\"" ~:
1987 (Data.Either.rights $
1989 (Format.Ledger.Read.comment <* P.eof)
1990 () "" ("; some comment"::Text)])
1993 , "; some comment \\n = Right \" some comment \"" ~:
1994 (Data.Either.rights $
1996 (Format.Ledger.Read.comment <* P.newline <* P.eof)
1997 () "" ("; some comment \n"::Text)])
1999 [ " some comment " ]
2000 , "; some comment \\r\\n = Right \" some comment \"" ~:
2001 (Data.Either.rights $
2003 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
2004 () "" ("; some comment \r\n"::Text)])
2006 [ " some comment " ]
2008 , "comments" ~: TestList
2009 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
2010 (Data.Either.rights $
2012 (Format.Ledger.Read.comments <* P.eof)
2013 () "" ("; some comment\n ; some other comment"::Text)])
2015 [ [" some comment", " some other comment"] ]
2016 , "; some comment \\n = Right \" some comment \"" ~:
2017 (Data.Either.rights $
2019 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
2020 () "" ("; some comment \n"::Text)])
2022 [ [" some comment "] ]
2024 , "date" ~: TestList
2026 (Data.Either.rights $
2027 [P.runParser_with_Error
2028 (Format.Ledger.Read.date Nothing <* P.eof)
2029 () "" ("2000/01/01"::Text)])
2033 (Time.fromGregorian 2000 01 01)
2034 (Time.TimeOfDay 0 0 0))
2036 , "2000/01/01 some text" ~:
2037 (Data.Either.rights $
2038 [P.runParser_with_Error
2039 (Format.Ledger.Read.date Nothing)
2040 () "" ("2000/01/01 some text"::Text)])
2044 (Time.fromGregorian 2000 01 01)
2045 (Time.TimeOfDay 0 0 0))
2047 , "2000/01/01 12:34" ~:
2048 (Data.Either.rights $
2049 [P.runParser_with_Error
2050 (Format.Ledger.Read.date Nothing <* P.eof)
2051 () "" ("2000/01/01 12:34"::Text)])
2055 (Time.fromGregorian 2000 01 01)
2056 (Time.TimeOfDay 12 34 0))
2058 , "2000/01/01 12:34:56" ~:
2059 (Data.Either.rights $
2060 [P.runParser_with_Error
2061 (Format.Ledger.Read.date Nothing <* P.eof)
2062 () "" ("2000/01/01 12:34:56"::Text)])
2066 (Time.fromGregorian 2000 01 01)
2067 (Time.TimeOfDay 12 34 56))
2069 , "2000/01/01 12:34 CET" ~:
2070 (Data.Either.rights $
2071 [P.runParser_with_Error
2072 (Format.Ledger.Read.date Nothing <* P.eof)
2073 () "" ("2000/01/01 12:34 CET"::Text)])
2077 (Time.fromGregorian 2000 01 01)
2078 (Time.TimeOfDay 12 34 0))
2079 (Time.TimeZone 60 True "CET")]
2080 , "2000/01/01 12:34 +0130" ~:
2081 (Data.Either.rights $
2082 [P.runParser_with_Error
2083 (Format.Ledger.Read.date Nothing <* P.eof)
2084 () "" ("2000/01/01 12:34 +0130"::Text)])
2088 (Time.fromGregorian 2000 01 01)
2089 (Time.TimeOfDay 12 34 0))
2090 (Time.TimeZone 90 False "+0130")]
2091 , "2000/01/01 12:34:56 CET" ~:
2092 (Data.Either.rights $
2093 [P.runParser_with_Error
2094 (Format.Ledger.Read.date Nothing <* P.eof)
2095 () "" ("2000/01/01 12:34:56 CET"::Text)])
2099 (Time.fromGregorian 2000 01 01)
2100 (Time.TimeOfDay 12 34 56))
2101 (Time.TimeZone 60 True "CET")]
2103 (Data.Either.rights $
2104 [P.runParser_with_Error
2105 (Format.Ledger.Read.date Nothing <* P.eof)
2106 () "" ("2001/02/29"::Text)])
2110 (Data.Either.rights $
2111 [P.runParser_with_Error
2112 (Format.Ledger.Read.date (Just 2000) <* P.eof)
2113 () "" ("01/01"::Text)])
2117 (Time.fromGregorian 2000 01 01)
2118 (Time.TimeOfDay 0 0 0))
2121 , "tag_value" ~: TestList
2123 (Data.Either.rights $
2125 (Format.Ledger.Read.tag_value <* P.eof)
2130 (Data.Either.rights $
2132 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
2133 () "" (",\n"::Text)])
2137 (Data.Either.rights $
2139 (Format.Ledger.Read.tag_value <* P.eof)
2140 () "" (",x"::Text)])
2144 (Data.Either.rights $
2146 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
2147 () "" (",x:"::Text)])
2151 (Data.Either.rights $
2153 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
2154 () "" ("v, v, n:"::Text)])
2160 (Data.Either.rights $
2162 (Format.Ledger.Read.tag <* P.eof)
2163 () "" ("Name:"::Text)])
2167 (Data.Either.rights $
2169 (Format.Ledger.Read.tag <* P.eof)
2170 () "" ("Name:Value"::Text)])
2173 , "Name:Value\\n" ~:
2174 (Data.Either.rights $
2176 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
2177 () "" ("Name:Value\n"::Text)])
2181 (Data.Either.rights $
2183 (Format.Ledger.Read.tag <* P.eof)
2184 () "" ("Name:Val ue"::Text)])
2186 [("Name", "Val ue")]
2188 (Data.Either.rights $
2190 (Format.Ledger.Read.tag <* P.eof)
2191 () "" ("Name:,"::Text)])
2195 (Data.Either.rights $
2197 (Format.Ledger.Read.tag <* P.eof)
2198 () "" ("Name:Val,ue"::Text)])
2200 [("Name", "Val,ue")]
2202 (Data.Either.rights $
2204 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
2205 () "" ("Name:Val,ue:"::Text)])
2209 , "tags" ~: TestList
2211 (Data.Either.rights $
2213 (Format.Ledger.Read.tags <* P.eof)
2214 () "" ("Name:"::Text)])
2221 (Data.Either.rights $
2223 (Format.Ledger.Read.tags <* P.eof)
2224 () "" ("Name:,"::Text)])
2231 (Data.Either.rights $
2233 (Format.Ledger.Read.tags <* P.eof)
2234 () "" ("Name:,Name:"::Text)])
2237 [ ("Name", ["", ""])
2241 (Data.Either.rights $
2243 (Format.Ledger.Read.tags <* P.eof)
2244 () "" ("Name:,Name2:"::Text)])
2251 , "Name: , Name2:" ~:
2252 (Data.Either.rights $
2254 (Format.Ledger.Read.tags <* P.eof)
2255 () "" ("Name: , Name2:"::Text)])
2262 , "Name:,Name2:,Name3:" ~:
2263 (Data.Either.rights $
2265 (Format.Ledger.Read.tags <* P.eof)
2266 () "" ("Name:,Name2:,Name3:"::Text)])
2274 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
2275 (Data.Either.rights $
2277 (Format.Ledger.Read.tags <* P.eof)
2278 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
2281 [ ("Name", ["Val ue"])
2282 , ("Name2", ["V a l u e"])
2283 , ("Name3", ["V al ue"])
2287 , "posting" ~: TestList
2288 [ " A:B:C = Right A:B:C" ~:
2289 (Data.Either.rights $
2290 [P.runParser_with_Error
2291 (Format.Ledger.Read.posting <* P.eof)
2292 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
2294 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
2295 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2297 , Format.Ledger.Posting_Type_Regular
2300 , " !A:B:C = Right !A:B:C" ~:
2301 (Data.List.map fst $
2302 Data.Either.rights $
2303 [P.runParser_with_Error
2304 (Format.Ledger.Read.posting <* P.eof)
2305 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
2307 [ (Format.Ledger.posting ("A":|["B", "C"]))
2308 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2309 , Format.Ledger.posting_status = True
2312 , " *A:B:C = Right *A:B:C" ~:
2313 (Data.List.map fst $
2314 Data.Either.rights $
2315 [P.runParser_with_Error
2316 (Format.Ledger.Read.posting <* P.eof)
2317 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
2319 [ (Format.Ledger.posting ("A":|["B", "C"]))
2320 { Format.Ledger.posting_amounts = Data.Map.fromList []
2321 , Format.Ledger.posting_comments = []
2322 , Format.Ledger.posting_dates = []
2323 , Format.Ledger.posting_status = True
2324 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2325 , Format.Ledger.posting_tags = Data.Map.fromList []
2328 , " A:B:C $1 = Right A:B:C $1" ~:
2329 (Data.List.map fst $
2330 Data.Either.rights $
2331 [P.runParser_with_Error
2332 (Format.Ledger.Read.posting <* P.eof)
2333 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
2335 [ (Format.Ledger.posting ("A":|["B","C $1"]))
2336 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2339 , " A:B:C $1 = Right A:B:C $1" ~:
2340 (Data.List.map fst $
2341 Data.Either.rights $
2342 [P.runParser_with_Error
2343 (Format.Ledger.Read.posting <* P.eof)
2344 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
2346 [ (Format.Ledger.posting ("A":|["B", "C"]))
2347 { Format.Ledger.posting_amounts = Data.Map.fromList
2349 { Amount.quantity = 1
2350 , Amount.style = Amount.Style.nil
2351 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2352 , Amount.Style.unit_spaced = Just False
2357 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2360 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
2361 (Data.List.map fst $
2362 Data.Either.rights $
2363 [P.runParser_with_Error
2364 (Format.Ledger.Read.posting <* P.eof)
2365 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
2367 [ (Format.Ledger.posting ("A":|["B", "C"]))
2368 { Format.Ledger.posting_amounts = Data.Map.fromList
2370 { Amount.quantity = 1
2371 , Amount.style = Amount.Style.nil
2372 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2373 , Amount.Style.unit_spaced = Just False
2378 { Amount.quantity = 1
2379 , Amount.style = Amount.Style.nil
2380 { Amount.Style.unit_side = Just Amount.Style.Side_Right
2381 , Amount.Style.unit_spaced = Just False
2386 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2389 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
2390 (Data.List.map fst $
2391 Data.Either.rights $
2392 [P.runParser_with_Error
2393 (Format.Ledger.Read.posting <* P.eof)
2394 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
2396 [ (Format.Ledger.posting ("A":|["B", "C"]))
2397 { Format.Ledger.posting_amounts = Data.Map.fromList
2399 { Amount.quantity = 2
2400 , Amount.style = Amount.Style.nil
2401 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2402 , Amount.Style.unit_spaced = Just False
2407 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2410 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
2411 (Data.List.map fst $
2412 Data.Either.rights $
2413 [P.runParser_with_Error
2414 (Format.Ledger.Read.posting <* P.eof)
2415 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
2417 [ (Format.Ledger.posting ("A":|["B", "C"]))
2418 { Format.Ledger.posting_amounts = Data.Map.fromList
2420 { Amount.quantity = 3
2421 , Amount.style = Amount.Style.nil
2422 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2423 , Amount.Style.unit_spaced = Just False
2428 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2431 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
2432 (Data.List.map fst $
2433 Data.Either.rights $
2434 [P.runParser_with_Error
2435 (Format.Ledger.Read.posting <* P.eof)
2436 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
2438 [ (Format.Ledger.posting ("A":|["B", "C"]))
2439 { Format.Ledger.posting_amounts = Data.Map.fromList []
2440 , Format.Ledger.posting_comments = [" some comment"]
2441 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2444 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
2445 (Data.List.map fst $
2446 Data.Either.rights $
2447 [P.runParser_with_Error
2448 (Format.Ledger.Read.posting <* P.eof)
2449 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
2451 [ (Format.Ledger.posting ("A":|["B", "C"]))
2452 { Format.Ledger.posting_amounts = Data.Map.fromList []
2453 , Format.Ledger.posting_comments = [" some comment", " some other comment"]
2454 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2457 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
2458 (Data.List.map fst $
2459 Data.Either.rights $
2460 [P.runParser_with_Error
2461 (Format.Ledger.Read.posting)
2462 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
2464 [ (Format.Ledger.posting ("A":|["B", "C"]))
2465 { Format.Ledger.posting_amounts = Data.Map.fromList
2467 { Amount.quantity = 1
2468 , Amount.style = Amount.Style.nil
2469 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2470 , Amount.Style.unit_spaced = Just False
2475 , Format.Ledger.posting_comments = [" some comment"]
2476 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2479 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
2480 (Data.List.map fst $
2481 Data.Either.rights $
2482 [P.runParser_with_Error
2483 (Format.Ledger.Read.posting <* P.eof)
2484 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
2486 [ (Format.Ledger.posting ("A":|["B", "C"]))
2487 { Format.Ledger.posting_comments = [" N:V"]
2488 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2489 , Format.Ledger.posting_tags = Data.Map.fromList
2494 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2495 (Data.List.map fst $
2496 Data.Either.rights $
2497 [P.runParser_with_Error
2498 (Format.Ledger.Read.posting <* P.eof)
2499 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2501 [ (Format.Ledger.posting ("A":|["B", "C"]))
2502 { Format.Ledger.posting_comments = [" some comment N:V"]
2503 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2504 , Format.Ledger.posting_tags = Data.Map.fromList
2509 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2510 (Data.List.map fst $
2511 Data.Either.rights $
2512 [P.runParser_with_Error
2513 (Format.Ledger.Read.posting )
2514 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2516 [ (Format.Ledger.posting ("A":|["B", "C"]))
2517 { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"]
2518 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2519 , Format.Ledger.posting_tags = Data.Map.fromList
2525 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2526 (Data.List.map fst $
2527 Data.Either.rights $
2528 [P.runParser_with_Error
2529 (Format.Ledger.Read.posting <* P.eof)
2530 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2532 [ (Format.Ledger.posting ("A":|["B", "C"]))
2533 { Format.Ledger.posting_comments = [" N:V", " N:V2"]
2534 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2535 , Format.Ledger.posting_tags = Data.Map.fromList
2536 [ ("N", ["V", "V2"])
2540 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2541 (Data.List.map fst $
2542 Data.Either.rights $
2543 [P.runParser_with_Error
2544 (Format.Ledger.Read.posting <* P.eof)
2545 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2547 [ (Format.Ledger.posting ("A":|["B", "C"]))
2548 { Format.Ledger.posting_comments = [" N:V", " N2:V"]
2549 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2550 , Format.Ledger.posting_tags = Data.Map.fromList
2556 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2557 (Data.List.map fst $
2558 Data.Either.rights $
2559 [P.runParser_with_Error
2560 (Format.Ledger.Read.posting <* P.eof)
2561 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2563 [ (Format.Ledger.posting ("A":|["B", "C"]))
2564 { Format.Ledger.posting_comments = [" date:2001/01/01"]
2565 , Format.Ledger.posting_dates =
2568 (Time.fromGregorian 2001 01 01)
2569 (Time.TimeOfDay 0 0 0))
2572 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2573 , Format.Ledger.posting_tags = Data.Map.fromList
2574 [ ("date", ["2001/01/01"])
2578 , " (A:B:C) = Right (A:B:C)" ~:
2579 (Data.Either.rights $
2580 [P.runParser_with_Error
2581 (Format.Ledger.Read.posting <* P.eof)
2582 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
2584 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
2585 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2587 , Format.Ledger.Posting_Type_Virtual
2590 , " [A:B:C] = Right [A:B:C]" ~:
2591 (Data.Either.rights $
2592 [P.runParser_with_Error
2593 (Format.Ledger.Read.posting <* P.eof)
2594 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
2596 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
2597 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
2599 , Format.Ledger.Posting_Type_Virtual_Balanced
2603 , "transaction" ~: TestList
2604 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
2605 (Data.Either.rights $
2606 [P.runParser_with_Error
2607 (Format.Ledger.Read.transaction <* P.eof)
2608 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
2610 [ Format.Ledger.transaction
2611 { Format.Ledger.transaction_dates=
2614 (Time.fromGregorian 2000 01 01)
2615 (Time.TimeOfDay 0 0 0))
2618 , Format.Ledger.transaction_description="some description"
2619 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
2620 [ (Format.Ledger.posting ("A":|["B", "C"]))
2621 { Format.Ledger.posting_amounts = Data.Map.fromList
2623 { Amount.quantity = 1
2624 , Amount.style = Amount.Style.nil
2625 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2626 , Amount.Style.unit_spaced = Just False
2631 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
2633 , (Format.Ledger.posting ("a":|["b", "c"]))
2634 { Format.Ledger.posting_sourcepos = P.newPos "" 3 1
2637 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
2640 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
2641 (Data.Either.rights $
2642 [P.runParser_with_Error
2643 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
2644 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
2646 [ Format.Ledger.transaction
2647 { Format.Ledger.transaction_dates=
2650 (Time.fromGregorian 2000 01 01)
2651 (Time.TimeOfDay 0 0 0))
2654 , Format.Ledger.transaction_description="some description"
2655 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
2656 [ (Format.Ledger.posting ("A":|["B", "C"]))
2657 { Format.Ledger.posting_amounts = Data.Map.fromList
2659 { Amount.quantity = 1
2660 , Amount.style = Amount.Style.nil
2661 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2662 , Amount.Style.unit_spaced = Just False
2667 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
2669 , (Format.Ledger.posting ("a":|["b", "c"]))
2670 { Format.Ledger.posting_sourcepos = P.newPos "" 3 1
2673 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
2676 , "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" ~:
2677 (Data.Either.rights $
2678 [P.runParser_with_Error
2679 (Format.Ledger.Read.transaction <* P.eof)
2680 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)])
2682 [ Format.Ledger.transaction
2683 { Format.Ledger.transaction_comments_after =
2685 , " some other;comment"
2687 , " some last comment"
2689 , Format.Ledger.transaction_dates=
2692 (Time.fromGregorian 2000 01 01)
2693 (Time.TimeOfDay 0 0 0))
2696 , Format.Ledger.transaction_description="some description"
2697 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
2698 [ (Format.Ledger.posting ("A":|["B", "C"]))
2699 { Format.Ledger.posting_amounts = Data.Map.fromList
2701 { Amount.quantity = 1
2702 , Amount.style = Amount.Style.nil
2703 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2704 , Amount.Style.unit_spaced = Just False
2709 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
2711 , (Format.Ledger.posting ("a":|["b", "c"]))
2712 { Format.Ledger.posting_sourcepos = P.newPos "" 6 1
2713 , Format.Ledger.posting_tags = Data.Map.fromList []
2716 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
2717 , Format.Ledger.transaction_tags = Data.Map.fromList
2723 , "journal" ~: TestList
2724 [ "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
2726 P.runParserT_with_Error
2727 (Format.Ledger.Read.journal "" {-<* P.eof-})
2728 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)
2730 (\j -> j{Format.Ledger.journal_last_read_time=
2731 Format.Ledger.journal_last_read_time Format.Ledger.journal}) $
2732 Data.Either.rights [jnl])
2734 [ Format.Ledger.journal
2735 { Format.Ledger.journal_transactions = Format.Ledger.transaction_by_Date
2736 [ Format.Ledger.transaction
2737 { Format.Ledger.transaction_dates=
2740 (Time.fromGregorian 2000 01 01)
2741 (Time.TimeOfDay 0 0 0))
2744 , Format.Ledger.transaction_description="1° description"
2745 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
2746 [ (Format.Ledger.posting ("A":|["B", "C"]))
2747 { Format.Ledger.posting_amounts = Data.Map.fromList
2749 { Amount.quantity = 1
2750 , Amount.style = Amount.Style.nil
2751 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2752 , Amount.Style.unit_spaced = Just False
2757 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
2759 , (Format.Ledger.posting ("a":|["b", "c"]))
2760 { Format.Ledger.posting_sourcepos = P.newPos "" 3 1
2763 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
2765 , Format.Ledger.transaction
2766 { Format.Ledger.transaction_dates=
2769 (Time.fromGregorian 2000 01 02)
2770 (Time.TimeOfDay 0 0 0))
2773 , Format.Ledger.transaction_description="2° description"
2774 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
2775 [ (Format.Ledger.posting ("A":|["B", "C"]))
2776 { Format.Ledger.posting_amounts = Data.Map.fromList
2778 { Amount.quantity = 1
2779 , Amount.style = Amount.Style.nil
2780 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2781 , Amount.Style.unit_spaced = Just False
2786 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
2788 , (Format.Ledger.posting ("x":|["y", "z"]))
2789 { Format.Ledger.posting_sourcepos = P.newPos "" 6 1
2792 , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1
2799 , "Write" ~: TestList
2800 [ "account" ~: TestList
2802 ((Format.Ledger.Write.show False $
2803 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
2808 ((Format.Ledger.Write.show False $
2809 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
2814 ((Format.Ledger.Write.show False $
2815 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual $
2820 ((Format.Ledger.Write.show False $
2821 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual_Balanced $
2826 , "amount" ~: TestList
2828 ((Format.Ledger.Write.show False $
2829 Format.Ledger.Write.amount
2834 ((Format.Ledger.Write.show False $
2835 Format.Ledger.Write.amount
2837 { Amount.style = Amount.Style.nil
2838 { Amount.Style.precision = 2 }
2843 ((Format.Ledger.Write.show False $
2844 Format.Ledger.Write.amount
2846 { Amount.quantity = Decimal 0 123
2851 ((Format.Ledger.Write.show False $
2852 Format.Ledger.Write.amount
2854 { Amount.quantity = Decimal 0 (- 123)
2858 , "12.3 @ prec=0" ~:
2859 ((Format.Ledger.Write.show False $
2860 Format.Ledger.Write.amount
2862 { Amount.quantity = Decimal 1 123
2863 , Amount.style = Amount.Style.nil
2864 { Amount.Style.fractioning = Just '.'
2869 , "12.5 @ prec=0" ~:
2870 ((Format.Ledger.Write.show False $
2871 Format.Ledger.Write.amount
2873 { Amount.quantity = Decimal 1 125
2874 , Amount.style = Amount.Style.nil
2875 { Amount.Style.fractioning = Just '.'
2880 , "12.3 @ prec=1" ~:
2881 ((Format.Ledger.Write.show False $
2882 Format.Ledger.Write.amount
2884 { Amount.quantity = Decimal 1 123
2885 , Amount.style = Amount.Style.nil
2886 { Amount.Style.fractioning = Just '.'
2887 , Amount.Style.precision = 1
2892 , "1,234.56 @ prec=2" ~:
2893 ((Format.Ledger.Write.show False $
2894 Format.Ledger.Write.amount
2896 { Amount.quantity = Decimal 2 123456
2897 , Amount.style = Amount.Style.nil
2898 { Amount.Style.fractioning = Just '.'
2899 , Amount.Style.precision = 2
2900 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2905 , "123,456,789,01,2.3456789 @ prec=7" ~:
2906 ((Format.Ledger.Write.show False $
2907 Format.Ledger.Write.amount
2909 { Amount.quantity = Decimal 7 1234567890123456789
2910 , Amount.style = Amount.Style.nil
2911 { Amount.Style.fractioning = Just '.'
2912 , Amount.Style.precision = 7
2913 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2917 "123,456,789,01,2.3456789")
2918 , "1234567.8,90,123,456,789 @ prec=12" ~:
2919 ((Format.Ledger.Write.show False $
2920 Format.Ledger.Write.amount
2922 { Amount.quantity = Decimal 12 1234567890123456789
2923 , Amount.style = Amount.Style.nil
2924 { Amount.Style.fractioning = Just '.'
2925 , Amount.Style.precision = 12
2926 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2930 "1234567.8,90,123,456,789")
2931 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2932 ((Format.Ledger.Write.show False $
2933 Format.Ledger.Write.amount
2935 { Amount.quantity = Decimal 7 1234567890123456789
2936 , Amount.style = Amount.Style.nil
2937 { Amount.Style.fractioning = Just '.'
2938 , Amount.Style.precision = 7
2939 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2943 "1,2,3,4,5,6,7,89,012.3456789")
2944 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2945 ((Format.Ledger.Write.show False $
2946 Format.Ledger.Write.amount
2948 { Amount.quantity = Decimal 12 1234567890123456789
2949 , Amount.style = Amount.Style.nil
2950 { Amount.Style.fractioning = Just '.'
2951 , Amount.Style.precision = 12
2952 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2956 "1234567.890,12,3,4,5,6,7,8,9")
2958 , "amount_length" ~: TestList
2960 ((Format.Ledger.Write.amount_length
2965 ((Format.Ledger.Write.amount_length
2967 { Amount.style = Amount.Style.nil
2968 { Amount.Style.precision = 2 }
2973 ((Format.Ledger.Write.amount_length
2975 { Amount.quantity = Decimal 0 123
2980 ((Format.Ledger.Write.amount_length
2982 { Amount.quantity = Decimal 0 (- 123)
2986 , "12.3 @ prec=0" ~:
2987 ((Format.Ledger.Write.amount_length
2989 { Amount.quantity = Decimal 1 123
2990 , Amount.style = Amount.Style.nil
2991 { Amount.Style.fractioning = Just '.'
2996 , "12.5 @ prec=0" ~:
2997 ((Format.Ledger.Write.amount_length
2999 { Amount.quantity = Decimal 1 125
3000 , Amount.style = Amount.Style.nil
3001 { Amount.Style.fractioning = Just '.'
3006 , "12.3 @ prec=1" ~:
3007 ((Format.Ledger.Write.amount_length
3009 { Amount.quantity = Decimal 1 123
3010 , Amount.style = Amount.Style.nil
3011 { Amount.Style.fractioning = Just '.'
3012 , Amount.Style.precision = 1
3017 , "1,234.56 @ prec=2" ~:
3018 ((Format.Ledger.Write.amount_length
3020 { Amount.quantity = Decimal 2 123456
3021 , Amount.style = Amount.Style.nil
3022 { Amount.Style.fractioning = Just '.'
3023 , Amount.Style.precision = 2
3024 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
3029 , "123,456,789,01,2.3456789 @ prec=7" ~:
3030 ((Format.Ledger.Write.amount_length
3032 { Amount.quantity = Decimal 7 1234567890123456789
3033 , Amount.style = Amount.Style.nil
3034 { Amount.Style.fractioning = Just '.'
3035 , Amount.Style.precision = 7
3036 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3041 , "1234567.8,90,123,456,789 @ prec=12" ~:
3042 ((Format.Ledger.Write.amount_length
3044 { Amount.quantity = Decimal 12 1234567890123456789
3045 , Amount.style = Amount.Style.nil
3046 { Amount.Style.fractioning = Just '.'
3047 , Amount.Style.precision = 12
3048 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
3053 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
3054 ((Format.Ledger.Write.amount_length
3056 { Amount.quantity = Decimal 7 1234567890123456789
3057 , Amount.style = Amount.Style.nil
3058 { Amount.Style.fractioning = Just '.'
3059 , Amount.Style.precision = 7
3060 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3065 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
3066 ((Format.Ledger.Write.amount_length
3068 { Amount.quantity = Decimal 12 1234567890123456789
3069 , Amount.style = Amount.Style.nil
3070 { Amount.Style.fractioning = Just '.'
3071 , Amount.Style.precision = 12
3072 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
3078 , "date" ~: TestList
3080 ((Format.Ledger.Write.show False $
3081 Format.Ledger.Write.date
3085 , "2000/01/01 12:34:51 CET" ~:
3086 (Format.Ledger.Write.show False $
3087 Format.Ledger.Write.date $
3090 (Time.fromGregorian 2000 01 01)
3091 (Time.TimeOfDay 12 34 51))
3092 (Time.TimeZone 60 False "CET"))
3094 "2000/01/01 12:34:51 CET"
3095 , "2000/01/01 12:34:51 +0100" ~:
3096 (Format.Ledger.Write.show False $
3097 Format.Ledger.Write.date $
3100 (Time.fromGregorian 2000 01 01)
3101 (Time.TimeOfDay 12 34 51))
3102 (Time.TimeZone 60 False ""))
3104 "2000/01/01 12:34:51 +0100"
3105 , "2000/01/01 01:02:03" ~:
3106 (Format.Ledger.Write.show False $
3107 Format.Ledger.Write.date $
3110 (Time.fromGregorian 2000 01 01)
3111 (Time.TimeOfDay 1 2 3))
3114 "2000/01/01 01:02:03"
3116 (Format.Ledger.Write.show False $
3117 Format.Ledger.Write.date $
3120 (Time.fromGregorian 0 01 01)
3121 (Time.TimeOfDay 1 2 0))
3126 (Format.Ledger.Write.show False $
3127 Format.Ledger.Write.date $
3130 (Time.fromGregorian 0 01 01)
3131 (Time.TimeOfDay 1 0 0))
3136 (Format.Ledger.Write.show False $
3137 Format.Ledger.Write.date $
3140 (Time.fromGregorian 0 01 01)
3141 (Time.TimeOfDay 0 1 0))
3146 (Format.Ledger.Write.show False $
3147 Format.Ledger.Write.date $
3150 (Time.fromGregorian 0 01 01)
3151 (Time.TimeOfDay 0 0 0))
3156 , "transaction" ~: TestList
3158 ((Format.Ledger.Write.show False $
3159 Format.Ledger.Write.transaction
3160 Format.Ledger.transaction)
3163 , "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" ~:
3164 ((Format.Ledger.Write.show False $
3165 Format.Ledger.Write.transaction $
3166 Format.Ledger.transaction
3167 { Format.Ledger.transaction_dates=
3170 (Time.fromGregorian 2000 01 01)
3171 (Time.TimeOfDay 0 0 0))
3174 , Format.Ledger.transaction_description="some description"
3175 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3176 [ (Format.Ledger.posting ("A":|["B", "C"]))
3177 { Format.Ledger.posting_amounts = Data.Map.fromList
3179 { Amount.quantity = 1
3180 , Amount.style = Amount.Style.nil
3181 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3182 , Amount.Style.unit_spaced = Just False
3188 , (Format.Ledger.posting ("a":|["b", "c"]))
3189 { Format.Ledger.posting_comments = ["first comment","second comment","third comment"]
3194 "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")
3195 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
3196 ((Format.Ledger.Write.show False $
3197 Format.Ledger.Write.transaction $
3198 Format.Ledger.transaction
3199 { Format.Ledger.transaction_dates=
3202 (Time.fromGregorian 2000 01 01)
3203 (Time.TimeOfDay 0 0 0))
3206 , Format.Ledger.transaction_description="some description"
3207 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
3208 [ (Format.Ledger.posting ("A":|["B", "C"]))
3209 { Format.Ledger.posting_amounts = Data.Map.fromList
3211 { Amount.quantity = 1
3212 , Amount.style = Amount.Style.nil
3213 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3214 , Amount.Style.unit_spaced = Just False
3220 , (Format.Ledger.posting ("AA":|["BB", "CC"]))
3221 { Format.Ledger.posting_amounts = Data.Map.fromList
3223 { Amount.quantity = 123
3224 , Amount.style = Amount.Style.nil
3225 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3226 , Amount.Style.unit_spaced = Just False
3235 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")