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_Section_Text
1829 (Filter.Filter_Text_Exact "A")
1831 (("A":|[]::Account))
1834 [ Filter.Filter_Account_Section_Any
1836 (("A":|[]::Account))
1839 [ Filter.Filter_Account_Section_Many
1841 (("A":|[]::Account))
1844 [ Filter.Filter_Account_Section_Many
1845 , Filter.Filter_Account_Section_Text
1846 (Filter.Filter_Text_Exact "A")
1848 (("A":|[]::Account))
1851 [ Filter.Filter_Account_Section_Text
1852 (Filter.Filter_Text_Exact "A")
1853 , Filter.Filter_Account_Section_Many
1855 (("A":|[]::Account))
1858 [ Filter.Filter_Account_Section_Text
1859 (Filter.Filter_Text_Exact "A")
1860 , Filter.Filter_Account_Section_Many
1862 (("A":|"B":[]::Account))
1865 [ Filter.Filter_Account_Section_Text
1866 (Filter.Filter_Text_Exact "A")
1867 , Filter.Filter_Account_Section_Text
1868 (Filter.Filter_Text_Exact "B")
1870 (("A":|"B":[]::Account))
1873 [ Filter.Filter_Account_Section_Text
1874 (Filter.Filter_Text_Exact "A")
1875 , Filter.Filter_Account_Section_Many
1876 , Filter.Filter_Account_Section_Text
1877 (Filter.Filter_Text_Exact "B")
1879 (("A":|"B":[]::Account))
1882 [ Filter.Filter_Account_Section_Many
1883 , Filter.Filter_Account_Section_Text
1884 (Filter.Filter_Text_Exact "B")
1885 , Filter.Filter_Account_Section_Many
1887 (("A":|"B":"C":[]::Account))
1890 [ Filter.Filter_Account_Section_Many
1891 , Filter.Filter_Account_Section_Text
1892 (Filter.Filter_Text_Exact "C")
1894 (("A":|"B":"C":[]::Account))
1896 , "Filter_Bool" ~: TestList
1899 (Filter.Any::Filter.Filter_Bool Filter.Filter_Account)
1900 (("A":|[]::Account))
1902 , "Filter_Ord" ~: TestList
1905 (Filter.With_Interval $ Filter.Filter_Ord_Gt (0::Integer))
1906 (fromJust $ (Lib.Interval.<=..<=) 1 2)
1909 (Filter.With_Interval $ Filter.Filter_Ord_Lt (0::Integer))
1910 (fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
1911 , "not (1 < (0, 2))" ~?
1913 (Filter.With_Interval $ Filter.Filter_Ord_Gt (1::Integer))
1914 (fromJust $ (Lib.Interval.<=..<=) 0 2))
1917 , "Read" ~: TestList
1918 [ "filter_account_section" ~: TestList
1920 (Data.Either.rights $
1922 (Filter.Read.filter_account <* P.eof)
1925 [ [Filter.Filter_Account_Section_Any]
1928 (Data.Either.rights $
1930 (Filter.Read.filter_account <* P.eof)
1933 [ [Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")]
1936 (Data.Either.rights $
1938 (Filter.Read.filter_account <* P.eof)
1939 () "" ("AA"::Text)])
1941 [ [Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "AA")]
1944 (Data.Either.rights $
1946 (Filter.Read.filter_account <* P.eof)
1947 () "" ("::A"::Text)])
1949 [ [ Filter.Filter_Account_Section_Many
1950 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1954 (Data.Either.rights $
1956 (Filter.Read.filter_account <* P.eof)
1957 () "" (":A"::Text)])
1959 [ [ Filter.Filter_Account_Section_Many
1960 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1964 (Data.Either.rights $
1966 (Filter.Read.filter_account <* P.eof)
1967 () "" ("A:"::Text)])
1969 [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1970 , Filter.Filter_Account_Section_Many
1974 (Data.Either.rights $
1976 (Filter.Read.filter_account <* P.eof)
1977 () "" ("A::"::Text)])
1979 [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1980 , Filter.Filter_Account_Section_Many
1984 (Data.Either.rights $
1986 (Filter.Read.filter_account <* P.eof)
1987 () "" ("A:B"::Text)])
1989 [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1990 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ]
1993 (Data.Either.rights $
1995 (Filter.Read.filter_account <* P.eof)
1996 () "" ("A::B"::Text)])
1998 [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
1999 , Filter.Filter_Account_Section_Many
2000 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2004 (Data.Either.rights $
2006 (Filter.Read.filter_account <* P.eof)
2007 () "" ("A:::B"::Text)])
2009 [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2010 , Filter.Filter_Account_Section_Many
2011 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2015 (Data.Either.rights $
2017 (Filter.Read.filter_account <* P.char ' ' <* P.eof)
2018 () "" ("A: "::Text)])
2020 [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2021 , Filter.Filter_Account_Section_Many
2025 , "filter_bool" ~: TestList
2027 (Data.Either.rights $
2029 (Filter.Read.filter_bool
2030 [ P.char 'E' >> return (return True) ]
2032 () "" ("( E )"::Text)])
2034 [ Filter.And (Filter.Bool True) Filter.Any
2037 (Data.Either.rights $
2039 (Filter.Read.filter_bool
2040 [ P.char 'E' >> return (return True) ]
2042 () "" ("( ( E ) )"::Text)])
2044 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
2046 , "( E ) & ( E )" ~:
2047 (Data.Either.rights $
2049 (Filter.Read.filter_bool
2050 [ P.char 'E' >> return (return True) ]
2052 () "" ("( E ) & ( E )"::Text)])
2055 (Filter.And (Filter.Bool True) Filter.Any)
2056 (Filter.And (Filter.Bool True) Filter.Any)
2058 , "( E ) + ( E )" ~:
2059 (Data.Either.rights $
2061 (Filter.Read.filter_bool
2062 [ P.char 'E' >> return (return True) ]
2064 () "" ("( E ) + ( E )"::Text)])
2067 (Filter.And (Filter.Bool True) Filter.Any)
2068 (Filter.And (Filter.Bool True) Filter.Any)
2070 , "( E ) - ( E )" ~:
2071 (Data.Either.rights $
2073 (Filter.Read.filter_bool
2074 [ P.char 'E' >> return (return True) ]
2076 () "" ("( E ) - ( E )"::Text)])
2079 (Filter.And (Filter.Bool True) Filter.Any)
2080 (Filter.Not (Filter.And (Filter.Bool True) Filter.Any))
2083 (Data.Either.rights $
2085 (Filter.Read.filter_bool
2086 [ P.char 'E' >> return (return True) ]
2088 () "" ("(- E )"::Text)])
2090 [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any
2095 , "Balance" ~: TestList
2096 [ "balance" ~: TestList
2097 [ "[A+$1] = A+$1 & $+1" ~:
2099 (Format.Ledger.posting ("A":|[]))
2100 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2105 { Balance.balance_by_account =
2106 Lib.TreeMap.from_List const $
2107 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2108 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2109 , Balance.balance_by_unit =
2110 Balance.Balance_by_Unit $
2112 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2114 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2115 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2120 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
2124 [ (Format.Ledger.posting ("A":|[]))
2125 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2127 , (Format.Ledger.posting ("A":|[]))
2128 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2133 { Balance.balance_by_account =
2134 Lib.TreeMap.from_List const $
2136 , Balance.Account_Sum $
2137 Data.Map.fromListWith const $
2138 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2144 , Balance.balance_by_unit =
2145 Balance.Balance_by_Unit $
2147 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2149 { Balance.unit_sum_amount = Amount.Sum_Both
2152 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2157 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
2161 [ (Format.Ledger.posting ("A":|[]))
2162 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2164 , (Format.Ledger.posting ("A":|[]))
2165 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ]
2170 { Balance.balance_by_account =
2171 Lib.TreeMap.from_List const $
2172 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2173 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
2174 , Balance.balance_by_unit =
2175 Balance.Balance_by_Unit $
2177 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2179 { Balance.unit_sum_amount = Amount.Sum_Positive (Amount.usd $ 1)
2180 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2184 { Balance.unit_sum_amount = Amount.Sum_Negative (Amount.eur $ -1)
2185 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2190 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
2194 [ (Format.Ledger.posting ("A":|[]))
2195 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2197 , (Format.Ledger.posting ("B":|[]))
2198 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2203 { Balance.balance_by_account =
2204 Lib.TreeMap.from_List const $
2205 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2206 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2207 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
2209 , Balance.balance_by_unit =
2210 Balance.Balance_by_Unit $
2212 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2214 { Balance.unit_sum_amount = Amount.Sum_Both
2217 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2226 [ (Format.Ledger.posting ("A":|[]))
2227 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2229 , (Format.Ledger.posting ("B":|[]))
2230 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2235 { Balance.balance_by_account =
2236 Lib.TreeMap.from_List const $
2237 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2238 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2239 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
2241 , Balance.balance_by_unit =
2242 Balance.Balance_by_Unit $
2244 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2246 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2247 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2252 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
2256 [ (Format.Ledger.posting ("A":|[]))
2257 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
2259 , (Format.Ledger.posting ("A":|[]))
2260 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
2265 { Balance.balance_by_account =
2266 Lib.TreeMap.from_List const $
2268 , Balance.Account_Sum $
2269 Data.Map.fromListWith const $
2270 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2271 [ Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2272 , Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2276 , Balance.balance_by_unit =
2277 Balance.Balance_by_Unit $
2279 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2281 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2282 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2286 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2287 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2292 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
2296 [ (Format.Ledger.posting ("A":|[]))
2297 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
2299 , (Format.Ledger.posting ("B":|[]))
2300 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
2305 { Balance.balance_by_account =
2306 Lib.TreeMap.from_List const $
2307 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2308 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
2309 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
2311 , Balance.balance_by_unit =
2312 Balance.Balance_by_Unit $
2314 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2316 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2317 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2321 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2322 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2326 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.gbp $ -3) (Amount.gbp $ 3)
2327 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2333 , "union" ~: TestList
2334 [ "empty empty = empty" ~:
2335 Balance.union Balance.empty Balance.empty
2337 (Balance.empty::Balance.Balance Amount)
2338 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
2341 { Balance.balance_by_account =
2342 Lib.TreeMap.from_List const $
2343 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2344 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2345 , Balance.balance_by_unit =
2346 Balance.Balance_by_Unit $
2348 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2350 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2351 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2357 { Balance.balance_by_account =
2358 Lib.TreeMap.from_List const $
2359 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2360 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2361 , Balance.balance_by_unit =
2362 Balance.Balance_by_Unit $
2364 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2366 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2367 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2374 { Balance.balance_by_account =
2375 Lib.TreeMap.from_List const $
2376 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2377 [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
2378 , Balance.balance_by_unit =
2379 Balance.Balance_by_Unit $
2381 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2383 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2384 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2389 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
2392 { Balance.balance_by_account =
2393 Lib.TreeMap.from_List const $
2394 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2395 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2396 , Balance.balance_by_unit =
2397 Balance.Balance_by_Unit $
2399 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2401 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2402 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2408 { Balance.balance_by_account =
2409 Lib.TreeMap.from_List const $
2410 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2411 [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2412 , Balance.balance_by_unit =
2413 Balance.Balance_by_Unit $
2415 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2417 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2418 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2425 { Balance.balance_by_account =
2426 Lib.TreeMap.from_List const $
2427 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2428 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2429 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2430 , Balance.balance_by_unit =
2431 Balance.Balance_by_Unit $
2433 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2435 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2436 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2441 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
2444 { Balance.balance_by_account =
2445 Lib.TreeMap.from_List const $
2446 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2447 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2448 , Balance.balance_by_unit =
2449 Balance.Balance_by_Unit $
2451 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2453 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2454 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2460 { Balance.balance_by_account =
2461 Lib.TreeMap.from_List const $
2462 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2463 [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
2464 , Balance.balance_by_unit =
2465 Balance.Balance_by_Unit $
2467 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2469 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2470 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2477 { Balance.balance_by_account =
2478 Lib.TreeMap.from_List const $
2479 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2480 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2481 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
2482 , Balance.balance_by_unit =
2483 Balance.Balance_by_Unit $
2485 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2487 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2488 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2492 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2493 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2499 , "expanded" ~: TestList
2504 (Lib.TreeMap.empty::Balance.Expanded Amount)
2507 (Lib.TreeMap.from_List const $
2508 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2509 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
2511 (Lib.TreeMap.from_List const $
2512 [ ("A":|[], Balance.Account_Sum_Expanded
2513 { Balance.inclusive =
2514 Balance.Account_Sum $
2515 Data.Map.map Amount.sum $
2516 Amount.from_List [ Amount.usd $ 1 ]
2517 , Balance.exclusive =
2518 Balance.Account_Sum $
2519 Data.Map.map Amount.sum $
2520 Amount.from_List [ Amount.usd $ 1 ]
2523 , "A/A+$1 = A+$1 A/A+$1" ~:
2525 (Lib.TreeMap.from_List const $
2526 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2527 [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
2529 (Lib.TreeMap.from_List const
2530 [ ("A":|[], Balance.Account_Sum_Expanded
2531 { Balance.inclusive =
2532 Balance.Account_Sum $
2533 Data.Map.map Amount.sum $
2534 Amount.from_List [ Amount.usd $ 1 ]
2535 , Balance.exclusive =
2536 Balance.Account_Sum $
2537 Data.Map.map Amount.sum $
2540 , ("A":|["A"], Balance.Account_Sum_Expanded
2541 { Balance.inclusive =
2542 Balance.Account_Sum $
2543 Data.Map.map Amount.sum $
2544 Amount.from_List [ Amount.usd $ 1 ]
2545 , Balance.exclusive =
2546 Balance.Account_Sum $
2547 Data.Map.map Amount.sum $
2548 Amount.from_List [ Amount.usd $ 1 ]
2551 , "A/B+$1 = A+$1 A/B+$1" ~:
2553 (Lib.TreeMap.from_List const $
2554 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2555 [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
2557 (Lib.TreeMap.from_List const
2558 [ ("A":|[], Balance.Account_Sum_Expanded
2559 { Balance.inclusive =
2560 Balance.Account_Sum $
2561 Data.Map.map Amount.sum $
2562 Amount.from_List [ Amount.usd $ 1 ]
2563 , Balance.exclusive =
2564 Balance.Account_Sum $
2565 Data.Map.map Amount.sum $
2568 , ("A":|["B"], Balance.Account_Sum_Expanded
2569 { Balance.inclusive =
2570 Balance.Account_Sum $
2571 Data.Map.map Amount.sum $
2572 Amount.from_List [ Amount.usd $ 1 ]
2573 , Balance.exclusive =
2574 Balance.Account_Sum $
2575 Data.Map.map Amount.sum $
2576 Amount.from_List [ Amount.usd $ 1 ]
2579 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
2581 (Lib.TreeMap.from_List const $
2582 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2583 [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
2585 (Lib.TreeMap.from_List const $
2586 [ ("A":|[], Balance.Account_Sum_Expanded
2587 { Balance.inclusive =
2588 Balance.Account_Sum $
2589 Data.Map.map Amount.sum $
2590 Amount.from_List [ Amount.usd $ 1 ]
2591 , Balance.exclusive =
2592 Balance.Account_Sum $
2593 Data.Map.map Amount.sum $
2596 , ("A":|["B"], Balance.Account_Sum_Expanded
2597 { Balance.inclusive =
2598 Balance.Account_Sum $
2599 Data.Map.map Amount.sum $
2600 Amount.from_List [ Amount.usd $ 1 ]
2601 , Balance.exclusive =
2602 Balance.Account_Sum $
2603 Data.Map.map Amount.sum $
2606 , ("A":|["B", "C"], 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+$1 A/B+$1 = A+$2 A/B+$1" ~:
2619 (Lib.TreeMap.from_List const $
2620 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2621 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2622 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2625 (Lib.TreeMap.from_List const
2626 [ ("A":|[], Balance.Account_Sum_Expanded
2627 { Balance.inclusive =
2628 Balance.Account_Sum $
2629 Data.Map.map Amount.sum $
2630 Amount.from_List [ Amount.usd $ 2 ]
2631 , Balance.exclusive =
2632 Balance.Account_Sum $
2633 Data.Map.map Amount.sum $
2634 Amount.from_List [ Amount.usd $ 1 ]
2636 , ("A":|["B"], Balance.Account_Sum_Expanded
2637 { Balance.inclusive =
2638 Balance.Account_Sum $
2639 Data.Map.map Amount.sum $
2640 Amount.from_List [ Amount.usd $ 1 ]
2641 , Balance.exclusive =
2642 Balance.Account_Sum $
2643 Data.Map.map Amount.sum $
2644 Amount.from_List [ Amount.usd $ 1 ]
2647 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
2649 (Lib.TreeMap.from_List const $
2650 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2651 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2652 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2653 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
2656 (Lib.TreeMap.from_List const
2657 [ ("A":|[], Balance.Account_Sum_Expanded
2658 { Balance.inclusive =
2659 Balance.Account_Sum $
2660 Data.Map.map Amount.sum $
2661 Amount.from_List [ Amount.usd $ 3 ]
2662 , Balance.exclusive =
2663 Balance.Account_Sum $
2664 Data.Map.map Amount.sum $
2665 Amount.from_List [ Amount.usd $ 1 ]
2667 , ("A":|["B"], Balance.Account_Sum_Expanded
2668 { Balance.inclusive =
2669 Balance.Account_Sum $
2670 Data.Map.map Amount.sum $
2671 Amount.from_List [ Amount.usd $ 2 ]
2672 , Balance.exclusive =
2673 Balance.Account_Sum $
2674 Data.Map.map Amount.sum $
2675 Amount.from_List [ Amount.usd $ 1 ]
2677 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
2678 { Balance.inclusive =
2679 Balance.Account_Sum $
2680 Data.Map.map Amount.sum $
2681 Amount.from_List [ Amount.usd $ 1 ]
2682 , Balance.exclusive =
2683 Balance.Account_Sum $
2684 Data.Map.map Amount.sum $
2685 Amount.from_List [ Amount.usd $ 1 ]
2688 , "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" ~:
2690 (Lib.TreeMap.from_List const $
2691 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2692 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2693 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2694 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
2695 , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
2698 (Lib.TreeMap.from_List const
2699 [ ("A":|[], Balance.Account_Sum_Expanded
2700 { Balance.inclusive =
2701 Balance.Account_Sum $
2702 Data.Map.map Amount.sum $
2703 Amount.from_List [ Amount.usd $ 4 ]
2704 , Balance.exclusive =
2705 Balance.Account_Sum $
2706 Data.Map.map Amount.sum $
2707 Amount.from_List [ Amount.usd $ 1 ]
2709 , ("A":|["B"], Balance.Account_Sum_Expanded
2710 { Balance.inclusive =
2711 Balance.Account_Sum $
2712 Data.Map.map Amount.sum $
2713 Amount.from_List [ Amount.usd $ 3 ]
2714 , Balance.exclusive =
2715 Balance.Account_Sum $
2716 Data.Map.map Amount.sum $
2717 Amount.from_List [ Amount.usd $ 1 ]
2719 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
2720 { Balance.inclusive =
2721 Balance.Account_Sum $
2722 Data.Map.map Amount.sum $
2723 Amount.from_List [ Amount.usd $ 2 ]
2724 , Balance.exclusive =
2725 Balance.Account_Sum $
2726 Data.Map.map Amount.sum $
2727 Amount.from_List [ Amount.usd $ 1 ]
2729 , ("A":|["B", "C", "D"], Balance.Account_Sum_Expanded
2730 { Balance.inclusive =
2731 Balance.Account_Sum $
2732 Data.Map.map Amount.sum $
2733 Amount.from_List [ Amount.usd $ 1 ]
2734 , Balance.exclusive =
2735 Balance.Account_Sum $
2736 Data.Map.map Amount.sum $
2737 Amount.from_List [ Amount.usd $ 1 ]
2740 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
2742 (Lib.TreeMap.from_List const $
2743 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2744 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2745 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
2746 , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
2747 , ("AA":|["B"], 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 $ 1 ]
2766 , Balance.exclusive =
2767 Balance.Account_Sum $
2768 Data.Map.map Amount.sum $
2769 Amount.from_List [ Amount.usd $ 1 ]
2771 , ("A":|["BB"], 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 ]
2781 , ("AA":|[], Balance.Account_Sum_Expanded
2782 { Balance.inclusive =
2783 Balance.Account_Sum $
2784 Data.Map.map Amount.sum $
2785 Amount.from_List [ Amount.usd $ 1 ]
2786 , Balance.exclusive =
2787 Balance.Account_Sum $
2788 Data.Map.map Amount.sum $
2791 , ("AA":|["B"], Balance.Account_Sum_Expanded
2792 { Balance.inclusive =
2793 Balance.Account_Sum $
2794 Data.Map.map Amount.sum $
2795 Amount.from_List [ Amount.usd $ 1 ]
2796 , Balance.exclusive =
2797 Balance.Account_Sum $
2798 Data.Map.map Amount.sum $
2799 Amount.from_List [ Amount.usd $ 1 ]
2803 , "deviation" ~: TestList
2805 (Balance.deviation $
2807 { Balance.balance_by_account =
2808 Lib.TreeMap.from_List const $
2809 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2810 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2811 , ("B":|[], Amount.from_List [])
2813 , Balance.balance_by_unit =
2814 Balance.Balance_by_Unit $
2816 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2818 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2819 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2825 (Balance.Deviation $
2826 Balance.Balance_by_Unit $
2828 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2830 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2831 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2835 , "{A+$1 B+$1, $2}" ~:
2836 (Balance.deviation $
2838 { Balance.balance_by_account =
2839 Lib.TreeMap.from_List const $
2840 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2841 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2842 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
2844 , Balance.balance_by_unit =
2845 Balance.Balance_by_Unit $
2847 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2849 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2850 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2858 (Balance.Deviation $
2859 Balance.Balance_by_Unit $
2861 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2863 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2864 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2870 , "is_equilibrium_inferrable" ~: TestList
2871 [ "nil" ~: TestCase $
2873 Balance.is_equilibrium_inferrable $
2875 (Balance.empty::Balance.Balance Amount.Amount)
2876 , "{A+$0, $+0}" ~: TestCase $
2878 Balance.is_equilibrium_inferrable $
2881 { Balance.balance_by_account =
2882 Lib.TreeMap.from_List const $
2883 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2884 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
2886 , Balance.balance_by_unit =
2887 Balance.Balance_by_Unit $
2889 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2891 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
2892 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2897 , "{A+$1, $+1}" ~: TestCase $
2899 Balance.is_equilibrium_inferrable $
2902 { Balance.balance_by_account =
2903 Lib.TreeMap.from_List const $
2904 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2905 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
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 (,())
2918 , "{A+$0+€0, $0 €+0}" ~: TestCase $
2920 Balance.is_equilibrium_inferrable $
2923 { Balance.balance_by_account =
2924 Lib.TreeMap.from_List const $
2925 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2926 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
2928 , Balance.balance_by_unit =
2929 Balance.Balance_by_Unit $
2931 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2933 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
2934 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2938 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
2939 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2944 , "{A+$1, B-$1, $+0}" ~: TestCase $
2946 Balance.is_equilibrium_inferrable $
2949 { Balance.balance_by_account =
2950 Lib.TreeMap.from_List const $
2951 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2952 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2953 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
2955 , Balance.balance_by_unit =
2956 Balance.Balance_by_Unit $
2958 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2960 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
2961 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2966 , "{A+$1 B, $+1}" ~: TestCase $
2968 Balance.is_equilibrium_inferrable $
2971 { Balance.balance_by_account =
2972 Lib.TreeMap.from_List const $
2973 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2974 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2975 , ("B":|[], Amount.from_List [])
2977 , Balance.balance_by_unit =
2978 Balance.Balance_by_Unit $
2980 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2982 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2983 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2988 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
2990 Balance.is_equilibrium_inferrable $
2993 { Balance.balance_by_account =
2994 Lib.TreeMap.from_List const $
2995 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2996 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2997 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
2999 , Balance.balance_by_unit =
3000 Balance.Balance_by_Unit $
3002 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3004 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3005 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3009 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3010 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3015 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
3017 Balance.is_equilibrium_inferrable $
3020 { Balance.balance_by_account =
3021 Lib.TreeMap.from_List const $
3022 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3023 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3024 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
3026 , Balance.balance_by_unit =
3027 Balance.Balance_by_Unit $
3029 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3031 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3032 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3036 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3037 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3042 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
3044 Balance.is_equilibrium_inferrable $
3047 { Balance.balance_by_account =
3048 Lib.TreeMap.from_List const $
3049 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3050 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
3051 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
3053 , Balance.balance_by_unit =
3054 Balance.Balance_by_Unit $
3056 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3058 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3059 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3063 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3064 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3068 { Balance.unit_sum_amount = Amount.sum $ Amount.gbp $ 0
3069 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3075 , "infer_equilibrium" ~: TestList
3077 (snd $ Balance.infer_equilibrium $
3078 Format.Ledger.posting_by_Account
3079 [ (Format.Ledger.posting ("A":|[]))
3080 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3081 , (Format.Ledger.posting ("B":|[]))
3082 { Format.Ledger.posting_amounts=Amount.from_List [] }
3086 Format.Ledger.posting_by_Account
3087 [ (Format.Ledger.posting ("A":|[]))
3088 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3089 , (Format.Ledger.posting ("B":|[]))
3090 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] }
3093 (snd $ Balance.infer_equilibrium $
3094 Format.Ledger.posting_by_Account
3095 [ (Format.Ledger.posting ("A":|[]))
3096 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3097 , (Format.Ledger.posting ("B":|[]))
3098 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] }
3102 Format.Ledger.posting_by_Account
3103 [ (Format.Ledger.posting ("A":|[]))
3104 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1] }
3105 , (Format.Ledger.posting ("B":|[]))
3106 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1, Amount.usd $ -1 ] }
3109 (snd $ Balance.infer_equilibrium $
3110 Format.Ledger.posting_by_Account
3111 [ (Format.Ledger.posting ("A":|[]))
3112 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3113 , (Format.Ledger.posting ("B":|[]))
3114 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3119 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3120 , Balance.unit_sum_accounts = Data.Map.fromList []}
3122 , "{A+$1 B-$1 B-1€}" ~:
3123 (snd $ Balance.infer_equilibrium $
3124 Format.Ledger.posting_by_Account
3125 [ (Format.Ledger.posting ("A":|[]))
3126 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3127 , (Format.Ledger.posting ("B":|[]))
3128 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
3132 Format.Ledger.posting_by_Account
3133 [ (Format.Ledger.posting ("A":|[]))
3134 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1 ] }
3135 , (Format.Ledger.posting ("B":|[]))
3136 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
3140 , "Format" ~: TestList
3141 [ "Ledger" ~: TestList
3142 [ "Read" ~: TestList
3143 [ "account_name" ~: TestList
3145 (Data.Either.rights $
3147 (Format.Ledger.Read.account_name <* P.eof)
3152 (Data.Either.rights $
3154 (Format.Ledger.Read.account_name <* P.eof)
3159 (Data.Either.rights $
3161 (Format.Ledger.Read.account_name <* P.eof)
3162 () "" ("AA"::Text)])
3166 (Data.Either.rights $
3168 (Format.Ledger.Read.account_name <* P.eof)
3173 (Data.Either.rights $
3175 (Format.Ledger.Read.account_name <* P.eof)
3180 (Data.Either.rights $
3182 (Format.Ledger.Read.account_name <* P.eof)
3183 () "" ("A:"::Text)])
3187 (Data.Either.rights $
3189 (Format.Ledger.Read.account_name <* P.eof)
3190 () "" (":A"::Text)])
3194 (Data.Either.rights $
3196 (Format.Ledger.Read.account_name <* P.eof)
3197 () "" ("A "::Text)])
3201 (Data.Either.rights $
3203 (Format.Ledger.Read.account_name)
3204 () "" ("A "::Text)])
3208 (Data.Either.rights $
3210 (Format.Ledger.Read.account_name <* P.eof)
3211 () "" ("A A"::Text)])
3215 (Data.Either.rights $
3217 (Format.Ledger.Read.account_name <* P.eof)
3218 () "" ("A "::Text)])
3222 (Data.Either.rights $
3224 (Format.Ledger.Read.account_name <* P.eof)
3225 () "" ("A \n"::Text)])
3229 (Data.Either.rights $
3231 (Format.Ledger.Read.account_name <* P.eof)
3232 () "" ("(A)A"::Text)])
3236 (Data.Either.rights $
3238 (Format.Ledger.Read.account_name <* P.eof)
3239 () "" ("( )A"::Text)])
3243 (Data.Either.rights $
3245 (Format.Ledger.Read.account_name <* P.eof)
3246 () "" ("(A) A"::Text)])
3250 (Data.Either.rights $
3252 (Format.Ledger.Read.account_name <* P.eof)
3253 () "" ("[ ]A"::Text)])
3257 (Data.Either.rights $
3259 (Format.Ledger.Read.account_name <* P.eof)
3260 () "" ("(A) "::Text)])
3264 (Data.Either.rights $
3266 (Format.Ledger.Read.account_name <* P.eof)
3267 () "" ("(A)"::Text)])
3271 (Data.Either.rights $
3273 (Format.Ledger.Read.account_name <* P.eof)
3274 () "" ("A(A)"::Text)])
3278 (Data.Either.rights $
3280 (Format.Ledger.Read.account_name <* P.eof)
3281 () "" ("[A]A"::Text)])
3285 (Data.Either.rights $
3287 (Format.Ledger.Read.account_name <* P.eof)
3288 () "" ("[A] A"::Text)])
3292 (Data.Either.rights $
3294 (Format.Ledger.Read.account_name <* P.eof)
3295 () "" ("[A] "::Text)])
3299 (Data.Either.rights $
3301 (Format.Ledger.Read.account_name <* P.eof)
3302 () "" ("[A]"::Text)])
3306 , "account" ~: TestList
3308 (Data.Either.rights $
3310 (Format.Ledger.Read.account <* P.eof)
3315 (Data.Either.rights $
3317 (Format.Ledger.Read.account <* P.eof)
3322 (Data.Either.rights $
3324 (Format.Ledger.Read.account <* P.eof)
3325 () "" ("A:"::Text)])
3329 (Data.Either.rights $
3331 (Format.Ledger.Read.account <* P.eof)
3332 () "" (":A"::Text)])
3336 (Data.Either.rights $
3338 (Format.Ledger.Read.account <* P.eof)
3339 () "" ("A "::Text)])
3343 (Data.Either.rights $
3345 (Format.Ledger.Read.account <* P.eof)
3346 () "" (" A"::Text)])
3350 (Data.Either.rights $
3352 (Format.Ledger.Read.account <* P.eof)
3353 () "" ("A:B"::Text)])
3357 (Data.Either.rights $
3359 (Format.Ledger.Read.account <* P.eof)
3360 () "" ("A:B:C"::Text)])
3363 , "\"Aa:Bbb:Cccc\"" ~:
3364 (Data.Either.rights $
3366 (Format.Ledger.Read.account <* P.eof)
3367 () "" ("Aa:Bbb:Cccc"::Text)])
3369 ["Aa":|["Bbb", "Cccc"]]
3370 , "\"A a : B b b : C c c c\"" ~:
3371 (Data.Either.rights $
3373 (Format.Ledger.Read.account <* P.eof)
3374 () "" ("A a : B b b : C c c c"::Text)])
3376 ["A a ":|[" B b b ", " C c c c"]]
3378 (Data.Either.rights $
3380 (Format.Ledger.Read.account <* P.eof)
3381 () "" ("A: :C"::Text)])
3385 (Data.Either.rights $
3387 (Format.Ledger.Read.account <* P.eof)
3388 () "" ("A::C"::Text)])
3392 (Data.Either.rights $
3394 (Format.Ledger.Read.account <* P.eof)
3395 () "" ("A:B:(C)"::Text)])
3399 , "posting_type" ~: TestList
3401 Format.Ledger.Read.posting_type
3404 (Format.Ledger.Posting_Type_Regular, "A":|[])
3406 Format.Ledger.Read.posting_type
3409 (Format.Ledger.Posting_Type_Regular, "(":|[])
3411 Format.Ledger.Read.posting_type
3414 (Format.Ledger.Posting_Type_Regular, ")":|[])
3416 Format.Ledger.Read.posting_type
3419 (Format.Ledger.Posting_Type_Regular, "()":|[])
3421 Format.Ledger.Read.posting_type
3424 (Format.Ledger.Posting_Type_Regular, "( )":|[])
3426 Format.Ledger.Read.posting_type
3429 (Format.Ledger.Posting_Type_Virtual, "A":|[])
3431 Format.Ledger.Read.posting_type
3434 (Format.Ledger.Posting_Type_Virtual, "A":|["B", "C"])
3436 Format.Ledger.Read.posting_type
3439 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
3441 Format.Ledger.Read.posting_type
3444 (Format.Ledger.Posting_Type_Regular, "(A)":|["B", "C"])
3446 Format.Ledger.Read.posting_type
3449 (Format.Ledger.Posting_Type_Regular, "A":|["(B)", "C"])
3451 Format.Ledger.Read.posting_type
3454 (Format.Ledger.Posting_Type_Regular, "A":|["B", "(C)"])
3456 Format.Ledger.Read.posting_type
3459 (Format.Ledger.Posting_Type_Regular, "[":|[])
3461 Format.Ledger.Read.posting_type
3464 (Format.Ledger.Posting_Type_Regular, "]":|[])
3466 Format.Ledger.Read.posting_type
3469 (Format.Ledger.Posting_Type_Regular, "[]":|[])
3471 Format.Ledger.Read.posting_type
3474 (Format.Ledger.Posting_Type_Regular, "[ ]":|[])
3476 Format.Ledger.Read.posting_type
3479 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|[])
3481 Format.Ledger.Read.posting_type
3484 (Format.Ledger.Posting_Type_Virtual_Balanced, "A":|["B", "C"])
3486 Format.Ledger.Read.posting_type
3489 (Format.Ledger.Posting_Type_Regular, "A":|["B", "C"])
3491 Format.Ledger.Read.posting_type
3494 (Format.Ledger.Posting_Type_Regular, "[A]":|["B", "C"])
3496 Format.Ledger.Read.posting_type
3499 (Format.Ledger.Posting_Type_Regular, "A":|["[B]", "C"])
3501 Format.Ledger.Read.posting_type
3504 (Format.Ledger.Posting_Type_Regular, "A":|["B", "[C]"])
3506 , "comment" ~: TestList
3507 [ "; some comment = Right \" some comment\"" ~:
3508 (Data.Either.rights $
3510 (Format.Ledger.Read.comment <* P.eof)
3511 () "" ("; some comment"::Text)])
3514 , "; some comment \\n = Right \" some comment \"" ~:
3515 (Data.Either.rights $
3517 (Format.Ledger.Read.comment <* P.newline <* P.eof)
3518 () "" ("; some comment \n"::Text)])
3520 [ " some comment " ]
3521 , "; some comment \\r\\n = Right \" some comment \"" ~:
3522 (Data.Either.rights $
3524 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
3525 () "" ("; some comment \r\n"::Text)])
3527 [ " some comment " ]
3529 , "comments" ~: TestList
3530 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
3531 (Data.Either.rights $
3533 (Format.Ledger.Read.comments <* P.eof)
3534 () "" ("; some comment\n ; some other comment"::Text)])
3536 [ [" some comment", " some other comment"] ]
3537 , "; some comment \\n = Right \" some comment \"" ~:
3538 (Data.Either.rights $
3540 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
3541 () "" ("; some comment \n"::Text)])
3543 [ [" some comment "] ]
3545 , "tag_value" ~: TestList
3547 (Data.Either.rights $
3549 (Format.Ledger.Read.tag_value <* P.eof)
3554 (Data.Either.rights $
3556 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
3557 () "" (",\n"::Text)])
3561 (Data.Either.rights $
3563 (Format.Ledger.Read.tag_value <* P.eof)
3564 () "" (",x"::Text)])
3568 (Data.Either.rights $
3570 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
3571 () "" (",x:"::Text)])
3575 (Data.Either.rights $
3577 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
3578 () "" ("v, v, n:"::Text)])
3584 (Data.Either.rights $
3586 (Format.Ledger.Read.tag <* P.eof)
3587 () "" ("Name:"::Text)])
3591 (Data.Either.rights $
3593 (Format.Ledger.Read.tag <* P.eof)
3594 () "" ("Name:Value"::Text)])
3597 , "Name:Value\\n" ~:
3598 (Data.Either.rights $
3600 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
3601 () "" ("Name:Value\n"::Text)])
3605 (Data.Either.rights $
3607 (Format.Ledger.Read.tag <* P.eof)
3608 () "" ("Name:Val ue"::Text)])
3610 [("Name", "Val ue")]
3612 (Data.Either.rights $
3614 (Format.Ledger.Read.tag <* P.eof)
3615 () "" ("Name:,"::Text)])
3619 (Data.Either.rights $
3621 (Format.Ledger.Read.tag <* P.eof)
3622 () "" ("Name:Val,ue"::Text)])
3624 [("Name", "Val,ue")]
3626 (Data.Either.rights $
3628 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
3629 () "" ("Name:Val,ue:"::Text)])
3633 , "tags" ~: TestList
3635 (Data.Either.rights $
3637 (Format.Ledger.Read.tags <* P.eof)
3638 () "" ("Name:"::Text)])
3645 (Data.Either.rights $
3647 (Format.Ledger.Read.tags <* P.eof)
3648 () "" ("Name:,"::Text)])
3655 (Data.Either.rights $
3657 (Format.Ledger.Read.tags <* P.eof)
3658 () "" ("Name:,Name:"::Text)])
3661 [ ("Name", ["", ""])
3665 (Data.Either.rights $
3667 (Format.Ledger.Read.tags <* P.eof)
3668 () "" ("Name:,Name2:"::Text)])
3675 , "Name: , Name2:" ~:
3676 (Data.Either.rights $
3678 (Format.Ledger.Read.tags <* P.eof)
3679 () "" ("Name: , Name2:"::Text)])
3686 , "Name:,Name2:,Name3:" ~:
3687 (Data.Either.rights $
3689 (Format.Ledger.Read.tags <* P.eof)
3690 () "" ("Name:,Name2:,Name3:"::Text)])
3698 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
3699 (Data.Either.rights $
3701 (Format.Ledger.Read.tags <* P.eof)
3702 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
3705 [ ("Name", ["Val ue"])
3706 , ("Name2", ["V a l u e"])
3707 , ("Name3", ["V al ue"])
3711 , "posting" ~: TestList
3712 [ " A:B:C = Right A:B:C" ~:
3713 (Data.Either.rights $
3714 [P.runParser_with_Error
3715 (Format.Ledger.Read.posting <* P.eof)
3716 ( Format.Ledger.Read.context () Format.Ledger.journal
3717 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3718 "" (" A:B:C"::Text)])
3720 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
3721 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3723 , Format.Ledger.Posting_Type_Regular
3726 , " !A:B:C = Right !A:B:C" ~:
3727 (Data.List.map fst $
3728 Data.Either.rights $
3729 [P.runParser_with_Error
3730 (Format.Ledger.Read.posting <* P.eof)
3731 ( Format.Ledger.Read.context () Format.Ledger.journal
3732 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3733 "" (" !A:B:C"::Text)])
3735 [ (Format.Ledger.posting ("A":|["B", "C"]))
3736 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3737 , Format.Ledger.posting_status = True
3740 , " *A:B:C = Right *A:B:C" ~:
3741 (Data.List.map fst $
3742 Data.Either.rights $
3743 [P.runParser_with_Error
3744 (Format.Ledger.Read.posting <* P.eof)
3745 ( Format.Ledger.Read.context () Format.Ledger.journal
3746 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3747 "" (" *A:B:C"::Text)])
3749 [ (Format.Ledger.posting ("A":|["B", "C"]))
3750 { Format.Ledger.posting_amounts = Data.Map.fromList []
3751 , Format.Ledger.posting_comments = []
3752 , Format.Ledger.posting_dates = []
3753 , Format.Ledger.posting_status = True
3754 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3755 , Format.Ledger.posting_tags = Data.Map.fromList []
3758 , " A:B:C $1 = Right A:B:C $1" ~:
3759 (Data.List.map fst $
3760 Data.Either.rights $
3761 [P.runParser_with_Error
3762 (Format.Ledger.Read.posting <* P.eof)
3763 ( Format.Ledger.Read.context () Format.Ledger.journal
3764 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3765 "" (" A:B:C $1"::Text)])
3767 [ (Format.Ledger.posting ("A":|["B","C $1"]))
3768 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3771 , " A:B:C $1 = Right A:B:C $1" ~:
3772 (Data.List.map fst $
3773 Data.Either.rights $
3774 [P.runParser_with_Error
3775 (Format.Ledger.Read.posting <* P.eof)
3776 ( Format.Ledger.Read.context () Format.Ledger.journal
3777 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3778 "" (" A:B:C $1"::Text)])
3780 [ (Format.Ledger.posting ("A":|["B", "C"]))
3781 { Format.Ledger.posting_amounts = Data.Map.fromList
3783 { Amount.quantity = 1
3784 , Amount.style = Amount.Style.nil
3785 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3786 , Amount.Style.unit_spaced = Just False
3791 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3794 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
3795 (Data.List.map fst $
3796 Data.Either.rights $
3797 [P.runParser_with_Error
3798 (Format.Ledger.Read.posting <* P.eof)
3799 ( Format.Ledger.Read.context () Format.Ledger.journal
3800 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3801 "" (" A:B:C $1 + 1€"::Text)])
3803 [ (Format.Ledger.posting ("A":|["B", "C"]))
3804 { Format.Ledger.posting_amounts = Data.Map.fromList
3806 { Amount.quantity = 1
3807 , Amount.style = Amount.Style.nil
3808 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3809 , Amount.Style.unit_spaced = Just False
3814 { Amount.quantity = 1
3815 , Amount.style = Amount.Style.nil
3816 { Amount.Style.unit_side = Just Amount.Style.Side_Right
3817 , Amount.Style.unit_spaced = Just False
3822 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3825 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
3826 (Data.List.map fst $
3827 Data.Either.rights $
3828 [P.runParser_with_Error
3829 (Format.Ledger.Read.posting <* P.eof)
3830 ( Format.Ledger.Read.context () Format.Ledger.journal
3831 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3832 "" (" A:B:C $1 + 1$"::Text)])
3834 [ (Format.Ledger.posting ("A":|["B", "C"]))
3835 { Format.Ledger.posting_amounts = Data.Map.fromList
3837 { Amount.quantity = 2
3838 , Amount.style = Amount.Style.nil
3839 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3840 , Amount.Style.unit_spaced = Just False
3845 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3848 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
3849 (Data.List.map fst $
3850 Data.Either.rights $
3851 [P.runParser_with_Error
3852 (Format.Ledger.Read.posting <* P.eof)
3853 ( Format.Ledger.Read.context () Format.Ledger.journal
3854 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3855 "" (" A:B:C $1 + 1$ + 1$"::Text)])
3857 [ (Format.Ledger.posting ("A":|["B", "C"]))
3858 { Format.Ledger.posting_amounts = Data.Map.fromList
3860 { Amount.quantity = 3
3861 , Amount.style = Amount.Style.nil
3862 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3863 , Amount.Style.unit_spaced = Just False
3868 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3871 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
3872 (Data.List.map fst $
3873 Data.Either.rights $
3874 [P.runParser_with_Error
3875 (Format.Ledger.Read.posting <* P.eof)
3876 ( Format.Ledger.Read.context () Format.Ledger.journal
3877 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3878 "" (" A:B:C ; some comment"::Text)])
3880 [ (Format.Ledger.posting ("A":|["B", "C"]))
3881 { Format.Ledger.posting_amounts = Data.Map.fromList []
3882 , Format.Ledger.posting_comments = [" some comment"]
3883 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3886 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
3887 (Data.List.map fst $
3888 Data.Either.rights $
3889 [P.runParser_with_Error
3890 (Format.Ledger.Read.posting <* P.eof)
3891 ( Format.Ledger.Read.context () Format.Ledger.journal
3892 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3893 "" (" A:B:C ; some comment\n ; some other comment"::Text)])
3895 [ (Format.Ledger.posting ("A":|["B", "C"]))
3896 { Format.Ledger.posting_amounts = Data.Map.fromList []
3897 , Format.Ledger.posting_comments = [" some comment", " some other comment"]
3898 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3901 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
3902 (Data.List.map fst $
3903 Data.Either.rights $
3904 [P.runParser_with_Error
3905 (Format.Ledger.Read.posting)
3906 ( Format.Ledger.Read.context () Format.Ledger.journal
3907 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3908 "" (" A:B:C $1 ; some comment"::Text)])
3910 [ (Format.Ledger.posting ("A":|["B", "C"]))
3911 { Format.Ledger.posting_amounts = Data.Map.fromList
3913 { Amount.quantity = 1
3914 , Amount.style = Amount.Style.nil
3915 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3916 , Amount.Style.unit_spaced = Just False
3921 , Format.Ledger.posting_comments = [" some comment"]
3922 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3925 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
3926 (Data.List.map fst $
3927 Data.Either.rights $
3928 [P.runParser_with_Error
3929 (Format.Ledger.Read.posting <* P.eof)
3930 ( Format.Ledger.Read.context () Format.Ledger.journal
3931 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3932 "" (" A:B:C ; N:V"::Text)])
3934 [ (Format.Ledger.posting ("A":|["B", "C"]))
3935 { Format.Ledger.posting_comments = [" N:V"]
3936 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3937 , Format.Ledger.posting_tags = Data.Map.fromList
3942 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
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 ; some comment N:V"::Text)])
3951 [ (Format.Ledger.posting ("A":|["B", "C"]))
3952 { Format.Ledger.posting_comments = [" some comment N:V"]
3953 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3954 , Format.Ledger.posting_tags = Data.Map.fromList
3959 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
3960 (Data.List.map fst $
3961 Data.Either.rights $
3962 [P.runParser_with_Error
3963 (Format.Ledger.Read.posting )
3964 ( Format.Ledger.Read.context () Format.Ledger.journal
3965 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3966 "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
3968 [ (Format.Ledger.posting ("A":|["B", "C"]))
3969 { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"]
3970 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3971 , Format.Ledger.posting_tags = Data.Map.fromList
3977 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
3978 (Data.List.map fst $
3979 Data.Either.rights $
3980 [P.runParser_with_Error
3981 (Format.Ledger.Read.posting <* P.eof)
3982 ( Format.Ledger.Read.context () Format.Ledger.journal
3983 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3984 "" (" A:B:C ; N:V\n ; N:V2"::Text)])
3986 [ (Format.Ledger.posting ("A":|["B", "C"]))
3987 { Format.Ledger.posting_comments = [" N:V", " N:V2"]
3988 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3989 , Format.Ledger.posting_tags = Data.Map.fromList
3990 [ ("N", ["V", "V2"])
3994 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
3995 (Data.List.map fst $
3996 Data.Either.rights $
3997 [P.runParser_with_Error
3998 (Format.Ledger.Read.posting <* P.eof)
3999 ( Format.Ledger.Read.context () Format.Ledger.journal
4000 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4001 "" (" A:B:C ; N:V\n ; N2:V"::Text)])
4003 [ (Format.Ledger.posting ("A":|["B", "C"]))
4004 { Format.Ledger.posting_comments = [" N:V", " N2:V"]
4005 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4006 , Format.Ledger.posting_tags = Data.Map.fromList
4012 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
4013 (Data.List.map fst $
4014 Data.Either.rights $
4015 [P.runParser_with_Error
4016 (Format.Ledger.Read.posting <* P.eof)
4017 ( Format.Ledger.Read.context () Format.Ledger.journal
4018 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4019 "" (" A:B:C ; date:2001/01/01"::Text)])
4021 [ (Format.Ledger.posting ("A":|["B", "C"]))
4022 { Format.Ledger.posting_comments = [" date:2001/01/01"]
4023 , Format.Ledger.posting_dates =
4024 [ Time.zonedTimeToUTC $
4027 (Time.fromGregorian 2001 01 01)
4028 (Time.TimeOfDay 0 0 0))
4031 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4032 , Format.Ledger.posting_tags = Data.Map.fromList
4033 [ ("date", ["2001/01/01"])
4037 , " (A:B:C) = Right (A:B:C)" ~:
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)"::Text)])
4045 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4046 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4048 , Format.Ledger.Posting_Type_Virtual
4051 , " [A:B:C] = Right [A:B:C]" ~:
4052 (Data.Either.rights $
4053 [P.runParser_with_Error
4054 (Format.Ledger.Read.posting <* P.eof)
4055 ( Format.Ledger.Read.context () Format.Ledger.journal
4056 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4057 "" (" [A:B:C]"::Text)])
4059 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4060 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4062 , Format.Ledger.Posting_Type_Virtual_Balanced
4066 , "transaction" ~: TestList
4067 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
4068 (Data.Either.rights $
4069 [P.runParser_with_Error
4070 (Format.Ledger.Read.transaction <* P.eof)
4071 ( Format.Ledger.Read.context () Format.Ledger.journal
4072 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4073 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
4075 [ Format.Ledger.transaction
4076 { Format.Ledger.transaction_dates=
4077 ( Time.zonedTimeToUTC $
4080 (Time.fromGregorian 2000 01 01)
4081 (Time.TimeOfDay 0 0 0))
4084 , Format.Ledger.transaction_description="some description"
4085 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4086 [ (Format.Ledger.posting ("A":|["B", "C"]))
4087 { Format.Ledger.posting_amounts = Data.Map.fromList
4089 { Amount.quantity = 1
4090 , Amount.style = Amount.Style.nil
4091 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4092 , Amount.Style.unit_spaced = Just False
4097 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4099 , (Format.Ledger.posting ("a":|["b", "c"]))
4100 { Format.Ledger.posting_amounts = Data.Map.fromList
4102 { Amount.quantity = -1
4103 , Amount.style = Amount.Style.nil
4104 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4105 , Amount.Style.unit_spaced = Just False
4110 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4113 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4116 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
4117 (Data.Either.rights $
4118 [P.runParser_with_Error
4119 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
4120 ( Format.Ledger.Read.context () Format.Ledger.journal
4121 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4122 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
4124 [ Format.Ledger.transaction
4125 { Format.Ledger.transaction_dates=
4126 ( Time.zonedTimeToUTC $
4129 (Time.fromGregorian 2000 01 01)
4130 (Time.TimeOfDay 0 0 0))
4133 , Format.Ledger.transaction_description="some description"
4134 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4135 [ (Format.Ledger.posting ("A":|["B", "C"]))
4136 { Format.Ledger.posting_amounts = Data.Map.fromList
4138 { Amount.quantity = 1
4139 , Amount.style = Amount.Style.nil
4140 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4141 , Amount.Style.unit_spaced = Just False
4146 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4148 , (Format.Ledger.posting ("a":|["b", "c"]))
4149 { Format.Ledger.posting_amounts = Data.Map.fromList
4151 { Amount.quantity = -1
4152 , Amount.style = Amount.Style.nil
4153 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4154 , Amount.Style.unit_spaced = Just False
4159 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4162 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4165 , "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" ~:
4166 (Data.Either.rights $
4167 [P.runParser_with_Error
4168 (Format.Ledger.Read.transaction <* P.eof)
4169 ( Format.Ledger.Read.context () Format.Ledger.journal
4170 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4171 "" ("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)])
4173 [ Format.Ledger.transaction
4174 { Format.Ledger.transaction_comments_after =
4176 , " some other;comment"
4178 , " some last comment"
4180 , Format.Ledger.transaction_dates=
4181 ( Time.zonedTimeToUTC $
4184 (Time.fromGregorian 2000 01 01)
4185 (Time.TimeOfDay 0 0 0))
4188 , Format.Ledger.transaction_description="some description"
4189 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4190 [ (Format.Ledger.posting ("A":|["B", "C"]))
4191 { Format.Ledger.posting_amounts = Data.Map.fromList
4193 { Amount.quantity = 1
4194 , Amount.style = Amount.Style.nil
4195 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4196 , Amount.Style.unit_spaced = Just False
4201 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4203 , (Format.Ledger.posting ("a":|["b", "c"]))
4204 { Format.Ledger.posting_amounts = Data.Map.fromList
4206 { Amount.quantity = -1
4207 , Amount.style = Amount.Style.nil
4208 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4209 , Amount.Style.unit_spaced = Just False
4214 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4217 , Format.Ledger.transaction_tags = Data.Map.fromList
4220 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4224 , "journal" ~: TestList
4225 [ "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
4227 P.runParserT_with_Error
4228 (Format.Ledger.Read.journal "" {-<* P.eof-})
4229 ( Format.Ledger.Read.context () Format.Ledger.journal
4230 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4231 "" ("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)
4233 (\j -> j{Format.Ledger.journal_last_read_time=Date.nil}) $
4234 Data.Either.rights [jnl])
4236 [ Format.Ledger.journal
4237 { Format.Ledger.journal_transactions =
4238 [ Format.Ledger.transaction
4239 { Format.Ledger.transaction_dates=
4240 ( Time.zonedTimeToUTC $
4243 (Time.fromGregorian 2000 01 02)
4244 (Time.TimeOfDay 0 0 0))
4247 , Format.Ledger.transaction_description="2° description"
4248 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4249 [ (Format.Ledger.posting ("A":|["B", "C"]))
4250 { Format.Ledger.posting_amounts = Data.Map.fromList
4252 { Amount.quantity = 1
4253 , Amount.style = Amount.Style.nil
4254 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4255 , Amount.Style.unit_spaced = Just False
4260 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4262 , (Format.Ledger.posting ("x":|["y", "z"]))
4263 { Format.Ledger.posting_amounts = Data.Map.fromList
4265 { Amount.quantity = -1
4266 , Amount.style = Amount.Style.nil
4267 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4268 , Amount.Style.unit_spaced = Just False
4273 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4276 , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1
4278 , Format.Ledger.transaction
4279 { Format.Ledger.transaction_dates=
4280 ( Time.zonedTimeToUTC $
4283 (Time.fromGregorian 2000 01 01)
4284 (Time.TimeOfDay 0 0 0))
4287 , Format.Ledger.transaction_description="1° description"
4288 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4289 [ (Format.Ledger.posting ("A":|["B", "C"]))
4290 { Format.Ledger.posting_amounts = Data.Map.fromList
4292 { Amount.quantity = 1
4293 , Amount.style = Amount.Style.nil
4294 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4295 , Amount.Style.unit_spaced = Just False
4300 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4302 , (Format.Ledger.posting ("a":|["b", "c"]))
4303 { Format.Ledger.posting_amounts = Data.Map.fromList
4305 { Amount.quantity = -1
4306 , Amount.style = Amount.Style.nil
4307 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4308 , Amount.Style.unit_spaced = Just False
4313 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4316 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4323 , "Write" ~: TestList
4324 [ "account" ~: TestList
4326 ((Format.Ledger.Write.show
4327 Format.Ledger.Write.Style
4328 { Format.Ledger.Write.style_color=False
4329 , Format.Ledger.Write.style_align=True
4331 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
4336 ((Format.Ledger.Write.show
4337 Format.Ledger.Write.Style
4338 { Format.Ledger.Write.style_color=False
4339 , Format.Ledger.Write.style_align=True
4341 Format.Ledger.Write.account Format.Ledger.Posting_Type_Regular $
4346 ((Format.Ledger.Write.show
4347 Format.Ledger.Write.Style
4348 { Format.Ledger.Write.style_color=False
4349 , Format.Ledger.Write.style_align=True
4351 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual $
4356 ((Format.Ledger.Write.show
4357 Format.Ledger.Write.Style
4358 { Format.Ledger.Write.style_color=False
4359 , Format.Ledger.Write.style_align=True
4361 Format.Ledger.Write.account Format.Ledger.Posting_Type_Virtual_Balanced $
4366 , "transaction" ~: TestList
4368 ((Format.Ledger.Write.show
4369 Format.Ledger.Write.Style
4370 { Format.Ledger.Write.style_color=False
4371 , Format.Ledger.Write.style_align=True
4373 Format.Ledger.Write.transaction
4374 Format.Ledger.transaction)
4377 , "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" ~:
4378 ((Format.Ledger.Write.show
4379 Format.Ledger.Write.Style
4380 { Format.Ledger.Write.style_color=False
4381 , Format.Ledger.Write.style_align=True
4383 Format.Ledger.Write.transaction $
4384 Format.Ledger.transaction
4385 { Format.Ledger.transaction_dates=
4386 ( Time.zonedTimeToUTC $
4389 (Time.fromGregorian 2000 01 01)
4390 (Time.TimeOfDay 0 0 0))
4393 , Format.Ledger.transaction_description="some description"
4394 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4395 [ (Format.Ledger.posting ("A":|["B", "C"]))
4396 { Format.Ledger.posting_amounts = Data.Map.fromList
4398 { Amount.quantity = 1
4399 , Amount.style = Amount.Style.nil
4400 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4401 , Amount.Style.unit_spaced = Just False
4407 , (Format.Ledger.posting ("a":|["b", "c"]))
4408 { Format.Ledger.posting_comments = ["first comment","second comment","third comment"]
4413 "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")
4414 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
4415 ((Format.Ledger.Write.show
4416 Format.Ledger.Write.Style
4417 { Format.Ledger.Write.style_color=False
4418 , Format.Ledger.Write.style_align=True
4420 Format.Ledger.Write.transaction $
4421 Format.Ledger.transaction
4422 { Format.Ledger.transaction_dates=
4423 ( Time.zonedTimeToUTC $
4426 (Time.fromGregorian 2000 01 01)
4427 (Time.TimeOfDay 0 0 0))
4430 , Format.Ledger.transaction_description="some description"
4431 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4432 [ (Format.Ledger.posting ("A":|["B", "C"]))
4433 { Format.Ledger.posting_amounts = Data.Map.fromList
4435 { Amount.quantity = 1
4436 , Amount.style = Amount.Style.nil
4437 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4438 , Amount.Style.unit_spaced = Just False
4444 , (Format.Ledger.posting ("AA":|["BB", "CC"]))
4445 { Format.Ledger.posting_amounts = Data.Map.fromList
4447 { Amount.quantity = 123
4448 , Amount.style = Amount.Style.nil
4449 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4450 , Amount.Style.unit_spaced = Just False
4459 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")