1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TupleSections #-}
7 import Test.HUnit hiding ((~?))
8 import Test.Framework.Providers.HUnit (hUnitTestToTests)
9 import Test.Framework.Runners.Console (defaultMain)
11 -- import Control.Applicative (Const(..))
12 import Control.Arrow ((***))
13 import Control.Monad.IO.Class (liftIO)
14 import Data.Decimal (DecimalRaw(..))
15 import qualified Data.Either
16 import Data.Function (on)
17 -- import Data.Functor.Compose (Compose(..))
18 import qualified Data.List
19 import Data.List.NonEmpty (NonEmpty(..))
20 import qualified Data.Map.Strict as Data.Map
21 import Data.Maybe (fromJust)
22 import qualified Data.Strict.Maybe as Strict
23 import Data.Text (Text)
24 import qualified Data.Time.Calendar as Time
25 import qualified Data.Time.LocalTime as Time
26 import qualified Text.Parsec as P hiding (char, space, spaces, string)
27 import qualified Text.Parsec.Pos as P
28 -- import qualified Text.PrettyPrint.Leijen.Text as PP
30 import Hcompta.Account (Account)
31 import qualified Hcompta.Account as Account
32 import Hcompta.Amount (Amount)
33 import qualified Hcompta.Amount as Amount
34 import qualified Hcompta.Amount.Read as Amount.Read
35 import qualified Hcompta.Amount.Write as Amount.Write
36 import qualified Hcompta.Amount.Style as Amount.Style
37 import qualified Hcompta.Balance as Balance
38 import qualified Hcompta.Date as Date
39 import qualified Hcompta.Date.Read as Date.Read
40 import qualified Hcompta.Date.Write as Date.Write
41 import qualified Hcompta.Filter as Filter
42 import qualified Hcompta.Filter.Read as Filter.Read
43 import qualified Hcompta.Format.Ledger as Format.Ledger
44 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
45 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
46 -- import qualified Hcompta.Journal as Journal
47 import qualified Hcompta.Lib.Foldable as Lib.Foldable
48 import qualified Hcompta.Lib.Interval as Lib.Interval
49 import qualified Hcompta.Lib.Interval.Sieve as Lib.Interval.Sieve
50 import qualified Hcompta.Lib.Parsec as P
51 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
54 main = defaultMain $ hUnitTestToTests test_Hcompta
56 (~?) :: String -> Bool -> Test
57 (~?) s b = s ~: (b ~?= True)
63 [ "TreeMap" ~: TestList
64 [ "insert" ~: TestList
66 (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty)
68 (Lib.TreeMap.TreeMap $
70 [ ((0::Int), Lib.TreeMap.leaf ())
73 (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty)
75 (Lib.TreeMap.TreeMap $
77 [ ((0::Int), Lib.TreeMap.Node
78 { Lib.TreeMap.node_value = Strict.Nothing
79 , Lib.TreeMap.node_size = 1
80 , Lib.TreeMap.node_descendants =
81 Lib.TreeMap.singleton ((1::Int):|[]) ()
88 , "map_by_depth_first" ~: TestList
89 [ "[0, 0/1, 0/1/2, 1, 1/2/3]" ~:
90 (Lib.TreeMap.map_by_depth_first
91 (\descendants value ->
94 Strict.fromMaybe undefined $
95 Lib.TreeMap.node_value v
97 (Strict.fromMaybe [] value)
98 (Lib.TreeMap.nodes descendants)
100 Lib.TreeMap.from_List const
101 [ (((0::Integer):|[]), [0])
103 , ((0:|1:2:[]), [0,1,2])
105 , ((1:|2:3:[]), [1,2,3])
109 (Lib.TreeMap.from_List const
110 [ ((0:|[]), [0,0,1,0,1,2])
111 , ((0:|1:[]), [0,1,0,1,2])
112 , ((0:|1:2:[]), [0,1,2])
113 , ((1:|[]), [1,1,2,3])
114 , ((1:|2:[]), [1,2,3])
115 , ((1:|2:3:[]), [1,2,3])
118 (Lib.TreeMap.map_by_depth_first
119 (\descendants value ->
121 (\acc v -> (++) acc $
122 Strict.fromMaybe undefined $
123 Lib.TreeMap.node_value v
125 (Strict.fromMaybe [] value)
126 (Lib.TreeMap.nodes descendants)
128 Lib.TreeMap.from_List const
129 [ (((0::Integer):|0:[]), [0,0])
133 (Lib.TreeMap.from_List const
138 , "flatten" ~: TestList
139 [ "[0, 0/1, 0/1/2]" ~:
140 (Lib.TreeMap.flatten id $
141 Lib.TreeMap.from_List const
142 [ (((0::Integer):|[]), ())
153 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
154 (Lib.TreeMap.flatten id $
155 Lib.TreeMap.from_List const
164 , ((11:|2:33:[]), ())
169 [ (((1::Integer):|[]), ())
177 , ((11:|2:33:[]), ())
181 , "Foldable" ~: TestList
182 [ "accumLeftsAndFoldrRights" ~: TestList
184 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
187 (([(0::Integer)], [(""::String)]))
189 ((take 1 *** take 0) $
190 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
191 ( repeat (Left [0]) ))
193 ([(0::Integer)], ([]::[String]))
194 , "Right:Left:Right:Left" ~:
195 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
196 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
198 (([1, 0]::[Integer]), (["2", "1", "0"]::[String]))
199 , "Right:Left:Right:repeat Left" ~:
200 ((take 1 *** take 2) $
201 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
202 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
204 (([1]::[Integer]), (["2", "1"]::[String]))
207 , "Interval" ~: TestList
208 [ "position" ~: TestList $
211 let i = fromJust mi in
212 let j = fromJust mj in
215 Lib.Interval.Equal -> (EQ, EQ)
217 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.position i j ~?= (p, le)
218 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.position j i ~?= (p, ge)
221 [ ( (Lib.Interval.<..<) 0 (4::Integer)
222 , (Lib.Interval.<..<) 5 9
223 , Lib.Interval.Away )
224 , ( (Lib.Interval.<..<) 0 4
225 , (Lib.Interval.<=..<) 4 9
226 , Lib.Interval.Adjacent )
227 , ( (Lib.Interval.<..<) 0 5
228 , (Lib.Interval.<..<) 4 9
229 , Lib.Interval.Overlap )
230 , ( (Lib.Interval.<..<) 0 5
231 , (Lib.Interval.<..<) 0 9
232 , Lib.Interval.Prefix )
233 , ( (Lib.Interval.<..<) 0 9
234 , (Lib.Interval.<..<) 1 8
235 , Lib.Interval.Include )
236 , ( (Lib.Interval.<..<) 0 9
237 , (Lib.Interval.<..<) 5 9
238 , Lib.Interval.Suffixed )
239 , ( (Lib.Interval.<..<) 0 9
240 , (Lib.Interval.<..<) 0 9
241 , Lib.Interval.Equal )
242 , ( (Lib.Interval.<..<) 0 9
243 , (Lib.Interval.<..<=) 0 9
244 , Lib.Interval.Prefix )
245 , ( (Lib.Interval.<=..<) 0 9
246 , (Lib.Interval.<..<) 0 9
247 , Lib.Interval.Suffixed )
248 , ( (Lib.Interval.<=..<=) 0 9
249 , (Lib.Interval.<..<) 0 9
250 , Lib.Interval.Include )
252 , "intersection" ~: TestList $
255 let i = fromJust mi in
256 let j = fromJust mj in
257 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.intersection i j ~?= e
258 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.intersection j i ~?= e
261 [ ( (Lib.Interval.<..<) 0 (4::Integer)
262 , (Lib.Interval.<..<) 5 9
264 , ( (Lib.Interval.<..<=) 0 5
265 , (Lib.Interval.<=..<) 5 9
266 , (Lib.Interval.<=..<=) 5 5 )
267 , ( (Lib.Interval.<..<) 0 6
268 , (Lib.Interval.<..<) 4 9
269 , (Lib.Interval.<..<) 4 6 )
270 , ( (Lib.Interval.<..<=) 0 6
271 , (Lib.Interval.<=..<) 4 9
272 , (Lib.Interval.<=..<=) 4 6 )
273 , ( (Lib.Interval.<..<) 0 6
274 , (Lib.Interval.<=..<) 4 9
275 , (Lib.Interval.<=..<) 4 6 )
276 , ( (Lib.Interval.<..<=) 0 6
277 , (Lib.Interval.<..<) 4 9
278 , (Lib.Interval.<..<=) 4 6 )
279 , ( (Lib.Interval.<..<) 0 9
280 , (Lib.Interval.<..<) 0 9
281 , (Lib.Interval.<..<) 0 9 )
282 , ( (Lib.Interval.<=..<) 0 9
283 , (Lib.Interval.<..<=) 0 9
284 , (Lib.Interval.<..<) 0 9 )
285 , ( (Lib.Interval.<..<=) 0 9
286 , (Lib.Interval.<=..<) 0 9
287 , (Lib.Interval.<..<) 0 9 )
288 , ( (Lib.Interval.<=..<=) 0 9
289 , (Lib.Interval.<=..<=) 0 9
290 , (Lib.Interval.<=..<=) 0 9 )
292 , "union" ~: TestList $
295 let i = fromJust mi in
296 let j = fromJust mj in
297 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.union i j ~?= e
298 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.union j i ~?= e
301 [ ( (Lib.Interval.<..<) 0 (4::Integer)
302 , (Lib.Interval.<..<) 5 9
304 , ( (Lib.Interval.<..<=) 0 5
305 , (Lib.Interval.<..<) 5 9
306 , (Lib.Interval.<..<) 0 9 )
307 , ( (Lib.Interval.<..<) 0 5
308 , (Lib.Interval.<=..<) 5 9
309 , (Lib.Interval.<..<) 0 9 )
310 , ( (Lib.Interval.<..<=) 0 5
311 , (Lib.Interval.<=..<) 5 9
312 , (Lib.Interval.<..<) 0 9 )
313 , ( (Lib.Interval.<..<) 0 6
314 , (Lib.Interval.<..<) 4 9
315 , (Lib.Interval.<..<) 0 9 )
316 , ( (Lib.Interval.<..<) 0 9
317 , (Lib.Interval.<..<) 0 9
318 , (Lib.Interval.<..<) 0 9 )
319 , ( (Lib.Interval.<=..<) 0 9
320 , (Lib.Interval.<..<=) 0 9
321 , (Lib.Interval.<=..<=) 0 9 )
322 , ( (Lib.Interval.<..<=) 0 9
323 , (Lib.Interval.<=..<) 0 9
324 , (Lib.Interval.<=..<=) 0 9 )
325 , ( (Lib.Interval.<=..<=) 0 9
326 , (Lib.Interval.<=..<=) 0 9
327 , (Lib.Interval.<=..<=) 0 9 )
329 , "Sieve" ~: TestList $
330 [ "union" ~: TestList $
333 let is = map (fromJust) mis in
334 let e = map (fromJust) me in
336 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
337 Lib.Interval.Sieve.empty is in
339 (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)
340 Lib.Interval.Sieve.empty is in
341 [ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ~:
342 Lib.Interval.Sieve.intervals sil ~?= e
343 , (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ reverse is) ~:
344 Lib.Interval.Sieve.intervals sir ~?= e
347 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer)
348 , (Lib.Interval.<=..<=) 5 9
350 , [ (Lib.Interval.<=..<=) 0 9 ]
352 , ( [ (Lib.Interval.<=..<=) 0 5
353 , (Lib.Interval.<=..<=) 0 9
355 , [ (Lib.Interval.<=..<=) 0 9 ]
357 , ( [ (Lib.Interval.<=..<=) 0 4
358 , (Lib.Interval.<=..<=) 5 9
359 , (Lib.Interval.<=..<=) 3 6
361 , [ (Lib.Interval.<=..<=) 0 9 ]
363 , ( [ (Lib.Interval.<=..<=) 1 4
364 , (Lib.Interval.<=..<=) 5 8
366 , [ (Lib.Interval.<=..<=) 1 4
367 , (Lib.Interval.<=..<=) 5 8
370 , ( [ (Lib.Interval.<=..<=) 1 8
371 , (Lib.Interval.<=..<=) 0 9
373 , [ (Lib.Interval.<=..<=) 0 9 ]
375 , ( [ (Lib.Interval.<=..<=) 1 4
376 , (Lib.Interval.<=..<=) 5 8
377 , (Lib.Interval.<=..<=) 0 9
379 , [ (Lib.Interval.<=..<=) 0 9 ]
382 ++ Data.List.concatMap
384 let is = map fromJust mis in
385 let js = map fromJust mjs in
386 let e = map fromJust me in
388 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
389 Lib.Interval.Sieve.empty is in
391 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
392 Lib.Interval.Sieve.empty js in
393 [ ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " u " ++
394 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
395 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union iu ju) ~?= e
396 , ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " u " ++
397 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
398 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union ju iu) ~?= e
401 [ ( [ (Lib.Interval.<=..<=) 0 (1::Integer)
402 , (Lib.Interval.<=..<=) 2 4
404 , [ (Lib.Interval.<=..<=) 0 3
406 , [ (Lib.Interval.<=..<=) 0 4
409 , ( [ (Lib.Interval.<=..<=) 0 1
410 , (Lib.Interval.<=..<=) 2 3
411 , (Lib.Interval.<=..<=) 4 5
412 , (Lib.Interval.<=..<=) 6 7
414 , [ (Lib.Interval.<=..<=) 1 2
415 , (Lib.Interval.<=..<=) 3 4
416 , (Lib.Interval.<=..<=) 5 6
418 , [ (Lib.Interval.<=..<=) 0 7
421 , ( [ (Lib.Interval.<=..<=) 0 1
422 , (Lib.Interval.<=..<=) 2 3
424 , [ (Lib.Interval.<=..<=) 4 5
426 , [ (Lib.Interval.<=..<=) 0 1
427 , (Lib.Interval.<=..<=) 2 3
428 , (Lib.Interval.<=..<=) 4 5
431 , ( [ (Lib.Interval.<=..<=) 0 1
432 , (Lib.Interval.<=..<=) 4 5
434 , [ (Lib.Interval.<=..<=) 2 3
436 , [ (Lib.Interval.<=..<=) 0 1
437 , (Lib.Interval.<=..<=) 2 3
438 , (Lib.Interval.<=..<=) 4 5
442 , "intersection" ~: TestList $
445 let is = map (fromJust) mis in
446 let js = map (fromJust) mjs in
447 let e = map (fromJust) me in
449 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
450 Lib.Interval.Sieve.empty is in
452 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
453 Lib.Interval.Sieve.empty js in
454 [ ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " n " ++
455 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
456 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection iu ju) ~?= e
457 , ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " n " ++
458 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
459 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection ju iu) ~?= e
462 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) ]
463 , [ (Lib.Interval.<=..<=) 5 9 ]
466 , ( [ (Lib.Interval.<=..<=) 0 5 ]
467 , [ (Lib.Interval.<=..<=) 5 9 ]
468 , [ (Lib.Interval.<=..<=) 5 5 ]
470 , ( [ (Lib.Interval.<=..<=) 0 5 ]
471 , [ (Lib.Interval.<=..<=) 0 9 ]
472 , [ (Lib.Interval.<=..<=) 0 5 ]
474 , ( [ (Lib.Interval.<=..<=) 0 4
475 , (Lib.Interval.<=..<=) 5 9
477 , [ (Lib.Interval.<=..<=) 3 6 ]
478 , [ (Lib.Interval.<=..<=) 3 4
479 , (Lib.Interval.<=..<=) 5 6
482 , ( [ (Lib.Interval.<=..<=) 1 4
483 , (Lib.Interval.<=..<=) 6 8
485 , [ (Lib.Interval.<=..<=) 2 3
486 , (Lib.Interval.<=..<=) 5 7
488 , [ (Lib.Interval.<=..<=) 2 3
489 , (Lib.Interval.<=..<=) 6 7
493 , "complement" ~: TestList $
496 let is = map fromJust mis in
497 let e = map fromJust me in
499 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
500 Lib.Interval.Sieve.empty is in
501 [ show (Lib.Interval.Pretty $
502 Lib.Interval.Sieve.fmap_interval
503 (Lib.Interval.fmap_unsafe $ Lib.Interval.Pretty) iu) ~:
504 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement iu) ~?= e
507 [ ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 (5::Integer)
508 , ((Lib.Interval.<=..<=) `on` Lib.Interval.Limited) 5 9
510 , [ Just $ (Lib.Interval...<) 0
511 , Just $ (Lib.Interval.<..) 9
514 , ( [ Just $ Lib.Interval.unlimited ]
518 , [ Just $ Lib.Interval.unlimited ]
520 , ( [ Just $ (Lib.Interval...<) 0
521 , Just $ (Lib.Interval.<..) 0
523 , [ Just $ Lib.Interval.point $ Lib.Interval.Limited 0
526 , ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 1
527 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 2 3
528 , ((Lib.Interval.<..<=) `on` Lib.Interval.Limited) 3 4
530 , [ Just $ (Lib.Interval...<) 0
531 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 1 2
532 , Just $ Lib.Interval.point $ Lib.Interval.Limited 3
533 , Just $ (Lib.Interval.<..) 4
537 , "complement_with" ~: TestList $
540 let ib = fromJust mib in
541 let is = map fromJust mis in
542 let e = map fromJust me in
544 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
545 Lib.Interval.Sieve.empty is in
546 [ show (Lib.Interval.Pretty iu) ~:
547 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement_with ib iu) ~?= e
550 [ ( (Lib.Interval.<=..<=) (-10) (10::Integer)
551 , [ (Lib.Interval.<=..<) 0 5
552 , (Lib.Interval.<=..<=) 5 9
554 , [ (Lib.Interval.<=..<) (-10) 0
555 , (Lib.Interval.<..<=) 9 10
558 , ( (Lib.Interval.<=..<=) (-10) 10
559 , [ (Lib.Interval.<=..<=) (-10) 10 ]
562 , ( (Lib.Interval.<=..<=) (-10) 10
564 , [ (Lib.Interval.<=..<=) (-10) 10 ]
566 , ( (Lib.Interval.<=..<=) (-10) 10
567 , [ (Lib.Interval.<=..<) (-10) 0
568 , (Lib.Interval.<..<=) 0 10
570 , [ Just $ Lib.Interval.point 0
573 , ( (Lib.Interval.<=..<=) (-10) 10
574 , [ Just $ Lib.Interval.point 0
576 , [ (Lib.Interval.<=..<) (-10) 0
577 , (Lib.Interval.<..<=) 0 10
580 , ( (Lib.Interval.<=..<=) 0 10
581 , [ (Lib.Interval.<..<=) 0 10
583 , [ Just $ Lib.Interval.point 0
586 , ( (Lib.Interval.<=..<=) 0 10
587 , [ (Lib.Interval.<=..<) 0 10
589 , [ Just $ Lib.Interval.point 10
592 , ( Just $ Lib.Interval.point 0
595 , [ Just $ Lib.Interval.point 0
598 , ( Just $ Lib.Interval.point 0
599 , [ Just $ Lib.Interval.point 0
608 , "Account" ~: TestList
609 [ "foldr" ~: TestList
611 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
613 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
615 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
617 , "ascending" ~: TestList
619 Account.ascending ("A":|[]) ~?= Nothing
621 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
623 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
626 , "Amount" ~: TestList
631 { Amount.quantity = Decimal 0 1
632 , Amount.style = Amount.Style.nil
633 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
638 { Amount.quantity = Decimal 0 1
639 , Amount.style = Amount.Style.nil
640 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
646 { Amount.quantity = Decimal 0 2
647 , Amount.style = Amount.Style.nil
648 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
653 , "from_List" ~: TestList
654 [ "from_List [$1, 1$] = $2" ~:
657 { Amount.quantity = Decimal 0 1
658 , Amount.style = Amount.Style.nil
659 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
664 { Amount.quantity = Decimal 0 1
665 , Amount.style = Amount.Style.nil
666 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
674 { Amount.quantity = Decimal 0 2
675 , Amount.style = Amount.Style.nil
676 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
683 [ "amount" ~: TestList
685 (Data.Either.rights $
687 (Amount.Read.amount <* P.eof)
691 , "\"0\" = Right 0" ~:
692 (Data.Either.rights $
694 (Amount.Read.amount <* P.eof)
698 { Amount.quantity = Decimal 0 0
700 , "\"00\" = Right 0" ~:
701 (Data.Either.rights $
703 (Amount.Read.amount <* P.eof)
707 { Amount.quantity = Decimal 0 0
709 , "\"0.\" = Right 0." ~:
710 (Data.Either.rights $
712 (Amount.Read.amount <* P.eof)
716 { Amount.quantity = Decimal 0 0
719 { Amount.Style.fractioning = Just '.'
722 , "\".0\" = Right 0.0" ~:
723 (Data.Either.rights $
725 (Amount.Read.amount <* P.eof)
729 { Amount.quantity = Decimal 0 0
732 { Amount.Style.fractioning = Just '.'
733 , Amount.Style.precision = 1
736 , "\"0,\" = Right 0," ~:
737 (Data.Either.rights $
739 (Amount.Read.amount <* P.eof)
743 { Amount.quantity = Decimal 0 0
746 { Amount.Style.fractioning = Just ','
749 , "\",0\" = Right 0,0" ~:
750 (Data.Either.rights $
752 (Amount.Read.amount <* P.eof)
756 { Amount.quantity = Decimal 0 0
759 { Amount.Style.fractioning = Just ','
760 , Amount.Style.precision = 1
764 (Data.Either.rights $
766 (Amount.Read.amount <* P.eof)
771 (Data.Either.rights $
773 (Amount.Read.amount <* P.eof)
777 , "\"0.0\" = Right 0.0" ~:
778 (Data.Either.rights $
780 (Amount.Read.amount <* P.eof)
781 () "" ("0.0"::Text)])
784 { Amount.quantity = Decimal 0 0
787 { Amount.Style.fractioning = Just '.'
788 , Amount.Style.precision = 1
791 , "\"00.00\" = Right 0.00" ~:
792 (Data.Either.rights $
794 (Amount.Read.amount <* P.eof)
795 () "" ("00.00"::Text)])
798 { Amount.quantity = Decimal 0 0
801 { Amount.Style.fractioning = Just '.'
802 , Amount.Style.precision = 2
805 , "\"0,0\" = Right 0,0" ~:
806 (Data.Either.rights $
808 (Amount.Read.amount <* P.eof)
809 () "" ("0,0"::Text)])
812 { Amount.quantity = Decimal 0 0
815 { Amount.Style.fractioning = Just ','
816 , Amount.Style.precision = 1
819 , "\"00,00\" = Right 0,00" ~:
820 (Data.Either.rights $
822 (Amount.Read.amount <* P.eof)
823 () "" ("00,00"::Text)])
826 { Amount.quantity = Decimal 0 0
829 { Amount.Style.fractioning = Just ','
830 , Amount.Style.precision = 2
833 , "\"0_0\" = Right 0" ~:
834 (Data.Either.rights $
836 (Amount.Read.amount <* P.eof)
837 () "" ("0_0"::Text)])
840 { Amount.quantity = Decimal 0 0
843 { Amount.Style.fractioning = Nothing
844 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
845 , Amount.Style.precision = 0
848 , "\"00_00\" = Right 0" ~:
849 (Data.Either.rights $
851 (Amount.Read.amount <* P.eof)
852 () "" ("00_00"::Text)])
855 { Amount.quantity = Decimal 0 0
858 { Amount.Style.fractioning = Nothing
859 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
860 , Amount.Style.precision = 0
863 , "\"0,000.00\" = Right 0,000.00" ~:
864 (Data.Either.rights $
866 (Amount.Read.amount <* P.eof)
867 () "" ("0,000.00"::Text)])
870 { Amount.quantity = Decimal 0 0
873 { Amount.Style.fractioning = Just '.'
874 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
875 , Amount.Style.precision = 2
878 , "\"0.000,00\" = Right 0.000,00" ~:
879 (Data.Either.rights $
882 () "" ("0.000,00"::Text)])
885 { Amount.quantity = Decimal 0 0
888 { Amount.Style.fractioning = Just ','
889 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
890 , Amount.Style.precision = 2
893 , "\"1,000.00\" = Right 1,000.00" ~:
894 (Data.Either.rights $
896 (Amount.Read.amount <* P.eof)
897 () "" ("1,000.00"::Text)])
900 { Amount.quantity = Decimal 0 1000
903 { Amount.Style.fractioning = Just '.'
904 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
905 , Amount.Style.precision = 2
908 , "\"1.000,00\" = Right 1.000,00" ~:
909 (Data.Either.rights $
912 () "" ("1.000,00"::Text)])
915 { Amount.quantity = Decimal 0 1000
918 { Amount.Style.fractioning = Just ','
919 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
920 , Amount.Style.precision = 2
923 , "\"1,000.00.\" = Left" ~:
924 (Data.Either.rights $
927 () "" ("1,000.00."::Text)])
930 , "\"1.000,00,\" = Left" ~:
931 (Data.Either.rights $
934 () "" ("1.000,00,"::Text)])
937 , "\"1,000.00_\" = Left" ~:
938 (Data.Either.rights $
941 () "" ("1,000.00_"::Text)])
944 , "\"12\" = Right 12" ~:
945 (Data.Either.rights $
947 (Amount.Read.amount <* P.eof)
948 () "" ("123"::Text)])
951 { Amount.quantity = Decimal 0 123
953 , "\"1.2\" = Right 1.2" ~:
954 (Data.Either.rights $
956 (Amount.Read.amount <* P.eof)
957 () "" ("1.2"::Text)])
960 { Amount.quantity = Decimal 1 12
963 { Amount.Style.fractioning = Just '.'
964 , Amount.Style.precision = 1
967 , "\"1,2\" = Right 1,2" ~:
968 (Data.Either.rights $
970 (Amount.Read.amount <* P.eof)
971 () "" ("1,2"::Text)])
974 { Amount.quantity = Decimal 1 12
977 { Amount.Style.fractioning = Just ','
978 , Amount.Style.precision = 1
981 , "\"12.23\" = Right 12.23" ~:
982 (Data.Either.rights $
984 (Amount.Read.amount <* P.eof)
985 () "" ("12.34"::Text)])
988 { Amount.quantity = Decimal 2 1234
991 { Amount.Style.fractioning = Just '.'
992 , Amount.Style.precision = 2
995 , "\"12,23\" = Right 12,23" ~:
996 (Data.Either.rights $
998 (Amount.Read.amount <* P.eof)
999 () "" ("12,34"::Text)])
1002 { Amount.quantity = Decimal 2 1234
1005 { Amount.Style.fractioning = Just ','
1006 , Amount.Style.precision = 2
1009 , "\"1_2\" = Right 1_2" ~:
1010 (Data.Either.rights $
1012 (Amount.Read.amount <* P.eof)
1013 () "" ("1_2"::Text)])
1016 { Amount.quantity = Decimal 0 12
1019 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1020 , Amount.Style.precision = 0
1023 , "\"1_23\" = Right 1_23" ~:
1024 (Data.Either.rights $
1026 (Amount.Read.amount <* P.eof)
1027 () "" ("1_23"::Text)])
1030 { Amount.quantity = Decimal 0 123
1033 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1034 , Amount.Style.precision = 0
1037 , "\"1_23_456\" = Right 1_23_456" ~:
1038 (Data.Either.rights $
1040 (Amount.Read.amount <* P.eof)
1041 () "" ("1_23_456"::Text)])
1044 { Amount.quantity = Decimal 0 123456
1047 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1048 , Amount.Style.precision = 0
1051 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1052 (Data.Either.rights $
1054 (Amount.Read.amount <* P.eof)
1055 () "" ("1_23_456.7890_12345_678901"::Text)])
1058 { Amount.quantity = Decimal 15 123456789012345678901
1061 { Amount.Style.fractioning = Just '.'
1062 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1063 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1064 , Amount.Style.precision = 15
1067 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1068 (Data.Either.rights $
1070 (Amount.Read.amount <* P.eof)
1071 () "" ("123456_78901_2345.678_90_1"::Text)])
1074 { Amount.quantity = Decimal 6 123456789012345678901
1077 { Amount.Style.fractioning = Just '.'
1078 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1079 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1080 , Amount.Style.precision = 6
1083 , "\"$1\" = Right $1" ~:
1084 (Data.Either.rights $
1086 (Amount.Read.amount <* P.eof)
1087 () "" ("$1"::Text)])
1090 { Amount.quantity = Decimal 0 1
1093 { Amount.Style.fractioning = Nothing
1094 , Amount.Style.grouping_integral = Nothing
1095 , Amount.Style.grouping_fractional = Nothing
1096 , Amount.Style.precision = 0
1097 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1098 , Amount.Style.unit_spaced = Just False
1102 , "\"1$\" = Right 1$" ~:
1103 (Data.Either.rights $
1105 (Amount.Read.amount <* P.eof)
1106 () "" ("1$"::Text)])
1109 { Amount.quantity = Decimal 0 1
1112 { Amount.Style.fractioning = Nothing
1113 , Amount.Style.grouping_integral = Nothing
1114 , Amount.Style.grouping_fractional = Nothing
1115 , Amount.Style.precision = 0
1116 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1117 , Amount.Style.unit_spaced = Just False
1121 , "\"$ 1\" = Right $ 1" ~:
1122 (Data.Either.rights $
1124 (Amount.Read.amount <* P.eof)
1125 () "" ("$ 1"::Text)])
1128 { Amount.quantity = Decimal 0 1
1131 { Amount.Style.fractioning = Nothing
1132 , Amount.Style.grouping_integral = Nothing
1133 , Amount.Style.grouping_fractional = Nothing
1134 , Amount.Style.precision = 0
1135 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1136 , Amount.Style.unit_spaced = Just True
1140 , "\"1 $\" = Right 1 $" ~:
1141 (Data.Either.rights $
1143 (Amount.Read.amount <* P.eof)
1144 () "" ("1 $"::Text)])
1147 { Amount.quantity = Decimal 0 1
1150 { Amount.Style.fractioning = Nothing
1151 , Amount.Style.grouping_integral = Nothing
1152 , Amount.Style.grouping_fractional = Nothing
1153 , Amount.Style.precision = 0
1154 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1155 , Amount.Style.unit_spaced = Just True
1159 , "\"-$1\" = Right $-1" ~:
1160 (Data.Either.rights $
1162 (Amount.Read.amount <* P.eof)
1163 () "" ("-$1"::Text)])
1166 { Amount.quantity = Decimal 0 (-1)
1169 { Amount.Style.fractioning = Nothing
1170 , Amount.Style.grouping_integral = Nothing
1171 , Amount.Style.grouping_fractional = Nothing
1172 , Amount.Style.precision = 0
1173 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1174 , Amount.Style.unit_spaced = Just False
1178 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1179 (Data.Either.rights $
1181 (Amount.Read.amount <* P.eof)
1182 () "" ("\"4 2\"1"::Text)])
1185 { Amount.quantity = Decimal 0 1
1188 { Amount.Style.fractioning = Nothing
1189 , Amount.Style.grouping_integral = Nothing
1190 , Amount.Style.grouping_fractional = Nothing
1191 , Amount.Style.precision = 0
1192 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1193 , Amount.Style.unit_spaced = Just False
1195 , Amount.unit = "4 2"
1197 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1198 (Data.Either.rights $
1200 (Amount.Read.amount <* P.eof)
1201 () "" ("1\"4 2\""::Text)])
1204 { Amount.quantity = Decimal 0 1
1207 { Amount.Style.fractioning = Nothing
1208 , Amount.Style.grouping_integral = Nothing
1209 , Amount.Style.grouping_fractional = Nothing
1210 , Amount.Style.precision = 0
1211 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1212 , Amount.Style.unit_spaced = Just False
1214 , Amount.unit = "4 2"
1216 , "\"$1.000,00\" = Right $1.000,00" ~:
1217 (Data.Either.rights $
1219 (Amount.Read.amount <* P.eof)
1220 () "" ("$1.000,00"::Text)])
1223 { Amount.quantity = Decimal 0 1000
1226 { Amount.Style.fractioning = Just ','
1227 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1228 , Amount.Style.grouping_fractional = Nothing
1229 , Amount.Style.precision = 2
1230 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1231 , Amount.Style.unit_spaced = Just False
1235 , "\"1.000,00$\" = Right 1.000,00$" ~:
1236 (Data.Either.rights $
1238 (Amount.Read.amount <* P.eof)
1239 () "" ("1.000,00$"::Text)])
1242 { Amount.quantity = Decimal 0 1000
1245 { Amount.Style.fractioning = Just ','
1246 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1247 , Amount.Style.grouping_fractional = Nothing
1248 , Amount.Style.precision = 2
1249 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1250 , Amount.Style.unit_spaced = Just False
1256 , "Write" ~: TestList
1257 [ "amount" ~: TestList
1259 ((Format.Ledger.Write.show
1260 Format.Ledger.Write.Style
1261 { Format.Ledger.Write.style_color=False
1262 , Format.Ledger.Write.style_align=True
1269 ((Format.Ledger.Write.show
1270 Format.Ledger.Write.Style
1271 { Format.Ledger.Write.style_color=False
1272 , Format.Ledger.Write.style_align=True
1276 { Amount.style = Amount.Style.nil
1277 { Amount.Style.precision = 2 }
1282 ((Format.Ledger.Write.show
1283 Format.Ledger.Write.Style
1284 { Format.Ledger.Write.style_color=False
1285 , Format.Ledger.Write.style_align=True
1289 { Amount.quantity = Decimal 0 123
1294 ((Format.Ledger.Write.show
1295 Format.Ledger.Write.Style
1296 { Format.Ledger.Write.style_color=False
1297 , Format.Ledger.Write.style_align=True
1301 { Amount.quantity = Decimal 0 (- 123)
1305 , "12.3 @ prec=0" ~:
1306 ((Format.Ledger.Write.show
1307 Format.Ledger.Write.Style
1308 { Format.Ledger.Write.style_color=False
1309 , Format.Ledger.Write.style_align=True
1313 { Amount.quantity = Decimal 1 123
1314 , Amount.style = Amount.Style.nil
1315 { Amount.Style.fractioning = Just '.'
1320 , "12.5 @ prec=0" ~:
1321 ((Format.Ledger.Write.show
1322 Format.Ledger.Write.Style
1323 { Format.Ledger.Write.style_color=False
1324 , Format.Ledger.Write.style_align=True
1328 { Amount.quantity = Decimal 1 125
1329 , Amount.style = Amount.Style.nil
1330 { Amount.Style.fractioning = Just '.'
1335 , "12.3 @ prec=1" ~:
1336 ((Format.Ledger.Write.show
1337 Format.Ledger.Write.Style
1338 { Format.Ledger.Write.style_color=False
1339 , Format.Ledger.Write.style_align=True
1343 { Amount.quantity = Decimal 1 123
1344 , Amount.style = Amount.Style.nil
1345 { Amount.Style.fractioning = Just '.'
1346 , Amount.Style.precision = 1
1351 , "1,234.56 @ prec=2" ~:
1352 ((Format.Ledger.Write.show
1353 Format.Ledger.Write.Style
1354 { Format.Ledger.Write.style_color=False
1355 , Format.Ledger.Write.style_align=True
1359 { Amount.quantity = Decimal 2 123456
1360 , Amount.style = Amount.Style.nil
1361 { Amount.Style.fractioning = Just '.'
1362 , Amount.Style.precision = 2
1363 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1368 , "123,456,789,01,2.3456789 @ prec=7" ~:
1369 ((Format.Ledger.Write.show
1370 Format.Ledger.Write.Style
1371 { Format.Ledger.Write.style_color=False
1372 , Format.Ledger.Write.style_align=True
1376 { Amount.quantity = Decimal 7 1234567890123456789
1377 , Amount.style = Amount.Style.nil
1378 { Amount.Style.fractioning = Just '.'
1379 , Amount.Style.precision = 7
1380 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1384 "123,456,789,01,2.3456789")
1385 , "1234567.8,90,123,456,789 @ prec=12" ~:
1386 ((Format.Ledger.Write.show
1387 Format.Ledger.Write.Style
1388 { Format.Ledger.Write.style_color=False
1389 , Format.Ledger.Write.style_align=True
1393 { Amount.quantity = Decimal 12 1234567890123456789
1394 , Amount.style = Amount.Style.nil
1395 { Amount.Style.fractioning = Just '.'
1396 , Amount.Style.precision = 12
1397 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1401 "1234567.8,90,123,456,789")
1402 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
1403 ((Format.Ledger.Write.show
1404 Format.Ledger.Write.Style
1405 { Format.Ledger.Write.style_color=False
1406 , Format.Ledger.Write.style_align=True
1410 { Amount.quantity = Decimal 7 1234567890123456789
1411 , Amount.style = Amount.Style.nil
1412 { Amount.Style.fractioning = Just '.'
1413 , Amount.Style.precision = 7
1414 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1418 "1,2,3,4,5,6,7,89,012.3456789")
1419 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
1420 ((Format.Ledger.Write.show
1421 Format.Ledger.Write.Style
1422 { Format.Ledger.Write.style_color=False
1423 , Format.Ledger.Write.style_align=True
1427 { Amount.quantity = Decimal 12 1234567890123456789
1428 , Amount.style = Amount.Style.nil
1429 { Amount.Style.fractioning = Just '.'
1430 , Amount.Style.precision = 12
1431 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1435 "1234567.890,12,3,4,5,6,7,8,9")
1437 , "amount_length" ~: TestList
1439 ((Amount.Write.amount_length
1444 ((Amount.Write.amount_length
1446 { Amount.style = Amount.Style.nil
1447 { Amount.Style.precision = 2 }
1452 ((Amount.Write.amount_length
1454 { Amount.quantity = Decimal 0 123
1459 ((Amount.Write.amount_length
1461 { Amount.quantity = Decimal 0 (- 123)
1465 , "12.3 @ prec=0" ~:
1466 ((Amount.Write.amount_length
1468 { Amount.quantity = Decimal 1 123
1469 , Amount.style = Amount.Style.nil
1470 { Amount.Style.fractioning = Just '.'
1475 , "12.5 @ prec=0" ~:
1476 ((Amount.Write.amount_length
1478 { Amount.quantity = Decimal 1 125
1479 , Amount.style = Amount.Style.nil
1480 { Amount.Style.fractioning = Just '.'
1485 , "12.3 @ prec=1" ~:
1486 ((Amount.Write.amount_length
1488 { Amount.quantity = Decimal 1 123
1489 , Amount.style = Amount.Style.nil
1490 { Amount.Style.fractioning = Just '.'
1491 , Amount.Style.precision = 1
1496 , "1,234.56 @ prec=2" ~:
1497 ((Amount.Write.amount_length
1499 { Amount.quantity = Decimal 2 123456
1500 , Amount.style = Amount.Style.nil
1501 { Amount.Style.fractioning = Just '.'
1502 , Amount.Style.precision = 2
1503 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1508 , "123,456,789,01,2.3456789 @ prec=7" ~:
1509 ((Amount.Write.amount_length
1511 { Amount.quantity = Decimal 7 1234567890123456789
1512 , Amount.style = Amount.Style.nil
1513 { Amount.Style.fractioning = Just '.'
1514 , Amount.Style.precision = 7
1515 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1520 , "1234567.8,90,123,456,789 @ prec=12" ~:
1521 ((Amount.Write.amount_length
1523 { Amount.quantity = Decimal 12 1234567890123456789
1524 , Amount.style = Amount.Style.nil
1525 { Amount.Style.fractioning = Just '.'
1526 , Amount.Style.precision = 12
1527 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1532 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
1533 ((Amount.Write.amount_length
1535 { Amount.quantity = Decimal 7 1234567890123456789
1536 , Amount.style = Amount.Style.nil
1537 { Amount.Style.fractioning = Just '.'
1538 , Amount.Style.precision = 7
1539 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1544 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
1545 ((Amount.Write.amount_length
1547 { Amount.quantity = Decimal 12 1234567890123456789
1548 , Amount.style = Amount.Style.nil
1549 { Amount.Style.fractioning = Just '.'
1550 , Amount.Style.precision = 12
1551 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1556 , "1000000.000,00,0,0,0,0,0,0,0 @ prec=12" ~:
1557 ((Amount.Write.amount_length
1559 { Amount.quantity = Decimal 12 1000000000000000000
1560 , Amount.style = Amount.Style.nil
1561 { Amount.Style.fractioning = Just '.'
1562 , Amount.Style.precision = 12
1563 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1569 ((Amount.Write.amount_length $
1571 { Amount.quantity = Decimal 0 999
1572 , Amount.style = Amount.Style.nil
1573 { Amount.Style.precision = 0
1578 , "1000 @ prec=0" ~:
1579 ((Amount.Write.amount_length $
1581 { Amount.quantity = Decimal 0 1000
1582 , Amount.style = Amount.Style.nil
1583 { Amount.Style.precision = 0
1588 , "10,00€ @ prec=2" ~:
1589 ((Amount.Write.amount_length $ Amount.eur 10)
1595 , "Date" ~: TestList
1596 [ "Read" ~: TestList
1597 [ "date" ~: TestList
1599 (Data.Either.rights $
1600 [P.runParser_with_Error
1601 (Date.Read.date id Nothing <* P.eof)
1602 () "" ("2000/01/01"::Text)])
1604 [ Time.zonedTimeToUTC $
1607 (Time.fromGregorian 2000 01 01)
1608 (Time.TimeOfDay 0 0 0))
1610 , "2000/01/01 some text" ~:
1611 (Data.Either.rights $
1612 [P.runParser_with_Error
1613 (Date.Read.date id Nothing)
1614 () "" ("2000/01/01 some text"::Text)])
1616 [ Time.zonedTimeToUTC $
1619 (Time.fromGregorian 2000 01 01)
1620 (Time.TimeOfDay 0 0 0))
1622 , "2000/01/01 12:34" ~:
1623 (Data.Either.rights $
1624 [P.runParser_with_Error
1625 (Date.Read.date id Nothing <* P.eof)
1626 () "" ("2000/01/01 12:34"::Text)])
1628 [ Time.zonedTimeToUTC $
1631 (Time.fromGregorian 2000 01 01)
1632 (Time.TimeOfDay 12 34 0))
1634 , "2000/01/01 12:34:56" ~:
1635 (Data.Either.rights $
1636 [P.runParser_with_Error
1637 (Date.Read.date id Nothing <* P.eof)
1638 () "" ("2000/01/01 12:34:56"::Text)])
1640 [ Time.zonedTimeToUTC $
1643 (Time.fromGregorian 2000 01 01)
1644 (Time.TimeOfDay 12 34 56))
1646 , "2000/01/01 12:34 CET" ~:
1647 (Data.Either.rights $
1648 [P.runParser_with_Error
1649 (Date.Read.date id Nothing <* P.eof)
1650 () "" ("2000/01/01 12:34 CET"::Text)])
1652 [ Time.zonedTimeToUTC $
1655 (Time.fromGregorian 2000 01 01)
1656 (Time.TimeOfDay 12 34 0))
1657 (Time.TimeZone 60 True "CET")]
1658 , "2000/01/01 12:34 +0130" ~:
1659 (Data.Either.rights $
1660 [P.runParser_with_Error
1661 (Date.Read.date id Nothing <* P.eof)
1662 () "" ("2000/01/01 12:34 +0130"::Text)])
1664 [ Time.zonedTimeToUTC $
1667 (Time.fromGregorian 2000 01 01)
1668 (Time.TimeOfDay 12 34 0))
1669 (Time.TimeZone 90 False "+0130")]
1670 , "2000/01/01 12:34:56 CET" ~:
1671 (Data.Either.rights $
1672 [P.runParser_with_Error
1673 (Date.Read.date id Nothing <* P.eof)
1674 () "" ("2000/01/01 12:34:56 CET"::Text)])
1676 [ Time.zonedTimeToUTC $
1679 (Time.fromGregorian 2000 01 01)
1680 (Time.TimeOfDay 12 34 56))
1681 (Time.TimeZone 60 True "CET")]
1683 (Data.Either.rights $
1684 [P.runParser_with_Error
1685 (Date.Read.date id Nothing <* P.eof)
1686 () "" ("2001/02/29"::Text)])
1690 (Data.Either.rights $
1691 [P.runParser_with_Error
1692 (Date.Read.date id (Just 2000) <* P.eof)
1693 () "" ("01/01"::Text)])
1695 [ Time.zonedTimeToUTC $
1698 (Time.fromGregorian 2000 01 01)
1699 (Time.TimeOfDay 0 0 0))
1703 , "Write" ~: TestList
1704 [ "date" ~: TestList
1706 ((Format.Ledger.Write.show
1707 Format.Ledger.Write.Style
1708 { Format.Ledger.Write.style_color=False
1709 , Format.Ledger.Write.style_align=True
1715 , "2000/01/01 12:34:51 CET" ~:
1716 (Format.Ledger.Write.show
1717 Format.Ledger.Write.Style
1718 { Format.Ledger.Write.style_color=False
1719 , Format.Ledger.Write.style_align=True
1722 Time.zonedTimeToUTC $
1725 (Time.fromGregorian 2000 01 01)
1726 (Time.TimeOfDay 12 34 51))
1727 (Time.TimeZone 60 False "CET"))
1729 "2000/01/01 11:34:51"
1730 , "2000/01/01 12:34:51 +0100" ~:
1731 (Format.Ledger.Write.show
1732 Format.Ledger.Write.Style
1733 { Format.Ledger.Write.style_color=False
1734 , Format.Ledger.Write.style_align=True
1737 Time.zonedTimeToUTC $
1740 (Time.fromGregorian 2000 01 01)
1741 (Time.TimeOfDay 12 34 51))
1742 (Time.TimeZone 60 False ""))
1744 "2000/01/01 11:34:51"
1745 , "2000/01/01 01:02:03" ~:
1746 (Format.Ledger.Write.show
1747 Format.Ledger.Write.Style
1748 { Format.Ledger.Write.style_color=False
1749 , Format.Ledger.Write.style_align=True
1752 Time.zonedTimeToUTC $
1755 (Time.fromGregorian 2000 01 01)
1756 (Time.TimeOfDay 1 2 3))
1759 "2000/01/01 01:02:03"
1761 (Format.Ledger.Write.show
1762 Format.Ledger.Write.Style
1763 { Format.Ledger.Write.style_color=False
1764 , Format.Ledger.Write.style_align=True
1767 Time.zonedTimeToUTC $
1770 (Time.fromGregorian 0 01 01)
1771 (Time.TimeOfDay 1 2 0))
1776 (Format.Ledger.Write.show
1777 Format.Ledger.Write.Style
1778 { Format.Ledger.Write.style_color=False
1779 , Format.Ledger.Write.style_align=True
1782 Time.zonedTimeToUTC $
1785 (Time.fromGregorian 0 01 01)
1786 (Time.TimeOfDay 1 0 0))
1791 (Format.Ledger.Write.show
1792 Format.Ledger.Write.Style
1793 { Format.Ledger.Write.style_color=False
1794 , Format.Ledger.Write.style_align=True
1797 Time.zonedTimeToUTC $
1800 (Time.fromGregorian 0 01 01)
1801 (Time.TimeOfDay 0 1 0))
1806 (Format.Ledger.Write.show
1807 Format.Ledger.Write.Style
1808 { Format.Ledger.Write.style_color=False
1809 , Format.Ledger.Write.style_align=True
1812 Time.zonedTimeToUTC $
1815 (Time.fromGregorian 0 01 01)
1816 (Time.TimeOfDay 0 0 0))
1823 , "Filter" ~: TestList
1824 [ "test" ~: TestList
1825 [ "Filter_Account" ~: TestList
1828 (Filter.Filter_Account Filter.Eq
1829 [ Filter.Filter_Account_Section_Text
1830 (Filter.Filter_Text_Exact "A")
1832 (("A":|[]::Account))
1835 (Filter.Filter_Account Filter.Eq
1836 [ Filter.Filter_Account_Section_Any
1838 (("A":|[]::Account))
1841 (Filter.Filter_Account Filter.Eq
1842 [ Filter.Filter_Account_Section_Many
1844 (("A":|[]::Account))
1847 (Filter.Filter_Account Filter.Eq
1848 [ Filter.Filter_Account_Section_Many
1849 , Filter.Filter_Account_Section_Text
1850 (Filter.Filter_Text_Exact "A")
1852 (("A":|[]::Account))
1855 (Filter.Filter_Account Filter.Eq
1856 [ Filter.Filter_Account_Section_Text
1857 (Filter.Filter_Text_Exact "A")
1858 , Filter.Filter_Account_Section_Many
1860 (("A":|[]::Account))
1863 (Filter.Filter_Account Filter.Eq
1864 [ Filter.Filter_Account_Section_Text
1865 (Filter.Filter_Text_Exact "A")
1866 , Filter.Filter_Account_Section_Many
1868 (("A":|"B":[]::Account))
1871 (Filter.Filter_Account Filter.Eq
1872 [ Filter.Filter_Account_Section_Text
1873 (Filter.Filter_Text_Exact "A")
1874 , Filter.Filter_Account_Section_Text
1875 (Filter.Filter_Text_Exact "B")
1877 (("A":|"B":[]::Account))
1880 (Filter.Filter_Account Filter.Eq
1881 [ Filter.Filter_Account_Section_Text
1882 (Filter.Filter_Text_Exact "A")
1883 , Filter.Filter_Account_Section_Many
1884 , Filter.Filter_Account_Section_Text
1885 (Filter.Filter_Text_Exact "B")
1887 (("A":|"B":[]::Account))
1890 (Filter.Filter_Account Filter.Eq
1891 [ Filter.Filter_Account_Section_Many
1892 , Filter.Filter_Account_Section_Text
1893 (Filter.Filter_Text_Exact "B")
1894 , Filter.Filter_Account_Section_Many
1896 (("A":|"B":"C":[]::Account))
1899 (Filter.Filter_Account Filter.Eq
1900 [ Filter.Filter_Account_Section_Many
1901 , Filter.Filter_Account_Section_Text
1902 (Filter.Filter_Text_Exact "C")
1904 (("A":|"B":"C":[]::Account))
1905 , "<A:B:C::D A:B" ~?
1907 (Filter.Filter_Account Filter.Lt
1908 [ Filter.Filter_Account_Section_Text
1909 (Filter.Filter_Text_Exact "A")
1910 , Filter.Filter_Account_Section_Text
1911 (Filter.Filter_Text_Exact "B")
1912 , Filter.Filter_Account_Section_Text
1913 (Filter.Filter_Text_Exact "C")
1914 , Filter.Filter_Account_Section_Many
1915 , Filter.Filter_Account_Section_Text
1916 (Filter.Filter_Text_Exact "D")
1918 (("A":|"B":[]::Account))
1919 , ">A:B:C::D A:B:C:CC:CCC:D:E" ~?
1921 (Filter.Filter_Account Filter.Gt
1922 [ Filter.Filter_Account_Section_Text
1923 (Filter.Filter_Text_Exact "A")
1924 , Filter.Filter_Account_Section_Text
1925 (Filter.Filter_Text_Exact "B")
1926 , Filter.Filter_Account_Section_Text
1927 (Filter.Filter_Text_Exact "C")
1928 , Filter.Filter_Account_Section_Many
1929 , Filter.Filter_Account_Section_Text
1930 (Filter.Filter_Text_Exact "D")
1932 (("A":|"B":"C":"CC":"CCC":"D":"E":[]::Account))
1934 , "Filter_Bool" ~: TestList
1937 (Filter.Any::Filter.Filter_Bool Filter.Filter_Account)
1938 (("A":|[]::Account))
1940 , "Filter_Ord" ~: TestList
1943 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer))
1944 (fromJust $ (Lib.Interval.<=..<=) 1 2)
1947 (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer))
1948 (fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
1949 , "not (1 < (0, 2))" ~?
1951 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer))
1952 (fromJust $ (Lib.Interval.<=..<=) 0 2))
1955 , "Read" ~: TestList
1956 [ "filter_account_section" ~: TestList
1958 (Data.Either.rights $
1960 (Filter.Read.filter_account <* P.eof)
1963 [ Filter.Filter_Account Filter.Eq
1964 [ Filter.Filter_Account_Section_Any ]
1967 (Data.Either.rights $
1969 (Filter.Read.filter_account <* P.eof)
1972 [ Filter.Filter_Account Filter.Eq
1973 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ]
1976 (Data.Either.rights $
1978 (Filter.Read.filter_account <* P.eof)
1979 () "" ("AA"::Text)])
1981 [ Filter.Filter_Account Filter.Eq
1982 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "AA") ]
1985 (Data.Either.rights $
1987 (Filter.Read.filter_account <* P.eof)
1988 () "" ("::A"::Text)])
1990 [ Filter.Filter_Account Filter.Eq
1991 [ Filter.Filter_Account_Section_Many
1992 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1996 (Data.Either.rights $
1998 (Filter.Read.filter_account <* P.eof)
1999 () "" (":A"::Text)])
2001 [ Filter.Filter_Account Filter.Eq
2002 [ Filter.Filter_Account_Section_Many
2003 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2007 (Data.Either.rights $
2009 (Filter.Read.filter_account <* P.eof)
2010 () "" ("A:"::Text)])
2012 [ Filter.Filter_Account Filter.Eq
2013 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2014 , Filter.Filter_Account_Section_Many
2018 (Data.Either.rights $
2020 (Filter.Read.filter_account <* P.eof)
2021 () "" ("A::"::Text)])
2023 [ Filter.Filter_Account Filter.Eq
2024 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2025 , Filter.Filter_Account_Section_Many
2029 (Data.Either.rights $
2031 (Filter.Read.filter_account <* P.eof)
2032 () "" ("A:B"::Text)])
2034 [ Filter.Filter_Account Filter.Eq
2035 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2036 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2040 (Data.Either.rights $
2042 (Filter.Read.filter_account <* P.eof)
2043 () "" ("A::B"::Text)])
2045 [ Filter.Filter_Account Filter.Eq
2046 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2047 , Filter.Filter_Account_Section_Many
2048 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2052 (Data.Either.rights $
2054 (Filter.Read.filter_account <* P.eof)
2055 () "" ("A:::B"::Text)])
2057 [ Filter.Filter_Account Filter.Eq
2058 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2059 , Filter.Filter_Account_Section_Many
2060 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2064 (Data.Either.rights $
2066 (Filter.Read.filter_account <* P.char ' ' <* P.eof)
2067 () "" ("A: "::Text)])
2069 [ Filter.Filter_Account Filter.Eq
2070 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2071 , Filter.Filter_Account_Section_Many
2075 (Data.Either.rights $
2077 (Filter.Read.filter_account <* P.eof)
2078 () "" ("<=A:B"::Text)])
2080 [ Filter.Filter_Account Filter.Le
2081 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2082 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2086 (Data.Either.rights $
2088 (Filter.Read.filter_account <* P.eof)
2089 () "" (">=A:B"::Text)])
2091 [ Filter.Filter_Account Filter.Ge
2092 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2093 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2097 (Data.Either.rights $
2099 (Filter.Read.filter_account <* P.eof)
2100 () "" ("<A:B"::Text)])
2102 [ Filter.Filter_Account Filter.Lt
2103 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2104 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2108 (Data.Either.rights $
2110 (Filter.Read.filter_account <* P.eof)
2111 () "" (">A:B"::Text)])
2113 [ Filter.Filter_Account Filter.Gt
2114 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2115 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2119 , "filter_bool" ~: TestList
2121 (Data.Either.rights $
2123 (Filter.Read.filter_bool
2124 [ P.char 'E' >> return (return True) ]
2126 () "" ("( E )"::Text)])
2128 [ Filter.And (Filter.Bool True) Filter.Any
2131 (Data.Either.rights $
2133 (Filter.Read.filter_bool
2134 [ P.char 'E' >> return (return True) ]
2136 () "" ("( ( E ) )"::Text)])
2138 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
2140 , "( E ) & ( E )" ~:
2141 (Data.Either.rights $
2143 (Filter.Read.filter_bool
2144 [ P.char 'E' >> return (return True) ]
2146 () "" ("( E ) & ( E )"::Text)])
2149 (Filter.And (Filter.Bool True) Filter.Any)
2150 (Filter.And (Filter.Bool True) Filter.Any)
2152 , "( E ) + ( E )" ~:
2153 (Data.Either.rights $
2155 (Filter.Read.filter_bool
2156 [ P.char 'E' >> return (return True) ]
2158 () "" ("( E ) + ( E )"::Text)])
2161 (Filter.And (Filter.Bool True) Filter.Any)
2162 (Filter.And (Filter.Bool True) Filter.Any)
2164 , "( E ) - ( E )" ~:
2165 (Data.Either.rights $
2167 (Filter.Read.filter_bool
2168 [ P.char 'E' >> return (return True) ]
2170 () "" ("( E ) - ( E )"::Text)])
2173 (Filter.And (Filter.Bool True) Filter.Any)
2174 (Filter.Not (Filter.And (Filter.Bool True) Filter.Any))
2177 (Data.Either.rights $
2179 (Filter.Read.filter_bool
2180 [ P.char 'E' >> return (return True) ]
2182 () "" ("(- E )"::Text)])
2184 [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any
2189 , "Balance" ~: TestList
2190 [ "balance" ~: TestList
2191 [ "[A+$1] = A+$1 & $+1" ~:
2193 (Format.Ledger.posting ("A":|[]))
2194 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2199 { Balance.balance_by_account =
2200 Lib.TreeMap.from_List const $
2201 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2202 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2203 , Balance.balance_by_unit =
2204 Balance.Balance_by_Unit $
2206 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2208 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2209 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2214 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
2218 [ (Format.Ledger.posting ("A":|[]))
2219 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2221 , (Format.Ledger.posting ("A":|[]))
2222 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2227 { Balance.balance_by_account =
2228 Lib.TreeMap.from_List const $
2230 , Balance.Account_Sum $
2231 Data.Map.fromListWith const $
2232 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2238 , Balance.balance_by_unit =
2239 Balance.Balance_by_Unit $
2241 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2243 { Balance.unit_sum_amount = Amount.Sum_Both
2246 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2251 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
2255 [ (Format.Ledger.posting ("A":|[]))
2256 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2258 , (Format.Ledger.posting ("A":|[]))
2259 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ]
2264 { Balance.balance_by_account =
2265 Lib.TreeMap.from_List const $
2266 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2267 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
2268 , Balance.balance_by_unit =
2269 Balance.Balance_by_Unit $
2271 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2273 { Balance.unit_sum_amount = Amount.Sum_Positive (Amount.usd $ 1)
2274 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2278 { Balance.unit_sum_amount = Amount.Sum_Negative (Amount.eur $ -1)
2279 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2284 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
2288 [ (Format.Ledger.posting ("A":|[]))
2289 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2291 , (Format.Ledger.posting ("B":|[]))
2292 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2297 { Balance.balance_by_account =
2298 Lib.TreeMap.from_List const $
2299 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2300 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2301 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
2303 , Balance.balance_by_unit =
2304 Balance.Balance_by_Unit $
2306 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2308 { Balance.unit_sum_amount = Amount.Sum_Both
2311 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2320 [ (Format.Ledger.posting ("A":|[]))
2321 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2323 , (Format.Ledger.posting ("B":|[]))
2324 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2329 { Balance.balance_by_account =
2330 Lib.TreeMap.from_List const $
2331 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2332 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2333 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
2335 , Balance.balance_by_unit =
2336 Balance.Balance_by_Unit $
2338 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2340 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2341 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2346 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
2350 [ (Format.Ledger.posting ("A":|[]))
2351 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
2353 , (Format.Ledger.posting ("A":|[]))
2354 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
2359 { Balance.balance_by_account =
2360 Lib.TreeMap.from_List const $
2362 , Balance.Account_Sum $
2363 Data.Map.fromListWith const $
2364 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2365 [ Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2366 , Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2370 , Balance.balance_by_unit =
2371 Balance.Balance_by_Unit $
2373 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2375 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2376 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2380 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2381 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2386 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
2390 [ (Format.Ledger.posting ("A":|[]))
2391 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
2393 , (Format.Ledger.posting ("B":|[]))
2394 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
2399 { Balance.balance_by_account =
2400 Lib.TreeMap.from_List const $
2401 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2402 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
2403 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
2405 , Balance.balance_by_unit =
2406 Balance.Balance_by_Unit $
2408 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2410 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2411 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2415 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2416 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2420 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.gbp $ -3) (Amount.gbp $ 3)
2421 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2427 , "union" ~: TestList
2428 [ "empty empty = empty" ~:
2429 Balance.union Balance.empty Balance.empty
2431 (Balance.empty::Balance.Balance Amount)
2432 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
2435 { Balance.balance_by_account =
2436 Lib.TreeMap.from_List const $
2437 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2438 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2439 , Balance.balance_by_unit =
2440 Balance.Balance_by_Unit $
2442 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2444 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2445 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2451 { Balance.balance_by_account =
2452 Lib.TreeMap.from_List const $
2453 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2454 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2455 , Balance.balance_by_unit =
2456 Balance.Balance_by_Unit $
2458 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2460 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2461 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2468 { Balance.balance_by_account =
2469 Lib.TreeMap.from_List const $
2470 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2471 [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
2472 , Balance.balance_by_unit =
2473 Balance.Balance_by_Unit $
2475 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2477 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2478 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2483 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
2486 { Balance.balance_by_account =
2487 Lib.TreeMap.from_List const $
2488 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2489 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2490 , Balance.balance_by_unit =
2491 Balance.Balance_by_Unit $
2493 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2495 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2496 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2502 { Balance.balance_by_account =
2503 Lib.TreeMap.from_List const $
2504 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2505 [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2506 , Balance.balance_by_unit =
2507 Balance.Balance_by_Unit $
2509 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2511 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2512 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2519 { Balance.balance_by_account =
2520 Lib.TreeMap.from_List const $
2521 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2522 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2523 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2524 , Balance.balance_by_unit =
2525 Balance.Balance_by_Unit $
2527 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2529 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2530 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2535 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
2538 { Balance.balance_by_account =
2539 Lib.TreeMap.from_List const $
2540 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2541 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2542 , Balance.balance_by_unit =
2543 Balance.Balance_by_Unit $
2545 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2547 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2548 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2554 { Balance.balance_by_account =
2555 Lib.TreeMap.from_List const $
2556 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2557 [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
2558 , Balance.balance_by_unit =
2559 Balance.Balance_by_Unit $
2561 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2563 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2564 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2571 { Balance.balance_by_account =
2572 Lib.TreeMap.from_List const $
2573 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2574 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2575 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
2576 , Balance.balance_by_unit =
2577 Balance.Balance_by_Unit $
2579 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2581 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2582 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2586 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2587 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2593 , "expanded" ~: TestList
2598 (Lib.TreeMap.empty::Balance.Expanded Amount)
2601 (Lib.TreeMap.from_List const $
2602 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2603 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
2605 (Lib.TreeMap.from_List const $
2606 [ ("A":|[], Balance.Account_Sum_Expanded
2607 { Balance.inclusive =
2608 Balance.Account_Sum $
2609 Data.Map.map Amount.sum $
2610 Amount.from_List [ Amount.usd $ 1 ]
2611 , Balance.exclusive =
2612 Balance.Account_Sum $
2613 Data.Map.map Amount.sum $
2614 Amount.from_List [ Amount.usd $ 1 ]
2617 , "A/A+$1 = A+$1 A/A+$1" ~:
2619 (Lib.TreeMap.from_List const $
2620 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2621 [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
2623 (Lib.TreeMap.from_List const
2624 [ ("A":|[], Balance.Account_Sum_Expanded
2625 { Balance.inclusive =
2626 Balance.Account_Sum $
2627 Data.Map.map Amount.sum $
2628 Amount.from_List [ Amount.usd $ 1 ]
2629 , Balance.exclusive =
2630 Balance.Account_Sum $
2631 Data.Map.map Amount.sum $
2634 , ("A":|["A"], Balance.Account_Sum_Expanded
2635 { Balance.inclusive =
2636 Balance.Account_Sum $
2637 Data.Map.map Amount.sum $
2638 Amount.from_List [ Amount.usd $ 1 ]
2639 , Balance.exclusive =
2640 Balance.Account_Sum $
2641 Data.Map.map Amount.sum $
2642 Amount.from_List [ Amount.usd $ 1 ]
2645 , "A/B+$1 = A+$1 A/B+$1" ~:
2647 (Lib.TreeMap.from_List const $
2648 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2649 [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
2651 (Lib.TreeMap.from_List const
2652 [ ("A":|[], Balance.Account_Sum_Expanded
2653 { Balance.inclusive =
2654 Balance.Account_Sum $
2655 Data.Map.map Amount.sum $
2656 Amount.from_List [ Amount.usd $ 1 ]
2657 , Balance.exclusive =
2658 Balance.Account_Sum $
2659 Data.Map.map Amount.sum $
2662 , ("A":|["B"], Balance.Account_Sum_Expanded
2663 { Balance.inclusive =
2664 Balance.Account_Sum $
2665 Data.Map.map Amount.sum $
2666 Amount.from_List [ Amount.usd $ 1 ]
2667 , Balance.exclusive =
2668 Balance.Account_Sum $
2669 Data.Map.map Amount.sum $
2670 Amount.from_List [ Amount.usd $ 1 ]
2673 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
2675 (Lib.TreeMap.from_List const $
2676 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2677 [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
2679 (Lib.TreeMap.from_List const $
2680 [ ("A":|[], Balance.Account_Sum_Expanded
2681 { Balance.inclusive =
2682 Balance.Account_Sum $
2683 Data.Map.map Amount.sum $
2684 Amount.from_List [ Amount.usd $ 1 ]
2685 , Balance.exclusive =
2686 Balance.Account_Sum $
2687 Data.Map.map Amount.sum $
2690 , ("A":|["B"], Balance.Account_Sum_Expanded
2691 { Balance.inclusive =
2692 Balance.Account_Sum $
2693 Data.Map.map Amount.sum $
2694 Amount.from_List [ Amount.usd $ 1 ]
2695 , Balance.exclusive =
2696 Balance.Account_Sum $
2697 Data.Map.map Amount.sum $
2700 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
2701 { Balance.inclusive =
2702 Balance.Account_Sum $
2703 Data.Map.map Amount.sum $
2704 Amount.from_List [ Amount.usd $ 1 ]
2705 , Balance.exclusive =
2706 Balance.Account_Sum $
2707 Data.Map.map Amount.sum $
2708 Amount.from_List [ Amount.usd $ 1 ]
2711 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
2713 (Lib.TreeMap.from_List const $
2714 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2715 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2716 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2719 (Lib.TreeMap.from_List const
2720 [ ("A":|[], Balance.Account_Sum_Expanded
2721 { Balance.inclusive =
2722 Balance.Account_Sum $
2723 Data.Map.map Amount.sum $
2724 Amount.from_List [ Amount.usd $ 2 ]
2725 , Balance.exclusive =
2726 Balance.Account_Sum $
2727 Data.Map.map Amount.sum $
2728 Amount.from_List [ Amount.usd $ 1 ]
2730 , ("A":|["B"], Balance.Account_Sum_Expanded
2731 { Balance.inclusive =
2732 Balance.Account_Sum $
2733 Data.Map.map Amount.sum $
2734 Amount.from_List [ Amount.usd $ 1 ]
2735 , Balance.exclusive =
2736 Balance.Account_Sum $
2737 Data.Map.map Amount.sum $
2738 Amount.from_List [ Amount.usd $ 1 ]
2741 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
2743 (Lib.TreeMap.from_List const $
2744 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2745 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2746 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2747 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
2750 (Lib.TreeMap.from_List const
2751 [ ("A":|[], Balance.Account_Sum_Expanded
2752 { Balance.inclusive =
2753 Balance.Account_Sum $
2754 Data.Map.map Amount.sum $
2755 Amount.from_List [ Amount.usd $ 3 ]
2756 , Balance.exclusive =
2757 Balance.Account_Sum $
2758 Data.Map.map Amount.sum $
2759 Amount.from_List [ Amount.usd $ 1 ]
2761 , ("A":|["B"], Balance.Account_Sum_Expanded
2762 { Balance.inclusive =
2763 Balance.Account_Sum $
2764 Data.Map.map Amount.sum $
2765 Amount.from_List [ Amount.usd $ 2 ]
2766 , Balance.exclusive =
2767 Balance.Account_Sum $
2768 Data.Map.map Amount.sum $
2769 Amount.from_List [ Amount.usd $ 1 ]
2771 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
2772 { Balance.inclusive =
2773 Balance.Account_Sum $
2774 Data.Map.map Amount.sum $
2775 Amount.from_List [ Amount.usd $ 1 ]
2776 , Balance.exclusive =
2777 Balance.Account_Sum $
2778 Data.Map.map Amount.sum $
2779 Amount.from_List [ Amount.usd $ 1 ]
2782 , "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" ~:
2784 (Lib.TreeMap.from_List const $
2785 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2786 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2787 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2788 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
2789 , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
2792 (Lib.TreeMap.from_List const
2793 [ ("A":|[], Balance.Account_Sum_Expanded
2794 { Balance.inclusive =
2795 Balance.Account_Sum $
2796 Data.Map.map Amount.sum $
2797 Amount.from_List [ Amount.usd $ 4 ]
2798 , Balance.exclusive =
2799 Balance.Account_Sum $
2800 Data.Map.map Amount.sum $
2801 Amount.from_List [ Amount.usd $ 1 ]
2803 , ("A":|["B"], Balance.Account_Sum_Expanded
2804 { Balance.inclusive =
2805 Balance.Account_Sum $
2806 Data.Map.map Amount.sum $
2807 Amount.from_List [ Amount.usd $ 3 ]
2808 , Balance.exclusive =
2809 Balance.Account_Sum $
2810 Data.Map.map Amount.sum $
2811 Amount.from_List [ Amount.usd $ 1 ]
2813 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
2814 { Balance.inclusive =
2815 Balance.Account_Sum $
2816 Data.Map.map Amount.sum $
2817 Amount.from_List [ Amount.usd $ 2 ]
2818 , Balance.exclusive =
2819 Balance.Account_Sum $
2820 Data.Map.map Amount.sum $
2821 Amount.from_List [ Amount.usd $ 1 ]
2823 , ("A":|["B", "C", "D"], Balance.Account_Sum_Expanded
2824 { Balance.inclusive =
2825 Balance.Account_Sum $
2826 Data.Map.map Amount.sum $
2827 Amount.from_List [ Amount.usd $ 1 ]
2828 , Balance.exclusive =
2829 Balance.Account_Sum $
2830 Data.Map.map Amount.sum $
2831 Amount.from_List [ Amount.usd $ 1 ]
2834 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
2836 (Lib.TreeMap.from_List const $
2837 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2838 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2839 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2840 , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
2841 , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2844 (Lib.TreeMap.from_List const
2845 [ ("A":|[], Balance.Account_Sum_Expanded
2846 { Balance.inclusive =
2847 Balance.Account_Sum $
2848 Data.Map.map Amount.sum $
2849 Amount.from_List [ Amount.usd $ 3 ]
2850 , Balance.exclusive =
2851 Balance.Account_Sum $
2852 Data.Map.map Amount.sum $
2853 Amount.from_List [ Amount.usd $ 1 ]
2855 , ("A":|["B"], Balance.Account_Sum_Expanded
2856 { Balance.inclusive =
2857 Balance.Account_Sum $
2858 Data.Map.map Amount.sum $
2859 Amount.from_List [ Amount.usd $ 1 ]
2860 , Balance.exclusive =
2861 Balance.Account_Sum $
2862 Data.Map.map Amount.sum $
2863 Amount.from_List [ Amount.usd $ 1 ]
2865 , ("A":|["BB"], Balance.Account_Sum_Expanded
2866 { Balance.inclusive =
2867 Balance.Account_Sum $
2868 Data.Map.map Amount.sum $
2869 Amount.from_List [ Amount.usd $ 1 ]
2870 , Balance.exclusive =
2871 Balance.Account_Sum $
2872 Data.Map.map Amount.sum $
2873 Amount.from_List [ Amount.usd $ 1 ]
2875 , ("AA":|[], Balance.Account_Sum_Expanded
2876 { Balance.inclusive =
2877 Balance.Account_Sum $
2878 Data.Map.map Amount.sum $
2879 Amount.from_List [ Amount.usd $ 1 ]
2880 , Balance.exclusive =
2881 Balance.Account_Sum $
2882 Data.Map.map Amount.sum $
2885 , ("AA":|["B"], Balance.Account_Sum_Expanded
2886 { Balance.inclusive =
2887 Balance.Account_Sum $
2888 Data.Map.map Amount.sum $
2889 Amount.from_List [ Amount.usd $ 1 ]
2890 , Balance.exclusive =
2891 Balance.Account_Sum $
2892 Data.Map.map Amount.sum $
2893 Amount.from_List [ Amount.usd $ 1 ]
2897 , "deviation" ~: TestList
2899 (Balance.deviation $
2901 { Balance.balance_by_account =
2902 Lib.TreeMap.from_List const $
2903 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2904 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2905 , ("B":|[], Amount.from_List [])
2907 , Balance.balance_by_unit =
2908 Balance.Balance_by_Unit $
2910 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2912 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2913 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2919 (Balance.Deviation $
2920 Balance.Balance_by_Unit $
2922 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2924 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2925 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2929 , "{A+$1 B+$1, $2}" ~:
2930 (Balance.deviation $
2932 { Balance.balance_by_account =
2933 Lib.TreeMap.from_List const $
2934 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2935 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2936 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
2938 , Balance.balance_by_unit =
2939 Balance.Balance_by_Unit $
2941 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2943 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2944 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2952 (Balance.Deviation $
2953 Balance.Balance_by_Unit $
2955 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2957 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2958 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2964 , "is_equilibrium_inferrable" ~: TestList
2965 [ "nil" ~: TestCase $
2967 Balance.is_equilibrium_inferrable $
2969 (Balance.empty::Balance.Balance Amount.Amount)
2970 , "{A+$0, $+0}" ~: TestCase $
2972 Balance.is_equilibrium_inferrable $
2975 { Balance.balance_by_account =
2976 Lib.TreeMap.from_List const $
2977 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2978 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
2980 , Balance.balance_by_unit =
2981 Balance.Balance_by_Unit $
2983 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2985 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
2986 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2991 , "{A+$1, $+1}" ~: TestCase $
2993 Balance.is_equilibrium_inferrable $
2996 { Balance.balance_by_account =
2997 Lib.TreeMap.from_List const $
2998 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2999 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3001 , Balance.balance_by_unit =
3002 Balance.Balance_by_Unit $
3004 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3006 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3007 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3012 , "{A+$0+€0, $0 €+0}" ~: TestCase $
3014 Balance.is_equilibrium_inferrable $
3017 { Balance.balance_by_account =
3018 Lib.TreeMap.from_List const $
3019 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3020 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
3022 , Balance.balance_by_unit =
3023 Balance.Balance_by_Unit $
3025 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3027 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3028 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3032 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3033 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3038 , "{A+$1, B-$1, $+0}" ~: TestCase $
3040 Balance.is_equilibrium_inferrable $
3043 { Balance.balance_by_account =
3044 Lib.TreeMap.from_List const $
3045 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3046 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3047 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
3049 , Balance.balance_by_unit =
3050 Balance.Balance_by_Unit $
3052 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3054 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3055 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3060 , "{A+$1 B, $+1}" ~: TestCase $
3062 Balance.is_equilibrium_inferrable $
3065 { Balance.balance_by_account =
3066 Lib.TreeMap.from_List const $
3067 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3068 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3069 , ("B":|[], Amount.from_List [])
3071 , Balance.balance_by_unit =
3072 Balance.Balance_by_Unit $
3074 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3076 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3077 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3082 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
3084 Balance.is_equilibrium_inferrable $
3087 { Balance.balance_by_account =
3088 Lib.TreeMap.from_List const $
3089 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3090 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3091 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
3093 , Balance.balance_by_unit =
3094 Balance.Balance_by_Unit $
3096 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3098 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3099 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3103 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3104 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3109 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
3111 Balance.is_equilibrium_inferrable $
3114 { Balance.balance_by_account =
3115 Lib.TreeMap.from_List const $
3116 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3117 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3118 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
3120 , Balance.balance_by_unit =
3121 Balance.Balance_by_Unit $
3123 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3125 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3126 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3130 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3131 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3136 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
3138 Balance.is_equilibrium_inferrable $
3141 { Balance.balance_by_account =
3142 Lib.TreeMap.from_List const $
3143 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3144 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
3145 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
3147 , Balance.balance_by_unit =
3148 Balance.Balance_by_Unit $
3150 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3152 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3153 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3157 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3158 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3162 { Balance.unit_sum_amount = Amount.sum $ Amount.gbp $ 0
3163 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3169 , "infer_equilibrium" ~: TestList
3171 (snd $ Balance.infer_equilibrium $
3172 Format.Ledger.posting_by_Account
3173 [ (Format.Ledger.posting ("A":|[]))
3174 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3175 , (Format.Ledger.posting ("B":|[]))
3176 { Format.Ledger.posting_amounts=Amount.from_List [] }
3180 Format.Ledger.posting_by_Account
3181 [ (Format.Ledger.posting ("A":|[]))
3182 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3183 , (Format.Ledger.posting ("B":|[]))
3184 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] }
3187 (snd $ Balance.infer_equilibrium $
3188 Format.Ledger.posting_by_Account
3189 [ (Format.Ledger.posting ("A":|[]))
3190 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3191 , (Format.Ledger.posting ("B":|[]))
3192 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] }
3196 Format.Ledger.posting_by_Account
3197 [ (Format.Ledger.posting ("A":|[]))
3198 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1] }
3199 , (Format.Ledger.posting ("B":|[]))
3200 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1, Amount.usd $ -1 ] }
3203 (snd $ Balance.infer_equilibrium $
3204 Format.Ledger.posting_by_Account
3205 [ (Format.Ledger.posting ("A":|[]))
3206 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3207 , (Format.Ledger.posting ("B":|[]))
3208 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3213 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3214 , Balance.unit_sum_accounts = Data.Map.fromList []}
3216 , "{A+$1 B-$1 B-1€}" ~:
3217 (snd $ Balance.infer_equilibrium $
3218 Format.Ledger.posting_by_Account
3219 [ (Format.Ledger.posting ("A":|[]))
3220 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3221 , (Format.Ledger.posting ("B":|[]))
3222 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
3226 Format.Ledger.posting_by_Account
3227 [ (Format.Ledger.posting ("A":|[]))
3228 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1 ] }
3229 , (Format.Ledger.posting ("B":|[]))
3230 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
3234 , "Format" ~: TestList
3235 [ "Ledger" ~: TestList
3236 [ "Read" ~: TestList
3237 [ "account_name" ~: TestList
3239 (Data.Either.rights $
3241 (Format.Ledger.Read.account_name <* P.eof)
3246 (Data.Either.rights $
3248 (Format.Ledger.Read.account_name <* P.eof)
3253 (Data.Either.rights $
3255 (Format.Ledger.Read.account_name <* P.eof)
3256 () "" ("AA"::Text)])
3260 (Data.Either.rights $
3262 (Format.Ledger.Read.account_name <* P.eof)
3267 (Data.Either.rights $
3269 (Format.Ledger.Read.account_name <* P.eof)
3274 (Data.Either.rights $
3276 (Format.Ledger.Read.account_name <* P.eof)
3277 () "" ("A:"::Text)])
3281 (Data.Either.rights $
3283 (Format.Ledger.Read.account_name <* P.eof)
3284 () "" (":A"::Text)])
3288 (Data.Either.rights $
3290 (Format.Ledger.Read.account_name <* P.eof)
3291 () "" ("A "::Text)])
3295 (Data.Either.rights $
3297 (Format.Ledger.Read.account_name)
3298 () "" ("A "::Text)])
3302 (Data.Either.rights $
3304 (Format.Ledger.Read.account_name <* P.eof)
3305 () "" ("A A"::Text)])
3309 (Data.Either.rights $
3311 (Format.Ledger.Read.account_name <* P.eof)
3312 () "" ("A "::Text)])
3316 (Data.Either.rights $
3318 (Format.Ledger.Read.account_name <* P.eof)
3319 () "" ("A \n"::Text)])
3323 (Data.Either.rights $
3325 (Format.Ledger.Read.account_name <* P.eof)
3326 () "" ("(A)A"::Text)])
3330 (Data.Either.rights $
3332 (Format.Ledger.Read.account_name <* P.eof)
3333 () "" ("( )A"::Text)])
3337 (Data.Either.rights $
3339 (Format.Ledger.Read.account_name <* P.eof)
3340 () "" ("(A) A"::Text)])
3344 (Data.Either.rights $
3346 (Format.Ledger.Read.account_name <* P.eof)
3347 () "" ("[ ]A"::Text)])
3351 (Data.Either.rights $
3353 (Format.Ledger.Read.account_name <* P.eof)
3354 () "" ("(A) "::Text)])
3358 (Data.Either.rights $
3360 (Format.Ledger.Read.account_name <* P.eof)
3361 () "" ("(A)"::Text)])
3365 (Data.Either.rights $
3367 (Format.Ledger.Read.account_name <* P.eof)
3368 () "" ("A(A)"::Text)])
3372 (Data.Either.rights $
3374 (Format.Ledger.Read.account_name <* P.eof)
3375 () "" ("[A]A"::Text)])
3379 (Data.Either.rights $
3381 (Format.Ledger.Read.account_name <* P.eof)
3382 () "" ("[A] A"::Text)])
3386 (Data.Either.rights $
3388 (Format.Ledger.Read.account_name <* P.eof)
3389 () "" ("[A] "::Text)])
3393 (Data.Either.rights $
3395 (Format.Ledger.Read.account_name <* P.eof)
3396 () "" ("[A]"::Text)])
3400 , "account" ~: TestList
3402 (Data.Either.rights $
3404 (Format.Ledger.Read.account <* P.eof)
3409 (Data.Either.rights $
3411 (Format.Ledger.Read.account <* P.eof)
3416 (Data.Either.rights $
3418 (Format.Ledger.Read.account <* P.eof)
3419 () "" ("A:"::Text)])
3423 (Data.Either.rights $
3425 (Format.Ledger.Read.account <* P.eof)
3426 () "" (":A"::Text)])
3430 (Data.Either.rights $
3432 (Format.Ledger.Read.account <* P.eof)
3433 () "" ("A "::Text)])
3437 (Data.Either.rights $
3439 (Format.Ledger.Read.account <* P.eof)
3440 () "" (" A"::Text)])
3444 (Data.Either.rights $
3446 (Format.Ledger.Read.account <* P.eof)
3447 () "" ("A:B"::Text)])
3451 (Data.Either.rights $
3453 (Format.Ledger.Read.account <* P.eof)
3454 () "" ("A:B:C"::Text)])
3457 , "\"Aa:Bbb:Cccc\"" ~:
3458 (Data.Either.rights $
3460 (Format.Ledger.Read.account <* P.eof)
3461 () "" ("Aa:Bbb:Cccc"::Text)])
3463 ["Aa":|["Bbb", "Cccc"]]
3464 , "\"A a : B b b : C c c c\"" ~:
3465 (Data.Either.rights $
3467 (Format.Ledger.Read.account <* P.eof)
3468 () "" ("A a : B b b : C c c c"::Text)])
3470 ["A a ":|[" B b b ", " C c c c"]]
3472 (Data.Either.rights $
3474 (Format.Ledger.Read.account <* P.eof)
3475 () "" ("A: :C"::Text)])
3479 (Data.Either.rights $
3481 (Format.Ledger.Read.account <* P.eof)
3482 () "" ("A::C"::Text)])
3486 (Data.Either.rights $
3488 (Format.Ledger.Read.account <* P.eof)
3489 () "" ("A:B:(C)"::Text)])
3493 , "posting_type" ~: TestList
3495 Format.Ledger.Read.posting_type
3498 (Format.Ledger.Posting_Type_Regular, "A":|[])
3500 Format.Ledger.Read.posting_type
3503 (Format.Ledger.Posting_Type_Regular, "(":|[])
3505 Format.Ledger.Read.posting_type
3508 (Format.Ledger.Posting_Type_Regular, ")":|[])
3510 Format.Ledger.Read.posting_type
3513 (Format.Ledger.Posting_Type_Regular, "()":|[])
3515 Format.Ledger.Read.posting_type
3518 (Format.Ledger.Posting_Type_Regular, "( )":|[])
3520 Format.Ledger.Read.posting_type
3523 (Format.Ledger.Posting_Type_Virtual, "A":|[])
3525 Format.Ledger.Read.posting_type
3528 (Format.Ledger.Posting_Type_Virtual, "A":|["B", "C"])
3530 Format.Ledger.Read.posting_type
3533 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
3535 Format.Ledger.Read.posting_type
3538 (Format.Ledger.Posting_Type_Regular, "(A)":|["B", "C"])
3540 Format.Ledger.Read.posting_type
3543 (Format.Ledger.Posting_Type_Regular, "A":|["(B)", "C"])
3545 Format.Ledger.Read.posting_type
3548 (Format.Ledger.Posting_Type_Regular, "A":|["B", "(C)"])
3550 Format.Ledger.Read.posting_type
3553 (Format.Ledger.Posting_Type_Regular, "[":|[])
3555 Format.Ledger.Read.posting_type
3558 (Format.Ledger.Posting_Type_Regular, "]":|[])
3560 Format.Ledger.Read.posting_type
3563 (Format.Ledger.Posting_Type_Regular, "[]":|[])
3565 Format.Ledger.Read.posting_type
3568 (Format.Ledger.Posting_Type_Regular, "[ ]":|[])
3570 Format.Ledger.Read.posting_type
3573 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|[])
3575 Format.Ledger.Read.posting_type
3578 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|["B", "C"])
3580 Format.Ledger.Read.posting_type
3583 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
3585 Format.Ledger.Read.posting_type
3588 (Format.Ledger.Posting_Type_Regular, "[A]":|["B", "C"])
3590 Format.Ledger.Read.posting_type
3593 (Format.Ledger.Posting_Type_Regular, "A":|["[B]", "C"])
3595 Format.Ledger.Read.posting_type
3598 (Format.Ledger.Posting_Type_Regular, "A":|["B", "[C]"])
3600 , "comment" ~: TestList
3601 [ "; some comment = Right \" some comment\"" ~:
3602 (Data.Either.rights $
3604 (Format.Ledger.Read.comment <* P.eof)
3605 () "" ("; some comment"::Text)])
3608 , "; some comment \\n = Right \" some comment \"" ~:
3609 (Data.Either.rights $
3611 (Format.Ledger.Read.comment <* P.newline <* P.eof)
3612 () "" ("; some comment \n"::Text)])
3614 [ " some comment " ]
3615 , "; some comment \\r\\n = Right \" some comment \"" ~:
3616 (Data.Either.rights $
3618 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
3619 () "" ("; some comment \r\n"::Text)])
3621 [ " some comment " ]
3623 , "comments" ~: TestList
3624 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
3625 (Data.Either.rights $
3627 (Format.Ledger.Read.comments <* P.eof)
3628 () "" ("; some comment\n ; some other comment"::Text)])
3630 [ [" some comment", " some other comment"] ]
3631 , "; some comment \\n = Right \" some comment \"" ~:
3632 (Data.Either.rights $
3634 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
3635 () "" ("; some comment \n"::Text)])
3637 [ [" some comment "] ]
3639 , "tag_value" ~: TestList
3641 (Data.Either.rights $
3643 (Format.Ledger.Read.tag_value <* P.eof)
3648 (Data.Either.rights $
3650 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
3651 () "" (",\n"::Text)])
3655 (Data.Either.rights $
3657 (Format.Ledger.Read.tag_value <* P.eof)
3658 () "" (",x"::Text)])
3662 (Data.Either.rights $
3664 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
3665 () "" (",x:"::Text)])
3669 (Data.Either.rights $
3671 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
3672 () "" ("v, v, n:"::Text)])
3678 (Data.Either.rights $
3680 (Format.Ledger.Read.tag <* P.eof)
3681 () "" ("Name:"::Text)])
3685 (Data.Either.rights $
3687 (Format.Ledger.Read.tag <* P.eof)
3688 () "" ("Name:Value"::Text)])
3691 , "Name:Value\\n" ~:
3692 (Data.Either.rights $
3694 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
3695 () "" ("Name:Value\n"::Text)])
3699 (Data.Either.rights $
3701 (Format.Ledger.Read.tag <* P.eof)
3702 () "" ("Name:Val ue"::Text)])
3704 [("Name", "Val ue")]
3706 (Data.Either.rights $
3708 (Format.Ledger.Read.tag <* P.eof)
3709 () "" ("Name:,"::Text)])
3713 (Data.Either.rights $
3715 (Format.Ledger.Read.tag <* P.eof)
3716 () "" ("Name:Val,ue"::Text)])
3718 [("Name", "Val,ue")]
3720 (Data.Either.rights $
3722 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
3723 () "" ("Name:Val,ue:"::Text)])
3727 , "tags" ~: TestList
3729 (Data.Either.rights $
3731 (Format.Ledger.Read.tags <* P.eof)
3732 () "" ("Name:"::Text)])
3739 (Data.Either.rights $
3741 (Format.Ledger.Read.tags <* P.eof)
3742 () "" ("Name:,"::Text)])
3749 (Data.Either.rights $
3751 (Format.Ledger.Read.tags <* P.eof)
3752 () "" ("Name:,Name:"::Text)])
3755 [ ("Name", ["", ""])
3759 (Data.Either.rights $
3761 (Format.Ledger.Read.tags <* P.eof)
3762 () "" ("Name:,Name2:"::Text)])
3769 , "Name: , Name2:" ~:
3770 (Data.Either.rights $
3772 (Format.Ledger.Read.tags <* P.eof)
3773 () "" ("Name: , Name2:"::Text)])
3780 , "Name:,Name2:,Name3:" ~:
3781 (Data.Either.rights $
3783 (Format.Ledger.Read.tags <* P.eof)
3784 () "" ("Name:,Name2:,Name3:"::Text)])
3792 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
3793 (Data.Either.rights $
3795 (Format.Ledger.Read.tags <* P.eof)
3796 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
3799 [ ("Name", ["Val ue"])
3800 , ("Name2", ["V a l u e"])
3801 , ("Name3", ["V al ue"])
3805 , "posting" ~: TestList
3806 [ " A:B:C = Right A:B:C" ~:
3807 (Data.Either.rights $
3808 [P.runParser_with_Error
3809 (Format.Ledger.Read.posting <* P.eof)
3810 ( Format.Ledger.Read.context () Format.Ledger.journal
3811 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3812 "" (" A:B:C"::Text)])
3814 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
3815 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3817 , Format.Ledger.Posting_Type_Regular
3820 , " !A:B:C = Right !A:B:C" ~:
3821 (Data.List.map fst $
3822 Data.Either.rights $
3823 [P.runParser_with_Error
3824 (Format.Ledger.Read.posting <* P.eof)
3825 ( Format.Ledger.Read.context () Format.Ledger.journal
3826 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3827 "" (" !A:B:C"::Text)])
3829 [ (Format.Ledger.posting ("A":|["B", "C"]))
3830 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3831 , Format.Ledger.posting_status = True
3834 , " *A:B:C = Right *A:B:C" ~:
3835 (Data.List.map fst $
3836 Data.Either.rights $
3837 [P.runParser_with_Error
3838 (Format.Ledger.Read.posting <* P.eof)
3839 ( Format.Ledger.Read.context () Format.Ledger.journal
3840 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3841 "" (" *A:B:C"::Text)])
3843 [ (Format.Ledger.posting ("A":|["B", "C"]))
3844 { Format.Ledger.posting_amounts = Data.Map.fromList []
3845 , Format.Ledger.posting_comments = []
3846 , Format.Ledger.posting_dates = []
3847 , Format.Ledger.posting_status = True
3848 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3849 , Format.Ledger.posting_tags = Data.Map.fromList []
3852 , " A:B:C $1 = Right A:B:C $1" ~:
3853 (Data.List.map fst $
3854 Data.Either.rights $
3855 [P.runParser_with_Error
3856 (Format.Ledger.Read.posting <* P.eof)
3857 ( Format.Ledger.Read.context () Format.Ledger.journal
3858 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3859 "" (" A:B:C $1"::Text)])
3861 [ (Format.Ledger.posting ("A":|["B","C $1"]))
3862 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3865 , " A:B:C $1 = Right A:B:C $1" ~:
3866 (Data.List.map fst $
3867 Data.Either.rights $
3868 [P.runParser_with_Error
3869 (Format.Ledger.Read.posting <* P.eof)
3870 ( Format.Ledger.Read.context () Format.Ledger.journal
3871 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3872 "" (" A:B:C $1"::Text)])
3874 [ (Format.Ledger.posting ("A":|["B", "C"]))
3875 { Format.Ledger.posting_amounts = Data.Map.fromList
3877 { Amount.quantity = 1
3878 , Amount.style = Amount.Style.nil
3879 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3880 , Amount.Style.unit_spaced = Just False
3885 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3888 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
3889 (Data.List.map fst $
3890 Data.Either.rights $
3891 [P.runParser_with_Error
3892 (Format.Ledger.Read.posting <* P.eof)
3893 ( Format.Ledger.Read.context () Format.Ledger.journal
3894 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3895 "" (" A:B:C $1 + 1€"::Text)])
3897 [ (Format.Ledger.posting ("A":|["B", "C"]))
3898 { Format.Ledger.posting_amounts = Data.Map.fromList
3900 { Amount.quantity = 1
3901 , Amount.style = Amount.Style.nil
3902 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3903 , Amount.Style.unit_spaced = Just False
3908 { Amount.quantity = 1
3909 , Amount.style = Amount.Style.nil
3910 { Amount.Style.unit_side = Just Amount.Style.Side_Right
3911 , Amount.Style.unit_spaced = Just False
3916 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3919 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
3920 (Data.List.map fst $
3921 Data.Either.rights $
3922 [P.runParser_with_Error
3923 (Format.Ledger.Read.posting <* P.eof)
3924 ( Format.Ledger.Read.context () Format.Ledger.journal
3925 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3926 "" (" A:B:C $1 + 1$"::Text)])
3928 [ (Format.Ledger.posting ("A":|["B", "C"]))
3929 { Format.Ledger.posting_amounts = Data.Map.fromList
3931 { Amount.quantity = 2
3932 , Amount.style = Amount.Style.nil
3933 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3934 , Amount.Style.unit_spaced = Just False
3939 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3942 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
3943 (Data.List.map fst $
3944 Data.Either.rights $
3945 [P.runParser_with_Error
3946 (Format.Ledger.Read.posting <* P.eof)
3947 ( Format.Ledger.Read.context () Format.Ledger.journal
3948 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3949 "" (" A:B:C $1 + 1$ + 1$"::Text)])
3951 [ (Format.Ledger.posting ("A":|["B", "C"]))
3952 { Format.Ledger.posting_amounts = Data.Map.fromList
3954 { Amount.quantity = 3
3955 , Amount.style = Amount.Style.nil
3956 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3957 , Amount.Style.unit_spaced = Just False
3962 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3965 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
3966 (Data.List.map fst $
3967 Data.Either.rights $
3968 [P.runParser_with_Error
3969 (Format.Ledger.Read.posting <* P.eof)
3970 ( Format.Ledger.Read.context () Format.Ledger.journal
3971 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3972 "" (" A:B:C ; some comment"::Text)])
3974 [ (Format.Ledger.posting ("A":|["B", "C"]))
3975 { Format.Ledger.posting_amounts = Data.Map.fromList []
3976 , Format.Ledger.posting_comments = [" some comment"]
3977 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3980 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
3981 (Data.List.map fst $
3982 Data.Either.rights $
3983 [P.runParser_with_Error
3984 (Format.Ledger.Read.posting <* P.eof)
3985 ( Format.Ledger.Read.context () Format.Ledger.journal
3986 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3987 "" (" A:B:C ; some comment\n ; some other comment"::Text)])
3989 [ (Format.Ledger.posting ("A":|["B", "C"]))
3990 { Format.Ledger.posting_amounts = Data.Map.fromList []
3991 , Format.Ledger.posting_comments = [" some comment", " some other comment"]
3992 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3995 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
3996 (Data.List.map fst $
3997 Data.Either.rights $
3998 [P.runParser_with_Error
3999 (Format.Ledger.Read.posting)
4000 ( Format.Ledger.Read.context () Format.Ledger.journal
4001 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4002 "" (" A:B:C $1 ; some comment"::Text)])
4004 [ (Format.Ledger.posting ("A":|["B", "C"]))
4005 { Format.Ledger.posting_amounts = Data.Map.fromList
4007 { Amount.quantity = 1
4008 , Amount.style = Amount.Style.nil
4009 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4010 , Amount.Style.unit_spaced = Just False
4015 , Format.Ledger.posting_comments = [" some comment"]
4016 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4019 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
4020 (Data.List.map fst $
4021 Data.Either.rights $
4022 [P.runParser_with_Error
4023 (Format.Ledger.Read.posting <* P.eof)
4024 ( Format.Ledger.Read.context () Format.Ledger.journal
4025 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4026 "" (" A:B:C ; N:V"::Text)])
4028 [ (Format.Ledger.posting ("A":|["B", "C"]))
4029 { Format.Ledger.posting_comments = [" N:V"]
4030 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4031 , Format.Ledger.posting_tags = Data.Map.fromList
4036 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
4037 (Data.List.map fst $
4038 Data.Either.rights $
4039 [P.runParser_with_Error
4040 (Format.Ledger.Read.posting <* P.eof)
4041 ( Format.Ledger.Read.context () Format.Ledger.journal
4042 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4043 "" (" A:B:C ; some comment N:V"::Text)])
4045 [ (Format.Ledger.posting ("A":|["B", "C"]))
4046 { Format.Ledger.posting_comments = [" some comment N:V"]
4047 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4048 , Format.Ledger.posting_tags = Data.Map.fromList
4053 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
4054 (Data.List.map fst $
4055 Data.Either.rights $
4056 [P.runParser_with_Error
4057 (Format.Ledger.Read.posting )
4058 ( Format.Ledger.Read.context () Format.Ledger.journal
4059 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4060 "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
4062 [ (Format.Ledger.posting ("A":|["B", "C"]))
4063 { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"]
4064 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4065 , Format.Ledger.posting_tags = Data.Map.fromList
4071 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
4072 (Data.List.map fst $
4073 Data.Either.rights $
4074 [P.runParser_with_Error
4075 (Format.Ledger.Read.posting <* P.eof)
4076 ( Format.Ledger.Read.context () Format.Ledger.journal
4077 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4078 "" (" A:B:C ; N:V\n ; N:V2"::Text)])
4080 [ (Format.Ledger.posting ("A":|["B", "C"]))
4081 { Format.Ledger.posting_comments = [" N:V", " N:V2"]
4082 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4083 , Format.Ledger.posting_tags = Data.Map.fromList
4084 [ ("N", ["V", "V2"])
4088 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
4089 (Data.List.map fst $
4090 Data.Either.rights $
4091 [P.runParser_with_Error
4092 (Format.Ledger.Read.posting <* P.eof)
4093 ( Format.Ledger.Read.context () Format.Ledger.journal
4094 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4095 "" (" A:B:C ; N:V\n ; N2:V"::Text)])
4097 [ (Format.Ledger.posting ("A":|["B", "C"]))
4098 { Format.Ledger.posting_comments = [" N:V", " N2:V"]
4099 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4100 , Format.Ledger.posting_tags = Data.Map.fromList
4106 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
4107 (Data.List.map fst $
4108 Data.Either.rights $
4109 [P.runParser_with_Error
4110 (Format.Ledger.Read.posting <* P.eof)
4111 ( Format.Ledger.Read.context () Format.Ledger.journal
4112 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4113 "" (" A:B:C ; date:2001/01/01"::Text)])
4115 [ (Format.Ledger.posting ("A":|["B", "C"]))
4116 { Format.Ledger.posting_comments = [" date:2001/01/01"]
4117 , Format.Ledger.posting_dates =
4118 [ Time.zonedTimeToUTC $
4121 (Time.fromGregorian 2001 01 01)
4122 (Time.TimeOfDay 0 0 0))
4125 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4126 , Format.Ledger.posting_tags = Data.Map.fromList
4127 [ ("date", ["2001/01/01"])
4131 , " (A:B:C) = Right (A:B:C)" ~:
4132 (Data.Either.rights $
4133 [P.runParser_with_Error
4134 (Format.Ledger.Read.posting <* P.eof)
4135 ( Format.Ledger.Read.context () Format.Ledger.journal
4136 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4137 "" (" (A:B:C)"::Text)])
4139 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4140 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4142 , Format.Ledger.Posting_Type_Virtual
4145 , " [A:B:C] = Right [A:B:C]" ~:
4146 (Data.Either.rights $
4147 [P.runParser_with_Error
4148 (Format.Ledger.Read.posting <* P.eof)
4149 ( Format.Ledger.Read.context () Format.Ledger.journal
4150 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4151 "" (" [A:B:C]"::Text)])
4153 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4154 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4156 , Format.Ledger.Posting_Type_Virtual_Balanced
4160 , "transaction" ~: TestList
4161 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
4162 (Data.Either.rights $
4163 [P.runParser_with_Error
4164 (Format.Ledger.Read.transaction <* P.eof)
4165 ( Format.Ledger.Read.context () Format.Ledger.journal
4166 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4167 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
4169 [ Format.Ledger.transaction
4170 { Format.Ledger.transaction_dates=
4171 ( Time.zonedTimeToUTC $
4174 (Time.fromGregorian 2000 01 01)
4175 (Time.TimeOfDay 0 0 0))
4178 , Format.Ledger.transaction_description="some description"
4179 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4180 [ (Format.Ledger.posting ("A":|["B", "C"]))
4181 { Format.Ledger.posting_amounts = Data.Map.fromList
4183 { Amount.quantity = 1
4184 , Amount.style = Amount.Style.nil
4185 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4186 , Amount.Style.unit_spaced = Just False
4191 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4193 , (Format.Ledger.posting ("a":|["b", "c"]))
4194 { Format.Ledger.posting_amounts = Data.Map.fromList
4196 { Amount.quantity = -1
4197 , Amount.style = Amount.Style.nil
4198 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4199 , Amount.Style.unit_spaced = Just False
4204 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4207 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4210 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
4211 (Data.Either.rights $
4212 [P.runParser_with_Error
4213 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
4214 ( Format.Ledger.Read.context () Format.Ledger.journal
4215 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4216 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
4218 [ Format.Ledger.transaction
4219 { Format.Ledger.transaction_dates=
4220 ( Time.zonedTimeToUTC $
4223 (Time.fromGregorian 2000 01 01)
4224 (Time.TimeOfDay 0 0 0))
4227 , Format.Ledger.transaction_description="some description"
4228 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4229 [ (Format.Ledger.posting ("A":|["B", "C"]))
4230 { Format.Ledger.posting_amounts = Data.Map.fromList
4232 { Amount.quantity = 1
4233 , Amount.style = Amount.Style.nil
4234 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4235 , Amount.Style.unit_spaced = Just False
4240 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4242 , (Format.Ledger.posting ("a":|["b", "c"]))
4243 { Format.Ledger.posting_amounts = Data.Map.fromList
4245 { Amount.quantity = -1
4246 , Amount.style = Amount.Style.nil
4247 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4248 , Amount.Style.unit_spaced = Just False
4253 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4256 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4259 , "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" ~:
4260 (Data.Either.rights $
4261 [P.runParser_with_Error
4262 (Format.Ledger.Read.transaction <* P.eof)
4263 ( Format.Ledger.Read.context () Format.Ledger.journal
4264 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4265 "" ("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)])
4267 [ Format.Ledger.transaction
4268 { Format.Ledger.transaction_comments_after =
4270 , " some other;comment"
4272 , " some last comment"
4274 , Format.Ledger.transaction_dates=
4275 ( Time.zonedTimeToUTC $
4278 (Time.fromGregorian 2000 01 01)
4279 (Time.TimeOfDay 0 0 0))
4282 , Format.Ledger.transaction_description="some description"
4283 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4284 [ (Format.Ledger.posting ("A":|["B", "C"]))
4285 { Format.Ledger.posting_amounts = Data.Map.fromList
4287 { Amount.quantity = 1
4288 , Amount.style = Amount.Style.nil
4289 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4290 , Amount.Style.unit_spaced = Just False
4295 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4297 , (Format.Ledger.posting ("a":|["b", "c"]))
4298 { Format.Ledger.posting_amounts = Data.Map.fromList
4300 { Amount.quantity = -1
4301 , Amount.style = Amount.Style.nil
4302 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4303 , Amount.Style.unit_spaced = Just False
4308 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4311 , Format.Ledger.transaction_tags = Data.Map.fromList
4314 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4318 , "journal" ~: TestList
4319 [ "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
4321 P.runParserT_with_Error
4322 (Format.Ledger.Read.journal "" {-<* P.eof-})
4323 ( Format.Ledger.Read.context () Format.Ledger.journal
4324 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4325 "" ("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)
4327 (\j -> j{Format.Ledger.journal_last_read_time=Date.nil}) $
4328 Data.Either.rights [jnl])
4330 [ Format.Ledger.journal
4331 { Format.Ledger.journal_transactions =
4332 [ Format.Ledger.transaction
4333 { Format.Ledger.transaction_dates=
4334 ( Time.zonedTimeToUTC $
4337 (Time.fromGregorian 2000 01 02)
4338 (Time.TimeOfDay 0 0 0))
4341 , Format.Ledger.transaction_description="2° description"
4342 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4343 [ (Format.Ledger.posting ("A":|["B", "C"]))
4344 { Format.Ledger.posting_amounts = Data.Map.fromList
4346 { Amount.quantity = 1
4347 , Amount.style = Amount.Style.nil
4348 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4349 , Amount.Style.unit_spaced = Just False
4354 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4356 , (Format.Ledger.posting ("x":|["y", "z"]))
4357 { Format.Ledger.posting_amounts = Data.Map.fromList
4359 { Amount.quantity = -1
4360 , Amount.style = Amount.Style.nil
4361 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4362 , Amount.Style.unit_spaced = Just False
4367 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4370 , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1
4372 , Format.Ledger.transaction
4373 { Format.Ledger.transaction_dates=
4374 ( Time.zonedTimeToUTC $
4377 (Time.fromGregorian 2000 01 01)
4378 (Time.TimeOfDay 0 0 0))
4381 , Format.Ledger.transaction_description="1° description"
4382 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4383 [ (Format.Ledger.posting ("A":|["B", "C"]))
4384 { Format.Ledger.posting_amounts = Data.Map.fromList
4386 { Amount.quantity = 1
4387 , Amount.style = Amount.Style.nil
4388 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4389 , Amount.Style.unit_spaced = Just False
4394 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4396 , (Format.Ledger.posting ("a":|["b", "c"]))
4397 { Format.Ledger.posting_amounts = Data.Map.fromList
4399 { Amount.quantity = -1
4400 , Amount.style = Amount.Style.nil
4401 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4402 , Amount.Style.unit_spaced = Just False
4407 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4410 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4417 , "Write" ~: TestList
4418 [ "account" ~: TestList
4420 ((Format.Ledger.Write.show
4421 Format.Ledger.Write.Style
4422 { Format.Ledger.Write.style_color=False
4423 , Format.Ledger.Write.style_align=True
4425 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
4430 ((Format.Ledger.Write.show
4431 Format.Ledger.Write.Style
4432 { Format.Ledger.Write.style_color=False
4433 , Format.Ledger.Write.style_align=True
4435 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
4440 ((Format.Ledger.Write.show
4441 Format.Ledger.Write.Style
4442 { Format.Ledger.Write.style_color=False
4443 , Format.Ledger.Write.style_align=True
4445 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual $
4450 ((Format.Ledger.Write.show
4451 Format.Ledger.Write.Style
4452 { Format.Ledger.Write.style_color=False
4453 , Format.Ledger.Write.style_align=True
4455 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual_Balanced $
4460 , "transaction" ~: TestList
4462 ((Format.Ledger.Write.show
4463 Format.Ledger.Write.Style
4464 { Format.Ledger.Write.style_color=False
4465 , Format.Ledger.Write.style_align=True
4467 Format.Ledger.Write.transaction
4468 Format.Ledger.transaction)
4471 , "2000/01/01 some description\\n\\ta:b:c\\n\\t ; first comment\\n\\t ; second comment\\n\\t ; third comment\\n\\tA:B:C $1" ~:
4472 ((Format.Ledger.Write.show
4473 Format.Ledger.Write.Style
4474 { Format.Ledger.Write.style_color=False
4475 , Format.Ledger.Write.style_align=True
4477 Format.Ledger.Write.transaction $
4478 Format.Ledger.transaction
4479 { Format.Ledger.transaction_dates=
4480 ( Time.zonedTimeToUTC $
4483 (Time.fromGregorian 2000 01 01)
4484 (Time.TimeOfDay 0 0 0))
4487 , Format.Ledger.transaction_description="some description"
4488 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4489 [ (Format.Ledger.posting ("A":|["B", "C"]))
4490 { Format.Ledger.posting_amounts = Data.Map.fromList
4492 { Amount.quantity = 1
4493 , Amount.style = Amount.Style.nil
4494 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4495 , Amount.Style.unit_spaced = Just False
4501 , (Format.Ledger.posting ("a":|["b", "c"]))
4502 { Format.Ledger.posting_comments = ["first comment","second comment","third comment"]
4507 "2000/01/01 some description\n\ta:b:c\n\t ; first comment\n\t ; second comment\n\t ; third comment\n\tA:B:C $1")
4508 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
4509 ((Format.Ledger.Write.show
4510 Format.Ledger.Write.Style
4511 { Format.Ledger.Write.style_color=False
4512 , Format.Ledger.Write.style_align=True
4514 Format.Ledger.Write.transaction $
4515 Format.Ledger.transaction
4516 { Format.Ledger.transaction_dates=
4517 ( Time.zonedTimeToUTC $
4520 (Time.fromGregorian 2000 01 01)
4521 (Time.TimeOfDay 0 0 0))
4524 , Format.Ledger.transaction_description="some description"
4525 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4526 [ (Format.Ledger.posting ("A":|["B", "C"]))
4527 { Format.Ledger.posting_amounts = Data.Map.fromList
4529 { Amount.quantity = 1
4530 , Amount.style = Amount.Style.nil
4531 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4532 , Amount.Style.unit_spaced = Just False
4538 , (Format.Ledger.posting ("AA":|["BB", "CC"]))
4539 { Format.Ledger.posting_amounts = Data.Map.fromList
4541 { Amount.quantity = 123
4542 , Amount.style = Amount.Style.nil
4543 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4544 , Amount.Style.unit_spaced = Just False
4553 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")