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 qualified Hcompta.Account.Read as Account.Read
33 import Hcompta.Amount (Amount)
34 import qualified Hcompta.Amount as Amount
35 import qualified Hcompta.Amount.Read as Amount.Read
36 import qualified Hcompta.Amount.Write as Amount.Write
37 import qualified Hcompta.Amount.Style as Amount.Style
38 import qualified Hcompta.Balance as Balance
39 import qualified Hcompta.Date as Date
40 import qualified Hcompta.Date.Read as Date.Read
41 import qualified Hcompta.Date.Write as Date.Write
42 import qualified Hcompta.Filter as Filter
43 import qualified Hcompta.Filter.Read as Filter.Read
44 import qualified Hcompta.Format.Ledger as Format.Ledger
45 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
46 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
47 import qualified Hcompta.Posting as Posting
48 -- import qualified Hcompta.Journal as Journal
49 import qualified Hcompta.Lib.Foldable as Lib.Foldable
50 import qualified Hcompta.Lib.Interval as Lib.Interval
51 import qualified Hcompta.Lib.Interval.Sieve as Lib.Interval.Sieve
52 import qualified Hcompta.Lib.Parsec as P
53 import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
56 main = defaultMain $ hUnitTestToTests test_Hcompta
58 (~?) :: String -> Bool -> Test
59 (~?) s b = s ~: (b ~?= True)
65 [ "TreeMap" ~: TestList
66 [ "insert" ~: TestList
68 (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty)
70 (Lib.TreeMap.TreeMap $
72 [ ((0::Int), Lib.TreeMap.leaf ())
75 (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty)
77 (Lib.TreeMap.TreeMap $
79 [ ((0::Int), Lib.TreeMap.Node
80 { Lib.TreeMap.node_value = Strict.Nothing
81 , Lib.TreeMap.node_size = 1
82 , Lib.TreeMap.node_descendants =
83 Lib.TreeMap.singleton ((1::Int):|[]) ()
90 , "map_by_depth_first" ~: TestList
91 [ "[0, 0/1, 0/1/2, 1, 1/2/3]" ~:
92 (Lib.TreeMap.map_by_depth_first
93 (\descendants value ->
96 Strict.fromMaybe undefined $
97 Lib.TreeMap.node_value v
99 (Strict.fromMaybe [] value)
100 (Lib.TreeMap.nodes descendants)
102 Lib.TreeMap.from_List const
103 [ (((0::Integer):|[]), [0])
105 , ((0:|1:2:[]), [0,1,2])
107 , ((1:|2:3:[]), [1,2,3])
111 (Lib.TreeMap.from_List const
112 [ ((0:|[]), [0,0,1,0,1,2])
113 , ((0:|1:[]), [0,1,0,1,2])
114 , ((0:|1:2:[]), [0,1,2])
115 , ((1:|[]), [1,1,2,3])
116 , ((1:|2:[]), [1,2,3])
117 , ((1:|2:3:[]), [1,2,3])
120 (Lib.TreeMap.map_by_depth_first
121 (\descendants value ->
123 (\acc v -> (++) acc $
124 Strict.fromMaybe undefined $
125 Lib.TreeMap.node_value v
127 (Strict.fromMaybe [] value)
128 (Lib.TreeMap.nodes descendants)
130 Lib.TreeMap.from_List const
131 [ (((0::Integer):|0:[]), [0,0])
135 (Lib.TreeMap.from_List const
140 , "flatten" ~: TestList
141 [ "[0, 0/1, 0/1/2]" ~:
142 (Lib.TreeMap.flatten id $
143 Lib.TreeMap.from_List const
144 [ (((0::Integer):|[]), ())
155 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
156 (Lib.TreeMap.flatten id $
157 Lib.TreeMap.from_List const
166 , ((11:|2:33:[]), ())
171 [ (((1::Integer):|[]), ())
179 , ((11:|2:33:[]), ())
183 , "Foldable" ~: TestList
184 [ "accumLeftsAndFoldrRights" ~: TestList
186 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
189 (([(0::Integer)], [(""::String)]))
191 ((take 1 *** take 0) $
192 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
193 ( repeat (Left [0]) ))
195 ([(0::Integer)], ([]::[String]))
196 , "Right:Left:Right:Left" ~:
197 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
198 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
200 (([1, 0]::[Integer]), (["2", "1", "0"]::[String]))
201 , "Right:Left:Right:repeat Left" ~:
202 ((take 1 *** take 2) $
203 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
204 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
206 (([1]::[Integer]), (["2", "1"]::[String]))
209 , "Interval" ~: TestList
210 [ "position" ~: TestList $
213 let i = fromJust mi in
214 let j = fromJust mj in
217 Lib.Interval.Equal -> (EQ, EQ)
219 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.position i j ~?= (p, le)
220 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.position j i ~?= (p, ge)
223 [ ( (Lib.Interval.<..<) 0 (4::Integer)
224 , (Lib.Interval.<..<) 5 9
225 , Lib.Interval.Away )
226 , ( (Lib.Interval.<..<) 0 4
227 , (Lib.Interval.<=..<) 4 9
228 , Lib.Interval.Adjacent )
229 , ( (Lib.Interval.<..<) 0 5
230 , (Lib.Interval.<..<) 4 9
231 , Lib.Interval.Overlap )
232 , ( (Lib.Interval.<..<) 0 5
233 , (Lib.Interval.<..<) 0 9
234 , Lib.Interval.Prefix )
235 , ( (Lib.Interval.<..<) 0 9
236 , (Lib.Interval.<..<) 1 8
237 , Lib.Interval.Include )
238 , ( (Lib.Interval.<..<) 0 9
239 , (Lib.Interval.<..<) 5 9
240 , Lib.Interval.Suffixed )
241 , ( (Lib.Interval.<..<) 0 9
242 , (Lib.Interval.<..<) 0 9
243 , Lib.Interval.Equal )
244 , ( (Lib.Interval.<..<) 0 9
245 , (Lib.Interval.<..<=) 0 9
246 , Lib.Interval.Prefix )
247 , ( (Lib.Interval.<=..<) 0 9
248 , (Lib.Interval.<..<) 0 9
249 , Lib.Interval.Suffixed )
250 , ( (Lib.Interval.<=..<=) 0 9
251 , (Lib.Interval.<..<) 0 9
252 , Lib.Interval.Include )
254 , "intersection" ~: TestList $
257 let i = fromJust mi in
258 let j = fromJust mj in
259 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.intersection i j ~?= e
260 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.intersection j i ~?= e
263 [ ( (Lib.Interval.<..<) 0 (4::Integer)
264 , (Lib.Interval.<..<) 5 9
266 , ( (Lib.Interval.<..<=) 0 5
267 , (Lib.Interval.<=..<) 5 9
268 , (Lib.Interval.<=..<=) 5 5 )
269 , ( (Lib.Interval.<..<) 0 6
270 , (Lib.Interval.<..<) 4 9
271 , (Lib.Interval.<..<) 4 6 )
272 , ( (Lib.Interval.<..<=) 0 6
273 , (Lib.Interval.<=..<) 4 9
274 , (Lib.Interval.<=..<=) 4 6 )
275 , ( (Lib.Interval.<..<) 0 6
276 , (Lib.Interval.<=..<) 4 9
277 , (Lib.Interval.<=..<) 4 6 )
278 , ( (Lib.Interval.<..<=) 0 6
279 , (Lib.Interval.<..<) 4 9
280 , (Lib.Interval.<..<=) 4 6 )
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
291 , (Lib.Interval.<=..<=) 0 9
292 , (Lib.Interval.<=..<=) 0 9 )
294 , "union" ~: TestList $
297 let i = fromJust mi in
298 let j = fromJust mj in
299 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.union i j ~?= e
300 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.union j i ~?= e
303 [ ( (Lib.Interval.<..<) 0 (4::Integer)
304 , (Lib.Interval.<..<) 5 9
306 , ( (Lib.Interval.<..<=) 0 5
307 , (Lib.Interval.<..<) 5 9
308 , (Lib.Interval.<..<) 0 9 )
309 , ( (Lib.Interval.<..<) 0 5
310 , (Lib.Interval.<=..<) 5 9
311 , (Lib.Interval.<..<) 0 9 )
312 , ( (Lib.Interval.<..<=) 0 5
313 , (Lib.Interval.<=..<) 5 9
314 , (Lib.Interval.<..<) 0 9 )
315 , ( (Lib.Interval.<..<) 0 6
316 , (Lib.Interval.<..<) 4 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
328 , (Lib.Interval.<=..<=) 0 9
329 , (Lib.Interval.<=..<=) 0 9 )
331 , "Sieve" ~: TestList $
332 [ "union" ~: TestList $
335 let is = map (fromJust) mis in
336 let e = map (fromJust) me in
338 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
339 Lib.Interval.Sieve.empty is in
341 (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)
342 Lib.Interval.Sieve.empty is in
343 [ (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ~:
344 Lib.Interval.Sieve.intervals sil ~?= e
345 , (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ reverse is) ~:
346 Lib.Interval.Sieve.intervals sir ~?= e
349 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer)
350 , (Lib.Interval.<=..<=) 5 9
352 , [ (Lib.Interval.<=..<=) 0 9 ]
354 , ( [ (Lib.Interval.<=..<=) 0 5
355 , (Lib.Interval.<=..<=) 0 9
357 , [ (Lib.Interval.<=..<=) 0 9 ]
359 , ( [ (Lib.Interval.<=..<=) 0 4
360 , (Lib.Interval.<=..<=) 5 9
361 , (Lib.Interval.<=..<=) 3 6
363 , [ (Lib.Interval.<=..<=) 0 9 ]
365 , ( [ (Lib.Interval.<=..<=) 1 4
366 , (Lib.Interval.<=..<=) 5 8
368 , [ (Lib.Interval.<=..<=) 1 4
369 , (Lib.Interval.<=..<=) 5 8
372 , ( [ (Lib.Interval.<=..<=) 1 8
373 , (Lib.Interval.<=..<=) 0 9
375 , [ (Lib.Interval.<=..<=) 0 9 ]
377 , ( [ (Lib.Interval.<=..<=) 1 4
378 , (Lib.Interval.<=..<=) 5 8
379 , (Lib.Interval.<=..<=) 0 9
381 , [ (Lib.Interval.<=..<=) 0 9 ]
384 ++ Data.List.concatMap
386 let is = map fromJust mis in
387 let js = map fromJust mjs in
388 let e = map fromJust me in
390 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
391 Lib.Interval.Sieve.empty is in
393 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
394 Lib.Interval.Sieve.empty js in
395 [ ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " u " ++
396 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
397 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union iu ju) ~?= e
398 , ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " u " ++
399 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
400 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union ju iu) ~?= e
403 [ ( [ (Lib.Interval.<=..<=) 0 (1::Integer)
404 , (Lib.Interval.<=..<=) 2 4
406 , [ (Lib.Interval.<=..<=) 0 3
408 , [ (Lib.Interval.<=..<=) 0 4
411 , ( [ (Lib.Interval.<=..<=) 0 1
412 , (Lib.Interval.<=..<=) 2 3
413 , (Lib.Interval.<=..<=) 4 5
414 , (Lib.Interval.<=..<=) 6 7
416 , [ (Lib.Interval.<=..<=) 1 2
417 , (Lib.Interval.<=..<=) 3 4
418 , (Lib.Interval.<=..<=) 5 6
420 , [ (Lib.Interval.<=..<=) 0 7
423 , ( [ (Lib.Interval.<=..<=) 0 1
424 , (Lib.Interval.<=..<=) 2 3
426 , [ (Lib.Interval.<=..<=) 4 5
428 , [ (Lib.Interval.<=..<=) 0 1
429 , (Lib.Interval.<=..<=) 2 3
430 , (Lib.Interval.<=..<=) 4 5
433 , ( [ (Lib.Interval.<=..<=) 0 1
434 , (Lib.Interval.<=..<=) 4 5
436 , [ (Lib.Interval.<=..<=) 2 3
438 , [ (Lib.Interval.<=..<=) 0 1
439 , (Lib.Interval.<=..<=) 2 3
440 , (Lib.Interval.<=..<=) 4 5
444 , "intersection" ~: TestList $
447 let is = map (fromJust) mis in
448 let js = map (fromJust) mjs in
449 let e = map (fromJust) me in
451 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
452 Lib.Interval.Sieve.empty is in
454 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
455 Lib.Interval.Sieve.empty js in
456 [ ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " n " ++
457 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
458 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection iu ju) ~?= e
459 , ((Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " n " ++
460 (Data.List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
461 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection ju iu) ~?= e
464 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) ]
465 , [ (Lib.Interval.<=..<=) 5 9 ]
468 , ( [ (Lib.Interval.<=..<=) 0 5 ]
469 , [ (Lib.Interval.<=..<=) 5 9 ]
470 , [ (Lib.Interval.<=..<=) 5 5 ]
472 , ( [ (Lib.Interval.<=..<=) 0 5 ]
473 , [ (Lib.Interval.<=..<=) 0 9 ]
474 , [ (Lib.Interval.<=..<=) 0 5 ]
476 , ( [ (Lib.Interval.<=..<=) 0 4
477 , (Lib.Interval.<=..<=) 5 9
479 , [ (Lib.Interval.<=..<=) 3 6 ]
480 , [ (Lib.Interval.<=..<=) 3 4
481 , (Lib.Interval.<=..<=) 5 6
484 , ( [ (Lib.Interval.<=..<=) 1 4
485 , (Lib.Interval.<=..<=) 6 8
487 , [ (Lib.Interval.<=..<=) 2 3
488 , (Lib.Interval.<=..<=) 5 7
490 , [ (Lib.Interval.<=..<=) 2 3
491 , (Lib.Interval.<=..<=) 6 7
495 , "complement" ~: TestList $
498 let is = map fromJust mis in
499 let e = map fromJust me in
501 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
502 Lib.Interval.Sieve.empty is in
503 [ show (Lib.Interval.Pretty $
504 Lib.Interval.Sieve.fmap_interval
505 (Lib.Interval.fmap_unsafe $ Lib.Interval.Pretty) iu) ~:
506 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement iu) ~?= e
509 [ ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 (5::Integer)
510 , ((Lib.Interval.<=..<=) `on` Lib.Interval.Limited) 5 9
512 , [ Just $ (Lib.Interval...<) 0
513 , Just $ (Lib.Interval.<..) 9
516 , ( [ Just $ Lib.Interval.unlimited ]
520 , [ Just $ Lib.Interval.unlimited ]
522 , ( [ Just $ (Lib.Interval...<) 0
523 , Just $ (Lib.Interval.<..) 0
525 , [ Just $ Lib.Interval.point $ Lib.Interval.Limited 0
528 , ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 1
529 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 2 3
530 , ((Lib.Interval.<..<=) `on` Lib.Interval.Limited) 3 4
532 , [ Just $ (Lib.Interval...<) 0
533 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 1 2
534 , Just $ Lib.Interval.point $ Lib.Interval.Limited 3
535 , Just $ (Lib.Interval.<..) 4
539 , "complement_with" ~: TestList $
542 let ib = fromJust mib in
543 let is = map fromJust mis in
544 let e = map fromJust me in
546 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
547 Lib.Interval.Sieve.empty is in
548 [ show (Lib.Interval.Pretty iu) ~:
549 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement_with ib iu) ~?= e
552 [ ( (Lib.Interval.<=..<=) (-10) (10::Integer)
553 , [ (Lib.Interval.<=..<) 0 5
554 , (Lib.Interval.<=..<=) 5 9
556 , [ (Lib.Interval.<=..<) (-10) 0
557 , (Lib.Interval.<..<=) 9 10
560 , ( (Lib.Interval.<=..<=) (-10) 10
561 , [ (Lib.Interval.<=..<=) (-10) 10 ]
564 , ( (Lib.Interval.<=..<=) (-10) 10
566 , [ (Lib.Interval.<=..<=) (-10) 10 ]
568 , ( (Lib.Interval.<=..<=) (-10) 10
569 , [ (Lib.Interval.<=..<) (-10) 0
570 , (Lib.Interval.<..<=) 0 10
572 , [ Just $ Lib.Interval.point 0
575 , ( (Lib.Interval.<=..<=) (-10) 10
576 , [ Just $ Lib.Interval.point 0
578 , [ (Lib.Interval.<=..<) (-10) 0
579 , (Lib.Interval.<..<=) 0 10
582 , ( (Lib.Interval.<=..<=) 0 10
583 , [ (Lib.Interval.<..<=) 0 10
585 , [ Just $ Lib.Interval.point 0
588 , ( (Lib.Interval.<=..<=) 0 10
589 , [ (Lib.Interval.<=..<) 0 10
591 , [ Just $ Lib.Interval.point 10
594 , ( Just $ Lib.Interval.point 0
597 , [ Just $ Lib.Interval.point 0
600 , ( Just $ Lib.Interval.point 0
601 , [ Just $ Lib.Interval.point 0
610 , "Account" ~: TestList
611 [ "foldr" ~: TestList
613 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
615 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
617 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
619 , "ascending" ~: TestList
621 Account.ascending ("A":|[]) ~?= Nothing
623 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
625 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
628 [ "section" ~: TestList
630 (Data.Either.rights $
632 (Account.Read.section <* P.eof)
637 (Data.Either.rights $
639 (Account.Read.section <* P.eof)
644 (Data.Either.rights $
646 (Account.Read.section <* P.eof)
651 (Data.Either.rights $
653 (Account.Read.section <* P.eof)
658 (Data.Either.rights $
660 (Account.Read.section <* P.eof)
665 (Data.Either.rights $
667 (Account.Read.section <* P.eof)
672 (Data.Either.rights $
674 (Account.Read.section <* P.eof)
679 (Data.Either.rights $
681 (Account.Read.section <* P.eof)
686 (Data.Either.rights $
688 (Account.Read.section)
693 (Data.Either.rights $
695 (Account.Read.section <* P.eof)
696 () "" ("A A"::Text)])
700 (Data.Either.rights $
702 (Account.Read.section <* P.eof)
707 (Data.Either.rights $
709 (Account.Read.section <* P.eof)
710 () "" ("A\t"::Text)])
714 (Data.Either.rights $
716 (Account.Read.section <* P.eof)
717 () "" ("A \n"::Text)])
721 (Data.Either.rights $
723 (Account.Read.section <* P.eof)
724 () "" ("(A)A"::Text)])
728 (Data.Either.rights $
730 (Account.Read.section <* P.eof)
731 () "" ("( )A"::Text)])
735 (Data.Either.rights $
737 (Account.Read.section <* P.eof)
738 () "" ("(A) A"::Text)])
742 (Data.Either.rights $
744 (Account.Read.section <* P.eof)
745 () "" ("[ ]A"::Text)])
749 (Data.Either.rights $
751 (Account.Read.section <* P.eof)
752 () "" ("(A) "::Text)])
756 (Data.Either.rights $
758 (Account.Read.section <* P.eof)
759 () "" ("(A)"::Text)])
763 (Data.Either.rights $
765 (Account.Read.section <* P.eof)
766 () "" ("A(A)"::Text)])
770 (Data.Either.rights $
772 (Account.Read.section <* P.eof)
773 () "" ("[A]A"::Text)])
777 (Data.Either.rights $
779 (Account.Read.section <* P.eof)
780 () "" ("[A] A"::Text)])
784 (Data.Either.rights $
786 (Account.Read.section <* P.eof)
787 () "" ("[A] "::Text)])
791 (Data.Either.rights $
793 (Account.Read.section <* P.eof)
794 () "" ("[A]"::Text)])
798 , "account" ~: TestList
800 (Data.Either.rights $
802 (Account.Read.account <* P.eof)
807 (Data.Either.rights $
809 (Account.Read.account <* P.eof)
814 (Data.Either.rights $
816 (Account.Read.account <* P.eof)
821 (Data.Either.rights $
823 (Account.Read.account <* P.eof)
828 (Data.Either.rights $
830 (Account.Read.account <* P.eof)
835 (Data.Either.rights $
837 (Account.Read.account <* P.eof)
842 (Data.Either.rights $
844 (Account.Read.account <* P.eof)
845 () "" ("A:B"::Text)])
849 (Data.Either.rights $
851 (Account.Read.account <* P.eof)
852 () "" ("A:B:C"::Text)])
855 , "\"Aa:Bbb:Cccc\"" ~:
856 (Data.Either.rights $
858 (Account.Read.account <* P.eof)
859 () "" ("Aa:Bbb:Cccc"::Text)])
861 ["Aa":|["Bbb", "Cccc"]]
862 , "\"A a : B b b : C c c c\"" ~:
863 (Data.Either.rights $
865 (Account.Read.account <* P.eof)
866 () "" ("A a : B b b : C c c c"::Text)])
868 ["A a ":|[" B b b ", " C c c c"]]
870 (Data.Either.rights $
872 (Account.Read.account <* P.eof)
873 () "" ("A: :C"::Text)])
877 (Data.Either.rights $
879 (Account.Read.account <* P.eof)
880 () "" ("A::C"::Text)])
884 (Data.Either.rights $
886 (Account.Read.account <* P.eof)
887 () "" ("A:B:(C)"::Text)])
893 , "Amount" ~: TestList
898 { Amount.quantity = Decimal 0 1
899 , Amount.style = Amount.Style.nil
900 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
905 { Amount.quantity = Decimal 0 1
906 , Amount.style = Amount.Style.nil
907 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
913 { Amount.quantity = Decimal 0 2
914 , Amount.style = Amount.Style.nil
915 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
920 , "from_List" ~: TestList
921 [ "from_List [$1, 1$] = $2" ~:
924 { Amount.quantity = Decimal 0 1
925 , Amount.style = Amount.Style.nil
926 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
931 { Amount.quantity = Decimal 0 1
932 , Amount.style = Amount.Style.nil
933 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
941 { Amount.quantity = Decimal 0 2
942 , Amount.style = Amount.Style.nil
943 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
950 [ "amount" ~: TestList
952 (Data.Either.rights $
954 (Amount.Read.amount <* P.eof)
958 , "\"0\" = Right 0" ~:
959 (Data.Either.rights $
961 (Amount.Read.amount <* P.eof)
965 { Amount.quantity = Decimal 0 0
967 , "\"00\" = Right 0" ~:
968 (Data.Either.rights $
970 (Amount.Read.amount <* P.eof)
974 { Amount.quantity = Decimal 0 0
976 , "\"0.\" = Right 0." ~:
977 (Data.Either.rights $
979 (Amount.Read.amount <* P.eof)
983 { Amount.quantity = Decimal 0 0
986 { Amount.Style.fractioning = Just '.'
989 , "\".0\" = Right 0.0" ~:
990 (Data.Either.rights $
992 (Amount.Read.amount <* P.eof)
996 { Amount.quantity = Decimal 0 0
999 { Amount.Style.fractioning = Just '.'
1000 , Amount.Style.precision = 1
1003 , "\"0,\" = Right 0," ~:
1004 (Data.Either.rights $
1006 (Amount.Read.amount <* P.eof)
1007 () "" ("0,"::Text)])
1010 { Amount.quantity = Decimal 0 0
1013 { Amount.Style.fractioning = Just ','
1016 , "\",0\" = Right 0,0" ~:
1017 (Data.Either.rights $
1019 (Amount.Read.amount <* P.eof)
1020 () "" (",0"::Text)])
1023 { Amount.quantity = Decimal 0 0
1026 { Amount.Style.fractioning = Just ','
1027 , Amount.Style.precision = 1
1030 , "\"0_\" = Left" ~:
1031 (Data.Either.rights $
1033 (Amount.Read.amount <* P.eof)
1034 () "" ("0_"::Text)])
1037 , "\"_0\" = Left" ~:
1038 (Data.Either.rights $
1040 (Amount.Read.amount <* P.eof)
1041 () "" ("_0"::Text)])
1044 , "\"0.0\" = Right 0.0" ~:
1045 (Data.Either.rights $
1047 (Amount.Read.amount <* P.eof)
1048 () "" ("0.0"::Text)])
1051 { Amount.quantity = Decimal 0 0
1054 { Amount.Style.fractioning = Just '.'
1055 , Amount.Style.precision = 1
1058 , "\"00.00\" = Right 0.00" ~:
1059 (Data.Either.rights $
1061 (Amount.Read.amount <* P.eof)
1062 () "" ("00.00"::Text)])
1065 { Amount.quantity = Decimal 0 0
1068 { Amount.Style.fractioning = Just '.'
1069 , Amount.Style.precision = 2
1072 , "\"0,0\" = Right 0,0" ~:
1073 (Data.Either.rights $
1075 (Amount.Read.amount <* P.eof)
1076 () "" ("0,0"::Text)])
1079 { Amount.quantity = Decimal 0 0
1082 { Amount.Style.fractioning = Just ','
1083 , Amount.Style.precision = 1
1086 , "\"00,00\" = Right 0,00" ~:
1087 (Data.Either.rights $
1089 (Amount.Read.amount <* P.eof)
1090 () "" ("00,00"::Text)])
1093 { Amount.quantity = Decimal 0 0
1096 { Amount.Style.fractioning = Just ','
1097 , Amount.Style.precision = 2
1100 , "\"0_0\" = Right 0" ~:
1101 (Data.Either.rights $
1103 (Amount.Read.amount <* P.eof)
1104 () "" ("0_0"::Text)])
1107 { Amount.quantity = Decimal 0 0
1110 { Amount.Style.fractioning = Nothing
1111 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1112 , Amount.Style.precision = 0
1115 , "\"00_00\" = Right 0" ~:
1116 (Data.Either.rights $
1118 (Amount.Read.amount <* P.eof)
1119 () "" ("00_00"::Text)])
1122 { Amount.quantity = Decimal 0 0
1125 { Amount.Style.fractioning = Nothing
1126 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1127 , Amount.Style.precision = 0
1130 , "\"0,000.00\" = Right 0,000.00" ~:
1131 (Data.Either.rights $
1133 (Amount.Read.amount <* P.eof)
1134 () "" ("0,000.00"::Text)])
1137 { Amount.quantity = Decimal 0 0
1140 { Amount.Style.fractioning = Just '.'
1141 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1142 , Amount.Style.precision = 2
1145 , "\"0.000,00\" = Right 0.000,00" ~:
1146 (Data.Either.rights $
1148 (Amount.Read.amount)
1149 () "" ("0.000,00"::Text)])
1152 { Amount.quantity = Decimal 0 0
1155 { Amount.Style.fractioning = Just ','
1156 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1157 , Amount.Style.precision = 2
1160 , "\"1,000.00\" = Right 1,000.00" ~:
1161 (Data.Either.rights $
1163 (Amount.Read.amount <* P.eof)
1164 () "" ("1,000.00"::Text)])
1167 { Amount.quantity = Decimal 0 1000
1170 { Amount.Style.fractioning = Just '.'
1171 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1172 , Amount.Style.precision = 2
1175 , "\"1.000,00\" = Right 1.000,00" ~:
1176 (Data.Either.rights $
1178 (Amount.Read.amount)
1179 () "" ("1.000,00"::Text)])
1182 { Amount.quantity = Decimal 0 1000
1185 { Amount.Style.fractioning = Just ','
1186 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1187 , Amount.Style.precision = 2
1190 , "\"1,000.00.\" = Left" ~:
1191 (Data.Either.rights $
1193 (Amount.Read.amount)
1194 () "" ("1,000.00."::Text)])
1197 , "\"1.000,00,\" = Left" ~:
1198 (Data.Either.rights $
1200 (Amount.Read.amount)
1201 () "" ("1.000,00,"::Text)])
1204 , "\"1,000.00_\" = Left" ~:
1205 (Data.Either.rights $
1207 (Amount.Read.amount)
1208 () "" ("1,000.00_"::Text)])
1211 , "\"12\" = Right 12" ~:
1212 (Data.Either.rights $
1214 (Amount.Read.amount <* P.eof)
1215 () "" ("123"::Text)])
1218 { Amount.quantity = Decimal 0 123
1220 , "\"1.2\" = Right 1.2" ~:
1221 (Data.Either.rights $
1223 (Amount.Read.amount <* P.eof)
1224 () "" ("1.2"::Text)])
1227 { Amount.quantity = Decimal 1 12
1230 { Amount.Style.fractioning = Just '.'
1231 , Amount.Style.precision = 1
1234 , "\"1,2\" = Right 1,2" ~:
1235 (Data.Either.rights $
1237 (Amount.Read.amount <* P.eof)
1238 () "" ("1,2"::Text)])
1241 { Amount.quantity = Decimal 1 12
1244 { Amount.Style.fractioning = Just ','
1245 , Amount.Style.precision = 1
1248 , "\"12.23\" = Right 12.23" ~:
1249 (Data.Either.rights $
1251 (Amount.Read.amount <* P.eof)
1252 () "" ("12.34"::Text)])
1255 { Amount.quantity = Decimal 2 1234
1258 { Amount.Style.fractioning = Just '.'
1259 , Amount.Style.precision = 2
1262 , "\"12,23\" = Right 12,23" ~:
1263 (Data.Either.rights $
1265 (Amount.Read.amount <* P.eof)
1266 () "" ("12,34"::Text)])
1269 { Amount.quantity = Decimal 2 1234
1272 { Amount.Style.fractioning = Just ','
1273 , Amount.Style.precision = 2
1276 , "\"1_2\" = Right 1_2" ~:
1277 (Data.Either.rights $
1279 (Amount.Read.amount <* P.eof)
1280 () "" ("1_2"::Text)])
1283 { Amount.quantity = Decimal 0 12
1286 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1287 , Amount.Style.precision = 0
1290 , "\"1_23\" = Right 1_23" ~:
1291 (Data.Either.rights $
1293 (Amount.Read.amount <* P.eof)
1294 () "" ("1_23"::Text)])
1297 { Amount.quantity = Decimal 0 123
1300 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1301 , Amount.Style.precision = 0
1304 , "\"1_23_456\" = Right 1_23_456" ~:
1305 (Data.Either.rights $
1307 (Amount.Read.amount <* P.eof)
1308 () "" ("1_23_456"::Text)])
1311 { Amount.quantity = Decimal 0 123456
1314 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1315 , Amount.Style.precision = 0
1318 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1319 (Data.Either.rights $
1321 (Amount.Read.amount <* P.eof)
1322 () "" ("1_23_456.7890_12345_678901"::Text)])
1325 { Amount.quantity = Decimal 15 123456789012345678901
1328 { Amount.Style.fractioning = Just '.'
1329 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1330 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1331 , Amount.Style.precision = 15
1334 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1335 (Data.Either.rights $
1337 (Amount.Read.amount <* P.eof)
1338 () "" ("123456_78901_2345.678_90_1"::Text)])
1341 { Amount.quantity = Decimal 6 123456789012345678901
1344 { Amount.Style.fractioning = Just '.'
1345 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1346 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1347 , Amount.Style.precision = 6
1350 , "\"$1\" = Right $1" ~:
1351 (Data.Either.rights $
1353 (Amount.Read.amount <* P.eof)
1354 () "" ("$1"::Text)])
1357 { Amount.quantity = Decimal 0 1
1360 { Amount.Style.fractioning = Nothing
1361 , Amount.Style.grouping_integral = Nothing
1362 , Amount.Style.grouping_fractional = Nothing
1363 , Amount.Style.precision = 0
1364 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1365 , Amount.Style.unit_spaced = Just False
1369 , "\"1$\" = Right 1$" ~:
1370 (Data.Either.rights $
1372 (Amount.Read.amount <* P.eof)
1373 () "" ("1$"::Text)])
1376 { Amount.quantity = Decimal 0 1
1379 { Amount.Style.fractioning = Nothing
1380 , Amount.Style.grouping_integral = Nothing
1381 , Amount.Style.grouping_fractional = Nothing
1382 , Amount.Style.precision = 0
1383 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1384 , Amount.Style.unit_spaced = Just False
1388 , "\"$ 1\" = Right $ 1" ~:
1389 (Data.Either.rights $
1391 (Amount.Read.amount <* P.eof)
1392 () "" ("$ 1"::Text)])
1395 { Amount.quantity = Decimal 0 1
1398 { Amount.Style.fractioning = Nothing
1399 , Amount.Style.grouping_integral = Nothing
1400 , Amount.Style.grouping_fractional = Nothing
1401 , Amount.Style.precision = 0
1402 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1403 , Amount.Style.unit_spaced = Just True
1407 , "\"1 $\" = Right 1 $" ~:
1408 (Data.Either.rights $
1410 (Amount.Read.amount <* P.eof)
1411 () "" ("1 $"::Text)])
1414 { Amount.quantity = Decimal 0 1
1417 { Amount.Style.fractioning = Nothing
1418 , Amount.Style.grouping_integral = Nothing
1419 , Amount.Style.grouping_fractional = Nothing
1420 , Amount.Style.precision = 0
1421 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1422 , Amount.Style.unit_spaced = Just True
1426 , "\"-$1\" = Right $-1" ~:
1427 (Data.Either.rights $
1429 (Amount.Read.amount <* P.eof)
1430 () "" ("-$1"::Text)])
1433 { Amount.quantity = Decimal 0 (-1)
1436 { Amount.Style.fractioning = Nothing
1437 , Amount.Style.grouping_integral = Nothing
1438 , Amount.Style.grouping_fractional = Nothing
1439 , Amount.Style.precision = 0
1440 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1441 , Amount.Style.unit_spaced = Just False
1445 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1446 (Data.Either.rights $
1448 (Amount.Read.amount <* P.eof)
1449 () "" ("\"4 2\"1"::Text)])
1452 { Amount.quantity = Decimal 0 1
1455 { Amount.Style.fractioning = Nothing
1456 , Amount.Style.grouping_integral = Nothing
1457 , Amount.Style.grouping_fractional = Nothing
1458 , Amount.Style.precision = 0
1459 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1460 , Amount.Style.unit_spaced = Just False
1462 , Amount.unit = "4 2"
1464 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1465 (Data.Either.rights $
1467 (Amount.Read.amount <* P.eof)
1468 () "" ("1\"4 2\""::Text)])
1471 { Amount.quantity = Decimal 0 1
1474 { Amount.Style.fractioning = Nothing
1475 , Amount.Style.grouping_integral = Nothing
1476 , Amount.Style.grouping_fractional = Nothing
1477 , Amount.Style.precision = 0
1478 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1479 , Amount.Style.unit_spaced = Just False
1481 , Amount.unit = "4 2"
1483 , "\"$1.000,00\" = Right $1.000,00" ~:
1484 (Data.Either.rights $
1486 (Amount.Read.amount <* P.eof)
1487 () "" ("$1.000,00"::Text)])
1490 { Amount.quantity = Decimal 0 1000
1493 { Amount.Style.fractioning = Just ','
1494 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1495 , Amount.Style.grouping_fractional = Nothing
1496 , Amount.Style.precision = 2
1497 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1498 , Amount.Style.unit_spaced = Just False
1502 , "\"1.000,00$\" = Right 1.000,00$" ~:
1503 (Data.Either.rights $
1505 (Amount.Read.amount <* P.eof)
1506 () "" ("1.000,00$"::Text)])
1509 { Amount.quantity = Decimal 0 1000
1512 { Amount.Style.fractioning = Just ','
1513 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1514 , Amount.Style.grouping_fractional = Nothing
1515 , Amount.Style.precision = 2
1516 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1517 , Amount.Style.unit_spaced = Just False
1523 , "Write" ~: TestList
1524 [ "amount" ~: TestList
1526 ((Format.Ledger.Write.show
1527 Format.Ledger.Write.Style
1528 { Format.Ledger.Write.style_color=False
1529 , Format.Ledger.Write.style_align=True
1536 ((Format.Ledger.Write.show
1537 Format.Ledger.Write.Style
1538 { Format.Ledger.Write.style_color=False
1539 , Format.Ledger.Write.style_align=True
1543 { Amount.style = Amount.Style.nil
1544 { Amount.Style.precision = 2 }
1549 ((Format.Ledger.Write.show
1550 Format.Ledger.Write.Style
1551 { Format.Ledger.Write.style_color=False
1552 , Format.Ledger.Write.style_align=True
1556 { Amount.quantity = Decimal 0 123
1561 ((Format.Ledger.Write.show
1562 Format.Ledger.Write.Style
1563 { Format.Ledger.Write.style_color=False
1564 , Format.Ledger.Write.style_align=True
1568 { Amount.quantity = Decimal 0 (- 123)
1572 , "12.3 @ prec=0" ~:
1573 ((Format.Ledger.Write.show
1574 Format.Ledger.Write.Style
1575 { Format.Ledger.Write.style_color=False
1576 , Format.Ledger.Write.style_align=True
1580 { Amount.quantity = Decimal 1 123
1581 , Amount.style = Amount.Style.nil
1582 { Amount.Style.fractioning = Just '.'
1587 , "12.5 @ prec=0" ~:
1588 ((Format.Ledger.Write.show
1589 Format.Ledger.Write.Style
1590 { Format.Ledger.Write.style_color=False
1591 , Format.Ledger.Write.style_align=True
1595 { Amount.quantity = Decimal 1 125
1596 , Amount.style = Amount.Style.nil
1597 { Amount.Style.fractioning = Just '.'
1602 , "12.3 @ prec=1" ~:
1603 ((Format.Ledger.Write.show
1604 Format.Ledger.Write.Style
1605 { Format.Ledger.Write.style_color=False
1606 , Format.Ledger.Write.style_align=True
1610 { Amount.quantity = Decimal 1 123
1611 , Amount.style = Amount.Style.nil
1612 { Amount.Style.fractioning = Just '.'
1613 , Amount.Style.precision = 1
1618 , "1,234.56 @ prec=2" ~:
1619 ((Format.Ledger.Write.show
1620 Format.Ledger.Write.Style
1621 { Format.Ledger.Write.style_color=False
1622 , Format.Ledger.Write.style_align=True
1626 { Amount.quantity = Decimal 2 123456
1627 , Amount.style = Amount.Style.nil
1628 { Amount.Style.fractioning = Just '.'
1629 , Amount.Style.precision = 2
1630 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1635 , "123,456,789,01,2.3456789 @ prec=7" ~:
1636 ((Format.Ledger.Write.show
1637 Format.Ledger.Write.Style
1638 { Format.Ledger.Write.style_color=False
1639 , Format.Ledger.Write.style_align=True
1643 { Amount.quantity = Decimal 7 1234567890123456789
1644 , Amount.style = Amount.Style.nil
1645 { Amount.Style.fractioning = Just '.'
1646 , Amount.Style.precision = 7
1647 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1651 "123,456,789,01,2.3456789")
1652 , "1234567.8,90,123,456,789 @ prec=12" ~:
1653 ((Format.Ledger.Write.show
1654 Format.Ledger.Write.Style
1655 { Format.Ledger.Write.style_color=False
1656 , Format.Ledger.Write.style_align=True
1660 { Amount.quantity = Decimal 12 1234567890123456789
1661 , Amount.style = Amount.Style.nil
1662 { Amount.Style.fractioning = Just '.'
1663 , Amount.Style.precision = 12
1664 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1668 "1234567.8,90,123,456,789")
1669 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
1670 ((Format.Ledger.Write.show
1671 Format.Ledger.Write.Style
1672 { Format.Ledger.Write.style_color=False
1673 , Format.Ledger.Write.style_align=True
1677 { Amount.quantity = Decimal 7 1234567890123456789
1678 , Amount.style = Amount.Style.nil
1679 { Amount.Style.fractioning = Just '.'
1680 , Amount.Style.precision = 7
1681 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1685 "1,2,3,4,5,6,7,89,012.3456789")
1686 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
1687 ((Format.Ledger.Write.show
1688 Format.Ledger.Write.Style
1689 { Format.Ledger.Write.style_color=False
1690 , Format.Ledger.Write.style_align=True
1694 { Amount.quantity = Decimal 12 1234567890123456789
1695 , Amount.style = Amount.Style.nil
1696 { Amount.Style.fractioning = Just '.'
1697 , Amount.Style.precision = 12
1698 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1702 "1234567.890,12,3,4,5,6,7,8,9")
1704 , "amount_length" ~: TestList
1706 ((Amount.Write.amount_length
1711 ((Amount.Write.amount_length
1713 { Amount.style = Amount.Style.nil
1714 { Amount.Style.precision = 2 }
1719 ((Amount.Write.amount_length
1721 { Amount.quantity = Decimal 0 123
1726 ((Amount.Write.amount_length
1728 { Amount.quantity = Decimal 0 (- 123)
1732 , "12.3 @ prec=0" ~:
1733 ((Amount.Write.amount_length
1735 { Amount.quantity = Decimal 1 123
1736 , Amount.style = Amount.Style.nil
1737 { Amount.Style.fractioning = Just '.'
1742 , "12.5 @ prec=0" ~:
1743 ((Amount.Write.amount_length
1745 { Amount.quantity = Decimal 1 125
1746 , Amount.style = Amount.Style.nil
1747 { Amount.Style.fractioning = Just '.'
1752 , "12.3 @ prec=1" ~:
1753 ((Amount.Write.amount_length
1755 { Amount.quantity = Decimal 1 123
1756 , Amount.style = Amount.Style.nil
1757 { Amount.Style.fractioning = Just '.'
1758 , Amount.Style.precision = 1
1763 , "1,234.56 @ prec=2" ~:
1764 ((Amount.Write.amount_length
1766 { Amount.quantity = Decimal 2 123456
1767 , Amount.style = Amount.Style.nil
1768 { Amount.Style.fractioning = Just '.'
1769 , Amount.Style.precision = 2
1770 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1775 , "123,456,789,01,2.3456789 @ prec=7" ~:
1776 ((Amount.Write.amount_length
1778 { Amount.quantity = Decimal 7 1234567890123456789
1779 , Amount.style = Amount.Style.nil
1780 { Amount.Style.fractioning = Just '.'
1781 , Amount.Style.precision = 7
1782 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1787 , "1234567.8,90,123,456,789 @ prec=12" ~:
1788 ((Amount.Write.amount_length
1790 { Amount.quantity = Decimal 12 1234567890123456789
1791 , Amount.style = Amount.Style.nil
1792 { Amount.Style.fractioning = Just '.'
1793 , Amount.Style.precision = 12
1794 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
1799 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
1800 ((Amount.Write.amount_length
1802 { Amount.quantity = Decimal 7 1234567890123456789
1803 , Amount.style = Amount.Style.nil
1804 { Amount.Style.fractioning = Just '.'
1805 , Amount.Style.precision = 7
1806 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1811 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
1812 ((Amount.Write.amount_length
1814 { Amount.quantity = Decimal 12 1234567890123456789
1815 , Amount.style = Amount.Style.nil
1816 { Amount.Style.fractioning = Just '.'
1817 , Amount.Style.precision = 12
1818 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1823 , "1000000.000,00,0,0,0,0,0,0,0 @ prec=12" ~:
1824 ((Amount.Write.amount_length
1826 { Amount.quantity = Decimal 12 1000000000000000000
1827 , Amount.style = Amount.Style.nil
1828 { Amount.Style.fractioning = Just '.'
1829 , Amount.Style.precision = 12
1830 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
1836 ((Amount.Write.amount_length $
1838 { Amount.quantity = Decimal 0 999
1839 , Amount.style = Amount.Style.nil
1840 { Amount.Style.precision = 0
1845 , "1000 @ prec=0" ~:
1846 ((Amount.Write.amount_length $
1848 { Amount.quantity = Decimal 0 1000
1849 , Amount.style = Amount.Style.nil
1850 { Amount.Style.precision = 0
1855 , "10,00€ @ prec=2" ~:
1856 ((Amount.Write.amount_length $ Amount.eur 10)
1862 , "Date" ~: TestList
1863 [ "Read" ~: TestList
1864 [ "date" ~: TestList
1866 (Data.Either.rights $
1867 [P.runParser_with_Error
1868 (Date.Read.date id Nothing <* P.eof)
1869 () "" ("2000/01/01"::Text)])
1871 [ Time.zonedTimeToUTC $
1874 (Time.fromGregorian 2000 01 01)
1875 (Time.TimeOfDay 0 0 0))
1877 , "2000/01/01 some text" ~:
1878 (Data.Either.rights $
1879 [P.runParser_with_Error
1880 (Date.Read.date id Nothing)
1881 () "" ("2000/01/01 some text"::Text)])
1883 [ Time.zonedTimeToUTC $
1886 (Time.fromGregorian 2000 01 01)
1887 (Time.TimeOfDay 0 0 0))
1889 , "2000/01/01_12:34" ~:
1890 (Data.Either.rights $
1891 [P.runParser_with_Error
1892 (Date.Read.date id Nothing <* P.eof)
1893 () "" ("2000/01/01_12:34"::Text)])
1895 [ Time.zonedTimeToUTC $
1898 (Time.fromGregorian 2000 01 01)
1899 (Time.TimeOfDay 12 34 0))
1901 , "2000/01/01_12:34:56" ~:
1902 (Data.Either.rights $
1903 [P.runParser_with_Error
1904 (Date.Read.date id Nothing <* P.eof)
1905 () "" ("2000/01/01_12:34:56"::Text)])
1907 [ Time.zonedTimeToUTC $
1910 (Time.fromGregorian 2000 01 01)
1911 (Time.TimeOfDay 12 34 56))
1913 , "2000/01/01_12:34CET" ~:
1914 (Data.Either.rights $
1915 [P.runParser_with_Error
1916 (Date.Read.date id Nothing <* P.eof)
1917 () "" ("2000/01/01_12:34CET"::Text)])
1919 [ Time.zonedTimeToUTC $
1922 (Time.fromGregorian 2000 01 01)
1923 (Time.TimeOfDay 12 34 0))
1924 (Time.TimeZone 60 True "CET")]
1925 , "2000/01/01_12:34+0130" ~:
1926 (Data.Either.rights $
1927 [P.runParser_with_Error
1928 (Date.Read.date id Nothing <* P.eof)
1929 () "" ("2000/01/01_12:34+0130"::Text)])
1931 [ Time.zonedTimeToUTC $
1934 (Time.fromGregorian 2000 01 01)
1935 (Time.TimeOfDay 12 34 0))
1936 (Time.TimeZone 90 False "+0130")]
1937 , "2000/01/01_12:34:56CET" ~:
1938 (Data.Either.rights $
1939 [P.runParser_with_Error
1940 (Date.Read.date id Nothing <* P.eof)
1941 () "" ("2000/01/01_12:34:56CET"::Text)])
1943 [ Time.zonedTimeToUTC $
1946 (Time.fromGregorian 2000 01 01)
1947 (Time.TimeOfDay 12 34 56))
1948 (Time.TimeZone 60 True "CET")]
1950 (Data.Either.rights $
1951 [P.runParser_with_Error
1952 (Date.Read.date id Nothing <* P.eof)
1953 () "" ("2001/02/29"::Text)])
1957 (Data.Either.rights $
1958 [P.runParser_with_Error
1959 (Date.Read.date id (Just 2000) <* P.eof)
1960 () "" ("01/01"::Text)])
1962 [ Time.zonedTimeToUTC $
1965 (Time.fromGregorian 2000 01 01)
1966 (Time.TimeOfDay 0 0 0))
1970 , "Write" ~: TestList
1971 [ "date" ~: TestList
1973 ((Format.Ledger.Write.show
1974 Format.Ledger.Write.Style
1975 { Format.Ledger.Write.style_color=False
1976 , Format.Ledger.Write.style_align=True
1982 , "2000/01/01_12:34:51CET" ~:
1983 (Format.Ledger.Write.show
1984 Format.Ledger.Write.Style
1985 { Format.Ledger.Write.style_color=False
1986 , Format.Ledger.Write.style_align=True
1989 Time.zonedTimeToUTC $
1992 (Time.fromGregorian 2000 01 01)
1993 (Time.TimeOfDay 12 34 51))
1994 (Time.TimeZone 60 False "CET"))
1996 "2000/01/01_11:34:51"
1997 , "2000/01/01_12:34:51+0100" ~:
1998 (Format.Ledger.Write.show
1999 Format.Ledger.Write.Style
2000 { Format.Ledger.Write.style_color=False
2001 , Format.Ledger.Write.style_align=True
2004 Time.zonedTimeToUTC $
2007 (Time.fromGregorian 2000 01 01)
2008 (Time.TimeOfDay 12 34 51))
2009 (Time.TimeZone 60 False ""))
2011 "2000/01/01_11:34:51"
2012 , "2000/01/01_01:02:03" ~:
2013 (Format.Ledger.Write.show
2014 Format.Ledger.Write.Style
2015 { Format.Ledger.Write.style_color=False
2016 , Format.Ledger.Write.style_align=True
2019 Time.zonedTimeToUTC $
2022 (Time.fromGregorian 2000 01 01)
2023 (Time.TimeOfDay 1 2 3))
2026 "2000/01/01_01:02:03"
2028 (Format.Ledger.Write.show
2029 Format.Ledger.Write.Style
2030 { Format.Ledger.Write.style_color=False
2031 , Format.Ledger.Write.style_align=True
2034 Time.zonedTimeToUTC $
2037 (Time.fromGregorian 0 01 01)
2038 (Time.TimeOfDay 1 2 0))
2043 (Format.Ledger.Write.show
2044 Format.Ledger.Write.Style
2045 { Format.Ledger.Write.style_color=False
2046 , Format.Ledger.Write.style_align=True
2049 Time.zonedTimeToUTC $
2052 (Time.fromGregorian 0 01 01)
2053 (Time.TimeOfDay 1 0 0))
2058 (Format.Ledger.Write.show
2059 Format.Ledger.Write.Style
2060 { Format.Ledger.Write.style_color=False
2061 , Format.Ledger.Write.style_align=True
2064 Time.zonedTimeToUTC $
2067 (Time.fromGregorian 0 01 01)
2068 (Time.TimeOfDay 0 1 0))
2073 (Format.Ledger.Write.show
2074 Format.Ledger.Write.Style
2075 { Format.Ledger.Write.style_color=False
2076 , Format.Ledger.Write.style_align=True
2079 Time.zonedTimeToUTC $
2082 (Time.fromGregorian 0 01 01)
2083 (Time.TimeOfDay 0 0 0))
2090 , "Filter" ~: TestList
2091 [ "test" ~: TestList
2092 [ "Filter_Path" ~: TestList
2095 (Filter.Filter_Path Filter.Eq
2096 [ Filter.Filter_Path_Section_Text
2097 (Filter.Filter_Text_Exact "A")
2099 (("A":|[]::Account))
2102 (Filter.Filter_Path Filter.Eq
2103 [ Filter.Filter_Path_Section_Any
2105 (("A":|[]::Account))
2108 (Filter.Filter_Path Filter.Eq
2109 [ Filter.Filter_Path_Section_Many
2111 (("A":|[]::Account))
2114 (Filter.Filter_Path Filter.Eq
2115 [ Filter.Filter_Path_Section_Many
2116 , Filter.Filter_Path_Section_Text
2117 (Filter.Filter_Text_Exact "A")
2119 (("A":|[]::Account))
2122 (Filter.Filter_Path Filter.Eq
2123 [ Filter.Filter_Path_Section_Text
2124 (Filter.Filter_Text_Exact "A")
2125 , Filter.Filter_Path_Section_Many
2127 (("A":|[]::Account))
2130 (Filter.Filter_Path Filter.Eq
2131 [ Filter.Filter_Path_Section_Text
2132 (Filter.Filter_Text_Exact "A")
2133 , Filter.Filter_Path_Section_Many
2135 (("A":|"B":[]::Account))
2138 (Filter.Filter_Path Filter.Eq
2139 [ Filter.Filter_Path_Section_Text
2140 (Filter.Filter_Text_Exact "A")
2141 , Filter.Filter_Path_Section_Text
2142 (Filter.Filter_Text_Exact "B")
2144 (("A":|"B":[]::Account))
2147 (Filter.Filter_Path Filter.Eq
2148 [ Filter.Filter_Path_Section_Text
2149 (Filter.Filter_Text_Exact "A")
2150 , Filter.Filter_Path_Section_Many
2151 , Filter.Filter_Path_Section_Many
2152 , Filter.Filter_Path_Section_Text
2153 (Filter.Filter_Text_Exact "B")
2155 (("A":|"B":[]::Account))
2158 (Filter.Filter_Path Filter.Eq
2159 [ Filter.Filter_Path_Section_Many
2160 , Filter.Filter_Path_Section_Text
2161 (Filter.Filter_Text_Exact "B")
2162 , Filter.Filter_Path_Section_Many
2164 (("A":|"B":"C":[]::Account))
2167 (Filter.Filter_Path Filter.Eq
2168 [ Filter.Filter_Path_Section_Many
2169 , Filter.Filter_Path_Section_Text
2170 (Filter.Filter_Text_Exact "C")
2172 (("A":|"B":"C":[]::Account))
2173 , "<A:B:C::D A:B" ~?
2175 (Filter.Filter_Path Filter.Lt
2176 [ Filter.Filter_Path_Section_Text
2177 (Filter.Filter_Text_Exact "A")
2178 , Filter.Filter_Path_Section_Text
2179 (Filter.Filter_Text_Exact "B")
2180 , Filter.Filter_Path_Section_Text
2181 (Filter.Filter_Text_Exact "C")
2182 , Filter.Filter_Path_Section_Many
2183 , Filter.Filter_Path_Section_Text
2184 (Filter.Filter_Text_Exact "D")
2186 (("A":|"B":[]::Account))
2187 , ">A:B:C::D A:B:C:CC:CCC:D:E" ~?
2189 (Filter.Filter_Path Filter.Gt
2190 [ Filter.Filter_Path_Section_Text
2191 (Filter.Filter_Text_Exact "A")
2192 , Filter.Filter_Path_Section_Text
2193 (Filter.Filter_Text_Exact "B")
2194 , Filter.Filter_Path_Section_Text
2195 (Filter.Filter_Text_Exact "C")
2196 , Filter.Filter_Path_Section_Many
2197 , Filter.Filter_Path_Section_Text
2198 (Filter.Filter_Text_Exact "D")
2200 (("A":|"B":"C":"CC":"CCC":"D":"E":[]::Account))
2202 , "Filter_Bool" ~: TestList
2205 (Filter.Any::Filter.Filter_Bool Filter.Filter_Account)
2206 (("A":|[]::Account))
2208 , "Filter_Ord" ~: TestList
2211 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer))
2212 (fromJust $ (Lib.Interval.<=..<=) 1 2)
2215 (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer))
2216 (fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
2217 , "not (1 < (0, 2))" ~?
2219 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer))
2220 (fromJust $ (Lib.Interval.<=..<=) 0 2))
2223 , "Read" ~: TestList
2224 [ "filter_account" ~: TestList
2226 (Data.Either.rights $
2228 (Filter.Read.filter_account <* P.eof)
2231 map (Filter.Filter_Posting_Type_Any,)
2232 [ Filter.Filter_Path Filter.Eq
2233 [ Filter.Filter_Path_Section_Any ]
2236 (Data.Either.rights $
2238 (Filter.Read.filter_account <* P.eof)
2241 map (Filter.Filter_Posting_Type_Any,)
2242 [ Filter.Filter_Path Filter.Eq
2243 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A") ]
2246 (Data.Either.rights $
2248 (Filter.Read.filter_account <* P.eof)
2249 () "" ("AA"::Text)])
2251 map (Filter.Filter_Posting_Type_Any,)
2252 [ Filter.Filter_Path Filter.Eq
2253 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "AA") ]
2256 (Data.Either.rights $
2258 (Filter.Read.filter_account <* P.eof)
2259 () "" ("::A"::Text)])
2261 map (Filter.Filter_Posting_Type_Any,)
2262 [ Filter.Filter_Path Filter.Eq
2263 [ Filter.Filter_Path_Section_Many
2264 , Filter.Filter_Path_Section_Many
2265 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2269 (Data.Either.rights $
2271 (Filter.Read.filter_account <* P.eof)
2272 () "" (":A"::Text)])
2274 map (Filter.Filter_Posting_Type_Any,)
2275 [ Filter.Filter_Path Filter.Eq
2276 [ Filter.Filter_Path_Section_Many
2277 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2281 (Data.Either.rights $
2283 (Filter.Read.filter_account <* P.eof)
2284 () "" ("A:"::Text)])
2286 map (Filter.Filter_Posting_Type_Any,)
2287 [ Filter.Filter_Path Filter.Eq
2288 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2289 , Filter.Filter_Path_Section_Many
2293 (Data.Either.rights $
2295 (Filter.Read.filter_account <* P.eof)
2296 () "" ("A::"::Text)])
2298 map (Filter.Filter_Posting_Type_Any,)
2299 [ Filter.Filter_Path Filter.Eq
2300 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2301 , Filter.Filter_Path_Section_Many
2302 , Filter.Filter_Path_Section_Many
2306 (Data.Either.rights $
2308 (Filter.Read.filter_account <* P.eof)
2309 () "" ("A:B"::Text)])
2311 map (Filter.Filter_Posting_Type_Any,)
2312 [ Filter.Filter_Path Filter.Eq
2313 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2314 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2318 (Data.Either.rights $
2320 (Filter.Read.filter_account <* P.eof)
2321 () "" ("A::B"::Text)])
2323 map (Filter.Filter_Posting_Type_Any,)
2324 [ Filter.Filter_Path Filter.Eq
2325 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2326 , Filter.Filter_Path_Section_Many
2327 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2331 (Data.Either.rights $
2333 (Filter.Read.filter_account <* P.eof)
2334 () "" ("A:::B"::Text)])
2336 map (Filter.Filter_Posting_Type_Any,)
2337 [ Filter.Filter_Path Filter.Eq
2338 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2339 , Filter.Filter_Path_Section_Many
2340 , Filter.Filter_Path_Section_Many
2341 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2345 (Data.Either.rights $
2347 (Filter.Read.filter_account <* P.char ' ' <* P.eof)
2348 () "" ("A: "::Text)])
2350 map (Filter.Filter_Posting_Type_Any,)
2351 [ Filter.Filter_Path Filter.Eq
2352 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2353 , Filter.Filter_Path_Section_Many
2357 (Data.Either.rights $
2359 (Filter.Read.filter_account <* P.eof)
2360 () "" ("<=A:B"::Text)])
2362 map (Filter.Filter_Posting_Type_Any,)
2363 [ Filter.Filter_Path Filter.Le
2364 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2365 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2369 (Data.Either.rights $
2371 (Filter.Read.filter_account <* P.eof)
2372 () "" (">=A:B"::Text)])
2374 map (Filter.Filter_Posting_Type_Any,)
2375 [ Filter.Filter_Path Filter.Ge
2376 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2377 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2381 (Data.Either.rights $
2383 (Filter.Read.filter_account <* P.eof)
2384 () "" ("<A:B"::Text)])
2386 map (Filter.Filter_Posting_Type_Any,)
2387 [ Filter.Filter_Path Filter.Lt
2388 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2389 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2393 (Data.Either.rights $
2395 (Filter.Read.filter_account <* P.eof)
2396 () "" (">A:B"::Text)])
2398 map (Filter.Filter_Posting_Type_Any,)
2399 [ Filter.Filter_Path Filter.Gt
2400 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
2401 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
2405 , "filter_bool" ~: TestList
2407 (Data.Either.rights $
2409 (Filter.Read.filter_bool
2410 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2412 () "" ("( E )"::Text)])
2414 [ Filter.And (Filter.Bool True) Filter.Any
2417 (Data.Either.rights $
2419 (Filter.Read.filter_bool
2420 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2422 () "" ("( ( E ) )"::Text)])
2424 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
2426 , "( E ) & ( E )" ~:
2427 (Data.Either.rights $
2429 (Filter.Read.filter_bool
2430 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2432 () "" ("( E ) & ( E )"::Text)])
2435 (Filter.And (Filter.Bool True) Filter.Any)
2436 (Filter.And (Filter.Bool True) Filter.Any)
2438 , "( E ) + ( E )" ~:
2439 (Data.Either.rights $
2441 (Filter.Read.filter_bool
2442 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2444 () "" ("( E ) + ( E )"::Text)])
2447 (Filter.And (Filter.Bool True) Filter.Any)
2448 (Filter.And (Filter.Bool True) Filter.Any)
2450 , "( E ) - ( E )" ~:
2451 (Data.Either.rights $
2453 (Filter.Read.filter_bool
2454 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2456 () "" ("( E ) - ( E )"::Text)])
2459 (Filter.And (Filter.Bool True) Filter.Any)
2460 (Filter.Not (Filter.And (Filter.Bool True) Filter.Any))
2463 (Data.Either.rights $
2465 (Filter.Read.filter_bool
2466 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2468 () "" ("(- E )"::Text)])
2470 [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any
2475 , "Balance" ~: TestList
2476 [ "balance" ~: TestList
2477 [ "[A+$1] = A+$1 & $+1" ~:
2479 (Format.Ledger.posting ("A":|[]))
2480 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2485 { Balance.balance_by_account =
2486 Lib.TreeMap.from_List const $
2487 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2488 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2489 , Balance.balance_by_unit =
2490 Balance.Balance_by_Unit $
2492 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2494 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2495 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2500 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
2504 [ (Format.Ledger.posting ("A":|[]))
2505 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2507 , (Format.Ledger.posting ("A":|[]))
2508 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2513 { Balance.balance_by_account =
2514 Lib.TreeMap.from_List const $
2516 , Balance.Account_Sum $
2517 Data.Map.fromListWith const $
2518 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2524 , Balance.balance_by_unit =
2525 Balance.Balance_by_Unit $
2527 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2529 { Balance.unit_sum_amount = Amount.Sum_Both
2532 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2537 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
2541 [ (Format.Ledger.posting ("A":|[]))
2542 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2544 , (Format.Ledger.posting ("A":|[]))
2545 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ]
2550 { Balance.balance_by_account =
2551 Lib.TreeMap.from_List const $
2552 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2553 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
2554 , Balance.balance_by_unit =
2555 Balance.Balance_by_Unit $
2557 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2559 { Balance.unit_sum_amount = Amount.Sum_Positive (Amount.usd $ 1)
2560 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2564 { Balance.unit_sum_amount = Amount.Sum_Negative (Amount.eur $ -1)
2565 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2570 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
2574 [ (Format.Ledger.posting ("A":|[]))
2575 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2577 , (Format.Ledger.posting ("B":|[]))
2578 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2583 { Balance.balance_by_account =
2584 Lib.TreeMap.from_List const $
2585 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2586 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2587 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
2589 , Balance.balance_by_unit =
2590 Balance.Balance_by_Unit $
2592 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2594 { Balance.unit_sum_amount = Amount.Sum_Both
2597 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2606 [ (Format.Ledger.posting ("A":|[]))
2607 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2609 , (Format.Ledger.posting ("B":|[]))
2610 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2615 { Balance.balance_by_account =
2616 Lib.TreeMap.from_List const $
2617 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2618 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2619 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
2621 , Balance.balance_by_unit =
2622 Balance.Balance_by_Unit $
2624 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2626 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2627 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2632 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
2636 [ (Format.Ledger.posting ("A":|[]))
2637 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
2639 , (Format.Ledger.posting ("A":|[]))
2640 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
2645 { Balance.balance_by_account =
2646 Lib.TreeMap.from_List const $
2648 , Balance.Account_Sum $
2649 Data.Map.fromListWith const $
2650 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2651 [ Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2652 , Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2656 , Balance.balance_by_unit =
2657 Balance.Balance_by_Unit $
2659 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2661 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2662 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2666 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2667 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2672 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
2676 [ (Format.Ledger.posting ("A":|[]))
2677 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
2679 , (Format.Ledger.posting ("B":|[]))
2680 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
2685 { Balance.balance_by_account =
2686 Lib.TreeMap.from_List const $
2687 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2688 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
2689 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
2691 , Balance.balance_by_unit =
2692 Balance.Balance_by_Unit $
2694 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2696 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.usd $ -1) (Amount.usd $ 1)
2697 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2701 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.eur $ -2) (Amount.eur $ 2)
2702 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2706 { Balance.unit_sum_amount = Amount.Sum_Both (Amount.gbp $ -3) (Amount.gbp $ 3)
2707 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2713 , "union" ~: TestList
2714 [ "empty empty = empty" ~:
2715 Balance.union Balance.empty Balance.empty
2717 (Balance.empty::Balance.Balance Amount)
2718 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
2721 { Balance.balance_by_account =
2722 Lib.TreeMap.from_List const $
2723 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2724 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2725 , Balance.balance_by_unit =
2726 Balance.Balance_by_Unit $
2728 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2730 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2731 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2737 { Balance.balance_by_account =
2738 Lib.TreeMap.from_List const $
2739 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2740 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2741 , Balance.balance_by_unit =
2742 Balance.Balance_by_Unit $
2744 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2746 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2747 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2754 { Balance.balance_by_account =
2755 Lib.TreeMap.from_List const $
2756 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2757 [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
2758 , Balance.balance_by_unit =
2759 Balance.Balance_by_Unit $
2761 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2763 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2764 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2769 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
2772 { Balance.balance_by_account =
2773 Lib.TreeMap.from_List const $
2774 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2775 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2776 , Balance.balance_by_unit =
2777 Balance.Balance_by_Unit $
2779 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2781 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2782 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2788 { Balance.balance_by_account =
2789 Lib.TreeMap.from_List const $
2790 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2791 [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2792 , Balance.balance_by_unit =
2793 Balance.Balance_by_Unit $
2795 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2797 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2798 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2805 { Balance.balance_by_account =
2806 Lib.TreeMap.from_List const $
2807 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2808 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2809 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2810 , Balance.balance_by_unit =
2811 Balance.Balance_by_Unit $
2813 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2815 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2816 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2821 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
2824 { Balance.balance_by_account =
2825 Lib.TreeMap.from_List const $
2826 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2827 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
2828 , Balance.balance_by_unit =
2829 Balance.Balance_by_Unit $
2831 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2833 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2834 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2840 { Balance.balance_by_account =
2841 Lib.TreeMap.from_List const $
2842 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2843 [ ("B":|[], Amount.from_List [ Amount.eur $ 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.eur $ 1
2850 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2857 { Balance.balance_by_account =
2858 Lib.TreeMap.from_List const $
2859 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2860 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
2861 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
2862 , Balance.balance_by_unit =
2863 Balance.Balance_by_Unit $
2865 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2867 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2868 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2872 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2873 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2879 , "expanded" ~: TestList
2884 (Lib.TreeMap.empty::Balance.Expanded Amount)
2887 (Lib.TreeMap.from_List const $
2888 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2889 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
2891 (Lib.TreeMap.from_List const $
2892 [ ("A":|[], Balance.Account_Sum_Expanded
2893 { Balance.inclusive =
2894 Balance.Account_Sum $
2895 Data.Map.map Amount.sum $
2896 Amount.from_List [ Amount.usd $ 1 ]
2897 , Balance.exclusive =
2898 Balance.Account_Sum $
2899 Data.Map.map Amount.sum $
2900 Amount.from_List [ Amount.usd $ 1 ]
2903 , "A/A+$1 = A+$1 A/A+$1" ~:
2905 (Lib.TreeMap.from_List const $
2906 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2907 [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
2909 (Lib.TreeMap.from_List const
2910 [ ("A":|[], Balance.Account_Sum_Expanded
2911 { Balance.inclusive =
2912 Balance.Account_Sum $
2913 Data.Map.map Amount.sum $
2914 Amount.from_List [ Amount.usd $ 1 ]
2915 , Balance.exclusive =
2916 Balance.Account_Sum $
2917 Data.Map.map Amount.sum $
2920 , ("A":|["A"], Balance.Account_Sum_Expanded
2921 { Balance.inclusive =
2922 Balance.Account_Sum $
2923 Data.Map.map Amount.sum $
2924 Amount.from_List [ Amount.usd $ 1 ]
2925 , Balance.exclusive =
2926 Balance.Account_Sum $
2927 Data.Map.map Amount.sum $
2928 Amount.from_List [ Amount.usd $ 1 ]
2931 , "A/B+$1 = A+$1 A/B+$1" ~:
2933 (Lib.TreeMap.from_List const $
2934 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2935 [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
2937 (Lib.TreeMap.from_List const
2938 [ ("A":|[], Balance.Account_Sum_Expanded
2939 { Balance.inclusive =
2940 Balance.Account_Sum $
2941 Data.Map.map Amount.sum $
2942 Amount.from_List [ Amount.usd $ 1 ]
2943 , Balance.exclusive =
2944 Balance.Account_Sum $
2945 Data.Map.map Amount.sum $
2948 , ("A":|["B"], Balance.Account_Sum_Expanded
2949 { Balance.inclusive =
2950 Balance.Account_Sum $
2951 Data.Map.map Amount.sum $
2952 Amount.from_List [ Amount.usd $ 1 ]
2953 , Balance.exclusive =
2954 Balance.Account_Sum $
2955 Data.Map.map Amount.sum $
2956 Amount.from_List [ Amount.usd $ 1 ]
2959 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
2961 (Lib.TreeMap.from_List const $
2962 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
2963 [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
2965 (Lib.TreeMap.from_List const $
2966 [ ("A":|[], Balance.Account_Sum_Expanded
2967 { Balance.inclusive =
2968 Balance.Account_Sum $
2969 Data.Map.map Amount.sum $
2970 Amount.from_List [ Amount.usd $ 1 ]
2971 , Balance.exclusive =
2972 Balance.Account_Sum $
2973 Data.Map.map Amount.sum $
2976 , ("A":|["B"], Balance.Account_Sum_Expanded
2977 { Balance.inclusive =
2978 Balance.Account_Sum $
2979 Data.Map.map Amount.sum $
2980 Amount.from_List [ Amount.usd $ 1 ]
2981 , Balance.exclusive =
2982 Balance.Account_Sum $
2983 Data.Map.map Amount.sum $
2986 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
2987 { Balance.inclusive =
2988 Balance.Account_Sum $
2989 Data.Map.map Amount.sum $
2990 Amount.from_List [ Amount.usd $ 1 ]
2991 , Balance.exclusive =
2992 Balance.Account_Sum $
2993 Data.Map.map Amount.sum $
2994 Amount.from_List [ Amount.usd $ 1 ]
2997 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
2999 (Lib.TreeMap.from_List const $
3000 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3001 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3002 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
3005 (Lib.TreeMap.from_List const
3006 [ ("A":|[], Balance.Account_Sum_Expanded
3007 { Balance.inclusive =
3008 Balance.Account_Sum $
3009 Data.Map.map Amount.sum $
3010 Amount.from_List [ Amount.usd $ 2 ]
3011 , Balance.exclusive =
3012 Balance.Account_Sum $
3013 Data.Map.map Amount.sum $
3014 Amount.from_List [ Amount.usd $ 1 ]
3016 , ("A":|["B"], Balance.Account_Sum_Expanded
3017 { Balance.inclusive =
3018 Balance.Account_Sum $
3019 Data.Map.map Amount.sum $
3020 Amount.from_List [ Amount.usd $ 1 ]
3021 , Balance.exclusive =
3022 Balance.Account_Sum $
3023 Data.Map.map Amount.sum $
3024 Amount.from_List [ Amount.usd $ 1 ]
3027 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
3029 (Lib.TreeMap.from_List const $
3030 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3031 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3032 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
3033 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
3036 (Lib.TreeMap.from_List const
3037 [ ("A":|[], Balance.Account_Sum_Expanded
3038 { Balance.inclusive =
3039 Balance.Account_Sum $
3040 Data.Map.map Amount.sum $
3041 Amount.from_List [ Amount.usd $ 3 ]
3042 , Balance.exclusive =
3043 Balance.Account_Sum $
3044 Data.Map.map Amount.sum $
3045 Amount.from_List [ Amount.usd $ 1 ]
3047 , ("A":|["B"], Balance.Account_Sum_Expanded
3048 { Balance.inclusive =
3049 Balance.Account_Sum $
3050 Data.Map.map Amount.sum $
3051 Amount.from_List [ Amount.usd $ 2 ]
3052 , Balance.exclusive =
3053 Balance.Account_Sum $
3054 Data.Map.map Amount.sum $
3055 Amount.from_List [ Amount.usd $ 1 ]
3057 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
3058 { Balance.inclusive =
3059 Balance.Account_Sum $
3060 Data.Map.map Amount.sum $
3061 Amount.from_List [ Amount.usd $ 1 ]
3062 , Balance.exclusive =
3063 Balance.Account_Sum $
3064 Data.Map.map Amount.sum $
3065 Amount.from_List [ Amount.usd $ 1 ]
3068 , "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" ~:
3070 (Lib.TreeMap.from_List const $
3071 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3072 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3073 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
3074 , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
3075 , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
3078 (Lib.TreeMap.from_List const
3079 [ ("A":|[], Balance.Account_Sum_Expanded
3080 { Balance.inclusive =
3081 Balance.Account_Sum $
3082 Data.Map.map Amount.sum $
3083 Amount.from_List [ Amount.usd $ 4 ]
3084 , Balance.exclusive =
3085 Balance.Account_Sum $
3086 Data.Map.map Amount.sum $
3087 Amount.from_List [ Amount.usd $ 1 ]
3089 , ("A":|["B"], Balance.Account_Sum_Expanded
3090 { Balance.inclusive =
3091 Balance.Account_Sum $
3092 Data.Map.map Amount.sum $
3093 Amount.from_List [ Amount.usd $ 3 ]
3094 , Balance.exclusive =
3095 Balance.Account_Sum $
3096 Data.Map.map Amount.sum $
3097 Amount.from_List [ Amount.usd $ 1 ]
3099 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
3100 { Balance.inclusive =
3101 Balance.Account_Sum $
3102 Data.Map.map Amount.sum $
3103 Amount.from_List [ Amount.usd $ 2 ]
3104 , Balance.exclusive =
3105 Balance.Account_Sum $
3106 Data.Map.map Amount.sum $
3107 Amount.from_List [ Amount.usd $ 1 ]
3109 , ("A":|["B", "C", "D"], Balance.Account_Sum_Expanded
3110 { Balance.inclusive =
3111 Balance.Account_Sum $
3112 Data.Map.map Amount.sum $
3113 Amount.from_List [ Amount.usd $ 1 ]
3114 , Balance.exclusive =
3115 Balance.Account_Sum $
3116 Data.Map.map Amount.sum $
3117 Amount.from_List [ Amount.usd $ 1 ]
3120 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
3122 (Lib.TreeMap.from_List const $
3123 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3124 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3125 , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
3126 , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
3127 , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ])
3130 (Lib.TreeMap.from_List const
3131 [ ("A":|[], Balance.Account_Sum_Expanded
3132 { Balance.inclusive =
3133 Balance.Account_Sum $
3134 Data.Map.map Amount.sum $
3135 Amount.from_List [ Amount.usd $ 3 ]
3136 , Balance.exclusive =
3137 Balance.Account_Sum $
3138 Data.Map.map Amount.sum $
3139 Amount.from_List [ Amount.usd $ 1 ]
3141 , ("A":|["B"], Balance.Account_Sum_Expanded
3142 { Balance.inclusive =
3143 Balance.Account_Sum $
3144 Data.Map.map Amount.sum $
3145 Amount.from_List [ Amount.usd $ 1 ]
3146 , Balance.exclusive =
3147 Balance.Account_Sum $
3148 Data.Map.map Amount.sum $
3149 Amount.from_List [ Amount.usd $ 1 ]
3151 , ("A":|["BB"], Balance.Account_Sum_Expanded
3152 { Balance.inclusive =
3153 Balance.Account_Sum $
3154 Data.Map.map Amount.sum $
3155 Amount.from_List [ Amount.usd $ 1 ]
3156 , Balance.exclusive =
3157 Balance.Account_Sum $
3158 Data.Map.map Amount.sum $
3159 Amount.from_List [ Amount.usd $ 1 ]
3161 , ("AA":|[], Balance.Account_Sum_Expanded
3162 { Balance.inclusive =
3163 Balance.Account_Sum $
3164 Data.Map.map Amount.sum $
3165 Amount.from_List [ Amount.usd $ 1 ]
3166 , Balance.exclusive =
3167 Balance.Account_Sum $
3168 Data.Map.map Amount.sum $
3171 , ("AA":|["B"], Balance.Account_Sum_Expanded
3172 { Balance.inclusive =
3173 Balance.Account_Sum $
3174 Data.Map.map Amount.sum $
3175 Amount.from_List [ Amount.usd $ 1 ]
3176 , Balance.exclusive =
3177 Balance.Account_Sum $
3178 Data.Map.map Amount.sum $
3179 Amount.from_List [ Amount.usd $ 1 ]
3183 , "deviation" ~: TestList
3185 (Balance.deviation $
3187 { Balance.balance_by_account =
3188 Lib.TreeMap.from_List const $
3189 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3190 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3191 , ("B":|[], Amount.from_List [])
3193 , Balance.balance_by_unit =
3194 Balance.Balance_by_Unit $
3196 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3198 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3199 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3205 (Balance.Deviation $
3206 Balance.Balance_by_Unit $
3208 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3210 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3211 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3215 , "{A+$1 B+$1, $2}" ~:
3216 (Balance.deviation $
3218 { Balance.balance_by_account =
3219 Lib.TreeMap.from_List const $
3220 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3221 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3222 , ("B":|[], Amount.from_List [ Amount.usd $ 1 ])
3224 , Balance.balance_by_unit =
3225 Balance.Balance_by_Unit $
3227 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3229 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3230 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3238 (Balance.Deviation $
3239 Balance.Balance_by_Unit $
3241 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3243 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3244 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3250 , "is_equilibrium_inferrable" ~: TestList
3251 [ "nil" ~: TestCase $
3253 Balance.is_equilibrium_inferrable $
3255 (Balance.empty::Balance.Balance Amount.Amount)
3256 , "{A+$0, $+0}" ~: TestCase $
3258 Balance.is_equilibrium_inferrable $
3261 { Balance.balance_by_account =
3262 Lib.TreeMap.from_List const $
3263 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3264 [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
3266 , Balance.balance_by_unit =
3267 Balance.Balance_by_Unit $
3269 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3271 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3272 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3277 , "{A+$1, $+1}" ~: TestCase $
3279 Balance.is_equilibrium_inferrable $
3282 { Balance.balance_by_account =
3283 Lib.TreeMap.from_List const $
3284 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3285 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3287 , Balance.balance_by_unit =
3288 Balance.Balance_by_Unit $
3290 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3292 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3293 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3298 , "{A+$0+€0, $0 €+0}" ~: TestCase $
3300 Balance.is_equilibrium_inferrable $
3303 { Balance.balance_by_account =
3304 Lib.TreeMap.from_List const $
3305 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3306 [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
3308 , Balance.balance_by_unit =
3309 Balance.Balance_by_Unit $
3311 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3313 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3314 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3318 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3319 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3324 , "{A+$1, B-$1, $+0}" ~: TestCase $
3326 Balance.is_equilibrium_inferrable $
3329 { Balance.balance_by_account =
3330 Lib.TreeMap.from_List const $
3331 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3332 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3333 , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
3335 , Balance.balance_by_unit =
3336 Balance.Balance_by_Unit $
3338 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3340 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3341 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3346 , "{A+$1 B, $+1}" ~: TestCase $
3348 Balance.is_equilibrium_inferrable $
3351 { Balance.balance_by_account =
3352 Lib.TreeMap.from_List const $
3353 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3354 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3355 , ("B":|[], Amount.from_List [])
3357 , Balance.balance_by_unit =
3358 Balance.Balance_by_Unit $
3360 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3362 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3363 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3368 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
3370 Balance.is_equilibrium_inferrable $
3373 { Balance.balance_by_account =
3374 Lib.TreeMap.from_List const $
3375 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3376 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3377 , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
3379 , Balance.balance_by_unit =
3380 Balance.Balance_by_Unit $
3382 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3384 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3385 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3389 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3390 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3395 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
3397 Balance.is_equilibrium_inferrable $
3400 { Balance.balance_by_account =
3401 Lib.TreeMap.from_List const $
3402 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3403 [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
3404 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
3406 , Balance.balance_by_unit =
3407 Balance.Balance_by_Unit $
3409 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3411 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3412 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3416 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3417 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3422 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
3424 Balance.is_equilibrium_inferrable $
3427 { Balance.balance_by_account =
3428 Lib.TreeMap.from_List const $
3429 Data.List.map (id *** Balance.Account_Sum . Data.Map.map Amount.sum) $
3430 [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
3431 , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
3433 , Balance.balance_by_unit =
3434 Balance.Balance_by_Unit $
3436 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3438 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3439 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3443 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3444 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3448 { Balance.unit_sum_amount = Amount.sum $ Amount.gbp $ 0
3449 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3455 , "infer_equilibrium" ~: TestList
3457 (snd $ Balance.infer_equilibrium $
3458 Format.Ledger.posting_by_Account
3459 [ (Format.Ledger.posting ("A":|[]))
3460 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3461 , (Format.Ledger.posting ("B":|[]))
3462 { Format.Ledger.posting_amounts=Amount.from_List [] }
3466 Format.Ledger.posting_by_Account
3467 [ (Format.Ledger.posting ("A":|[]))
3468 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3469 , (Format.Ledger.posting ("B":|[]))
3470 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ] }
3473 (snd $ Balance.infer_equilibrium $
3474 Format.Ledger.posting_by_Account
3475 [ (Format.Ledger.posting ("A":|[]))
3476 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3477 , (Format.Ledger.posting ("B":|[]))
3478 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ] }
3482 Format.Ledger.posting_by_Account
3483 [ (Format.Ledger.posting ("A":|[]))
3484 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1] }
3485 , (Format.Ledger.posting ("B":|[]))
3486 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1, Amount.usd $ -1 ] }
3489 (snd $ Balance.infer_equilibrium $
3490 Format.Ledger.posting_by_Account
3491 [ (Format.Ledger.posting ("A":|[]))
3492 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3493 , (Format.Ledger.posting ("B":|[]))
3494 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3499 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3500 , Balance.unit_sum_accounts = Data.Map.fromList []}
3502 , "{A+$1 B-$1 B-1€}" ~:
3503 (snd $ Balance.infer_equilibrium $
3504 Format.Ledger.posting_by_Account
3505 [ (Format.Ledger.posting ("A":|[]))
3506 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ] }
3507 , (Format.Ledger.posting ("B":|[]))
3508 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
3512 Format.Ledger.posting_by_Account
3513 [ (Format.Ledger.posting ("A":|[]))
3514 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 1 ] }
3515 , (Format.Ledger.posting ("B":|[]))
3516 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -1 ] }
3520 , "Format" ~: TestList
3521 [ "Ledger" ~: TestList
3522 [ "Read" ~: TestList
3523 [ "posting_type" ~: TestList
3525 Format.Ledger.Read.posting_type
3528 (Posting.Posting_Type_Regular, "A":|[])
3530 Format.Ledger.Read.posting_type
3533 (Posting.Posting_Type_Regular, "(":|[])
3535 Format.Ledger.Read.posting_type
3538 (Posting.Posting_Type_Regular, ")":|[])
3540 Format.Ledger.Read.posting_type
3543 (Posting.Posting_Type_Regular, "()":|[])
3545 Format.Ledger.Read.posting_type
3548 (Posting.Posting_Type_Regular, "( )":|[])
3550 Format.Ledger.Read.posting_type
3553 (Posting.Posting_Type_Virtual, "A":|[])
3555 Format.Ledger.Read.posting_type
3558 (Posting.Posting_Type_Virtual, "A":|["B", "C"])
3560 Format.Ledger.Read.posting_type
3563 (Posting.Posting_Type_Regular, "A":|["B", "C"])
3565 Format.Ledger.Read.posting_type
3568 (Posting.Posting_Type_Regular, "(A)":|["B", "C"])
3570 Format.Ledger.Read.posting_type
3573 (Posting.Posting_Type_Regular, "A":|["(B)", "C"])
3575 Format.Ledger.Read.posting_type
3578 (Posting.Posting_Type_Regular, "A":|["B", "(C)"])
3580 Format.Ledger.Read.posting_type
3583 (Posting.Posting_Type_Regular, "[":|[])
3585 Format.Ledger.Read.posting_type
3588 (Posting.Posting_Type_Regular, "]":|[])
3590 Format.Ledger.Read.posting_type
3593 (Posting.Posting_Type_Regular, "[]":|[])
3595 Format.Ledger.Read.posting_type
3598 (Posting.Posting_Type_Regular, "[ ]":|[])
3600 Format.Ledger.Read.posting_type
3603 (Posting.Posting_Type_Virtual_Balanced, "A":|[])
3605 Format.Ledger.Read.posting_type
3608 (Posting.Posting_Type_Virtual_Balanced, "A":|["B", "C"])
3610 Format.Ledger.Read.posting_type
3613 (Posting.Posting_Type_Regular, "A":|["B", "C"])
3615 Format.Ledger.Read.posting_type
3618 (Posting.Posting_Type_Regular, "[A]":|["B", "C"])
3620 Format.Ledger.Read.posting_type
3623 (Posting.Posting_Type_Regular, "A":|["[B]", "C"])
3625 Format.Ledger.Read.posting_type
3628 (Posting.Posting_Type_Regular, "A":|["B", "[C]"])
3630 , "comment" ~: TestList
3631 [ "; some comment = Right \" some comment\"" ~:
3632 (Data.Either.rights $
3634 (Format.Ledger.Read.comment <* P.eof)
3635 () "" ("; some comment"::Text)])
3638 , "; some comment \\n = Right \" some comment \"" ~:
3639 (Data.Either.rights $
3641 (Format.Ledger.Read.comment <* P.newline <* P.eof)
3642 () "" ("; some comment \n"::Text)])
3644 [ " some comment " ]
3645 , "; some comment \\r\\n = Right \" some comment \"" ~:
3646 (Data.Either.rights $
3648 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
3649 () "" ("; some comment \r\n"::Text)])
3651 [ " some comment " ]
3653 , "comments" ~: TestList
3654 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
3655 (Data.Either.rights $
3657 (Format.Ledger.Read.comments <* P.eof)
3658 () "" ("; some comment\n ; some other comment"::Text)])
3660 [ [" some comment", " some other comment"] ]
3661 , "; some comment \\n = Right \" some comment \"" ~:
3662 (Data.Either.rights $
3664 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
3665 () "" ("; some comment \n"::Text)])
3667 [ [" some comment "] ]
3669 , "tag_value" ~: TestList
3671 (Data.Either.rights $
3673 (Format.Ledger.Read.tag_value <* P.eof)
3678 (Data.Either.rights $
3680 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
3681 () "" (",\n"::Text)])
3685 (Data.Either.rights $
3687 (Format.Ledger.Read.tag_value <* P.eof)
3688 () "" (",x"::Text)])
3692 (Data.Either.rights $
3694 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
3695 () "" (",x:"::Text)])
3699 (Data.Either.rights $
3701 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
3702 () "" ("v, v, n:"::Text)])
3708 (Data.Either.rights $
3710 (Format.Ledger.Read.tag <* P.eof)
3711 () "" ("Name:"::Text)])
3715 (Data.Either.rights $
3717 (Format.Ledger.Read.tag <* P.eof)
3718 () "" ("Name:Value"::Text)])
3720 [("Name":|[], "Value")]
3721 , "Name:Value\\n" ~:
3722 (Data.Either.rights $
3724 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
3725 () "" ("Name:Value\n"::Text)])
3727 [("Name":|[], "Value")]
3729 (Data.Either.rights $
3731 (Format.Ledger.Read.tag <* P.eof)
3732 () "" ("Name:Val ue"::Text)])
3734 [("Name":|[], "Val ue")]
3736 (Data.Either.rights $
3738 (Format.Ledger.Read.tag <* P.eof)
3739 () "" ("Name:,"::Text)])
3743 (Data.Either.rights $
3745 (Format.Ledger.Read.tag <* P.eof)
3746 () "" ("Name:Val,ue"::Text)])
3748 [("Name":|[], "Val,ue")]
3750 (Data.Either.rights $
3752 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
3753 () "" ("Name:Val,ue:"::Text)])
3755 [("Name":|[], "Val")]
3756 , "Name:Val,ue :" ~:
3757 (Data.Either.rights $
3759 (Format.Ledger.Read.tag <* P.eof)
3760 () "" ("Name:Val,ue :"::Text)])
3762 [("Name":|[], "Val,ue :")]
3764 , "tags" ~: TestList
3766 (Data.Either.rights $
3768 (Format.Ledger.Read.tags <* P.eof)
3769 () "" ("Name:"::Text)])
3772 [ ("Name":|[], [""])
3776 (Data.Either.rights $
3778 (Format.Ledger.Read.tags <* P.eof)
3779 () "" ("Name:,"::Text)])
3782 [ ("Name":|[], [","])
3786 (Data.Either.rights $
3788 (Format.Ledger.Read.tags <* P.eof)
3789 () "" ("Name:,Name:"::Text)])
3792 [ ("Name":|[], ["", ""])
3796 (Data.Either.rights $
3798 (Format.Ledger.Read.tags <* P.eof)
3799 () "" ("Name:,Name2:"::Text)])
3802 [ ("Name":|[], [""])
3803 , ("Name2":|[], [""])
3806 , "Name: , Name2:" ~:
3807 (Data.Either.rights $
3809 (Format.Ledger.Read.tags <* P.eof)
3810 () "" ("Name: , Name2:"::Text)])
3813 [ ("Name":|[], [" "])
3814 , ("Name2":|[], [""])
3817 , "Name:,Name2:,Name3:" ~:
3818 (Data.Either.rights $
3820 (Format.Ledger.Read.tags <* P.eof)
3821 () "" ("Name:,Name2:,Name3:"::Text)])
3824 [ ("Name":|[], [""])
3825 , ("Name2":|[], [""])
3826 , ("Name3":|[], [""])
3829 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
3830 (Data.Either.rights $
3832 (Format.Ledger.Read.tags <* P.eof)
3833 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
3836 [ ("Name":|[], ["Val ue"])
3837 , ("Name2":|[], ["V a l u e"])
3838 , ("Name3":|[], ["V al ue"])
3842 , "posting" ~: TestList
3843 [ " A:B:C = Right A:B:C" ~:
3844 (Data.Either.rights $
3845 [P.runParser_with_Error
3846 (Format.Ledger.Read.posting <* P.eof)
3847 ( Format.Ledger.Read.context () Format.Ledger.journal
3848 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3849 "" (" A:B:C"::Text)])
3851 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
3852 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3854 , Posting.Posting_Type_Regular
3857 , " !A:B:C = Right !A:B:C" ~:
3858 (Data.List.map fst $
3859 Data.Either.rights $
3860 [P.runParser_with_Error
3861 (Format.Ledger.Read.posting <* P.eof)
3862 ( Format.Ledger.Read.context () Format.Ledger.journal
3863 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3864 "" (" !A:B:C"::Text)])
3866 [ (Format.Ledger.posting ("A":|["B", "C"]))
3867 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3868 , Format.Ledger.posting_status = True
3871 , " *A:B:C = Right *A:B:C" ~:
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"::Text)])
3880 [ (Format.Ledger.posting ("A":|["B", "C"]))
3881 { Format.Ledger.posting_amounts = Data.Map.fromList []
3882 , Format.Ledger.posting_comments = []
3883 , Format.Ledger.posting_dates = []
3884 , Format.Ledger.posting_status = True
3885 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3886 , Format.Ledger.posting_tags = Data.Map.fromList []
3889 , " A:B:C $1 = Right A:B:C $1" ~:
3890 (Data.List.map fst $
3891 Data.Either.rights $
3892 [P.runParser_with_Error
3893 (Format.Ledger.Read.posting <* P.eof)
3894 ( Format.Ledger.Read.context () Format.Ledger.journal
3895 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3896 "" (" A:B:C $1"::Text)])
3898 [ (Format.Ledger.posting ("A":|["B","C $1"]))
3899 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3902 , " A:B:C $1 = Right A:B:C $1" ~:
3903 (Data.List.map fst $
3904 Data.Either.rights $
3905 [P.runParser_with_Error
3906 (Format.Ledger.Read.posting <* P.eof)
3907 ( Format.Ledger.Read.context () Format.Ledger.journal
3908 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3909 "" (" A:B:C $1"::Text)])
3911 [ (Format.Ledger.posting ("A":|["B", "C"]))
3912 { Format.Ledger.posting_amounts = Data.Map.fromList
3914 { Amount.quantity = 1
3915 , Amount.style = Amount.Style.nil
3916 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3917 , Amount.Style.unit_spaced = Just False
3922 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3925 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
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 $1 + 1€"::Text)])
3934 [ (Format.Ledger.posting ("A":|["B", "C"]))
3935 { Format.Ledger.posting_amounts = Data.Map.fromList
3937 { Amount.quantity = 1
3938 , Amount.style = Amount.Style.nil
3939 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3940 , Amount.Style.unit_spaced = Just False
3945 { Amount.quantity = 1
3946 , Amount.style = Amount.Style.nil
3947 { Amount.Style.unit_side = Just Amount.Style.Side_Right
3948 , Amount.Style.unit_spaced = Just False
3953 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3956 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
3957 (Data.List.map fst $
3958 Data.Either.rights $
3959 [P.runParser_with_Error
3960 (Format.Ledger.Read.posting <* P.eof)
3961 ( Format.Ledger.Read.context () Format.Ledger.journal
3962 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3963 "" (" A:B:C $1 + 1$"::Text)])
3965 [ (Format.Ledger.posting ("A":|["B", "C"]))
3966 { Format.Ledger.posting_amounts = Data.Map.fromList
3968 { Amount.quantity = 2
3969 , Amount.style = Amount.Style.nil
3970 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3971 , Amount.Style.unit_spaced = Just False
3976 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3979 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
3980 (Data.List.map fst $
3981 Data.Either.rights $
3982 [P.runParser_with_Error
3983 (Format.Ledger.Read.posting <* P.eof)
3984 ( Format.Ledger.Read.context () Format.Ledger.journal
3985 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3986 "" (" A:B:C $1 + 1$ + 1$"::Text)])
3988 [ (Format.Ledger.posting ("A":|["B", "C"]))
3989 { Format.Ledger.posting_amounts = Data.Map.fromList
3991 { Amount.quantity = 3
3992 , Amount.style = Amount.Style.nil
3993 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3994 , Amount.Style.unit_spaced = Just False
3999 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4002 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
4003 (Data.List.map fst $
4004 Data.Either.rights $
4005 [P.runParser_with_Error
4006 (Format.Ledger.Read.posting <* P.eof)
4007 ( Format.Ledger.Read.context () Format.Ledger.journal
4008 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4009 "" (" A:B:C ; some comment"::Text)])
4011 [ (Format.Ledger.posting ("A":|["B", "C"]))
4012 { Format.Ledger.posting_amounts = Data.Map.fromList []
4013 , Format.Ledger.posting_comments = [" some comment"]
4014 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4017 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
4018 (Data.List.map fst $
4019 Data.Either.rights $
4020 [P.runParser_with_Error
4021 (Format.Ledger.Read.posting <* P.eof)
4022 ( Format.Ledger.Read.context () Format.Ledger.journal
4023 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4024 "" (" A:B:C ; some comment\n ; some other comment"::Text)])
4026 [ (Format.Ledger.posting ("A":|["B", "C"]))
4027 { Format.Ledger.posting_amounts = Data.Map.fromList []
4028 , Format.Ledger.posting_comments = [" some comment", " some other comment"]
4029 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4032 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
4033 (Data.List.map fst $
4034 Data.Either.rights $
4035 [P.runParser_with_Error
4036 (Format.Ledger.Read.posting)
4037 ( Format.Ledger.Read.context () Format.Ledger.journal
4038 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4039 "" (" A:B:C $1 ; some comment"::Text)])
4041 [ (Format.Ledger.posting ("A":|["B", "C"]))
4042 { Format.Ledger.posting_amounts = Data.Map.fromList
4044 { Amount.quantity = 1
4045 , Amount.style = Amount.Style.nil
4046 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4047 , Amount.Style.unit_spaced = Just False
4052 , Format.Ledger.posting_comments = [" some comment"]
4053 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4056 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
4057 (Data.List.map fst $
4058 Data.Either.rights $
4059 [P.runParser_with_Error
4060 (Format.Ledger.Read.posting <* P.eof)
4061 ( Format.Ledger.Read.context () Format.Ledger.journal
4062 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4063 "" (" A:B:C ; N:V"::Text)])
4065 [ (Format.Ledger.posting ("A":|["B", "C"]))
4066 { Format.Ledger.posting_comments = [" N:V"]
4067 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4068 , Format.Ledger.posting_tags = Data.Map.fromList
4073 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
4074 (Data.List.map fst $
4075 Data.Either.rights $
4076 [P.runParser_with_Error
4077 (Format.Ledger.Read.posting <* P.eof)
4078 ( Format.Ledger.Read.context () Format.Ledger.journal
4079 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4080 "" (" A:B:C ; some comment N:V"::Text)])
4082 [ (Format.Ledger.posting ("A":|["B", "C"]))
4083 { Format.Ledger.posting_comments = [" some comment N:V"]
4084 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4085 , Format.Ledger.posting_tags = Data.Map.fromList
4090 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
4091 (Data.List.map fst $
4092 Data.Either.rights $
4093 [P.runParser_with_Error
4094 (Format.Ledger.Read.posting )
4095 ( Format.Ledger.Read.context () Format.Ledger.journal
4096 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4097 "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
4099 [ (Format.Ledger.posting ("A":|["B", "C"]))
4100 { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"]
4101 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4102 , Format.Ledger.posting_tags = Data.Map.fromList
4103 [ ("N":|[], ["V v"])
4104 , ("N2":|[], ["V2 v2"])
4108 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
4109 (Data.List.map fst $
4110 Data.Either.rights $
4111 [P.runParser_with_Error
4112 (Format.Ledger.Read.posting <* P.eof)
4113 ( Format.Ledger.Read.context () Format.Ledger.journal
4114 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4115 "" (" A:B:C ; N:V\n ; N:V2"::Text)])
4117 [ (Format.Ledger.posting ("A":|["B", "C"]))
4118 { Format.Ledger.posting_comments = [" N:V", " N:V2"]
4119 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4120 , Format.Ledger.posting_tags = Data.Map.fromList
4121 [ ("N":|[], ["V", "V2"])
4125 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
4126 (Data.List.map fst $
4127 Data.Either.rights $
4128 [P.runParser_with_Error
4129 (Format.Ledger.Read.posting <* P.eof)
4130 ( Format.Ledger.Read.context () Format.Ledger.journal
4131 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4132 "" (" A:B:C ; N:V\n ; N2:V"::Text)])
4134 [ (Format.Ledger.posting ("A":|["B", "C"]))
4135 { Format.Ledger.posting_comments = [" N:V", " N2:V"]
4136 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4137 , Format.Ledger.posting_tags = Data.Map.fromList
4143 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
4144 (Data.List.map fst $
4145 Data.Either.rights $
4146 [P.runParser_with_Error
4147 (Format.Ledger.Read.posting <* P.eof)
4148 ( Format.Ledger.Read.context () Format.Ledger.journal
4149 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4150 "" (" A:B:C ; date:2001/01/01"::Text)])
4152 [ (Format.Ledger.posting ("A":|["B", "C"]))
4153 { Format.Ledger.posting_comments = [" date:2001/01/01"]
4154 , Format.Ledger.posting_dates =
4155 [ Time.zonedTimeToUTC $
4158 (Time.fromGregorian 2001 01 01)
4159 (Time.TimeOfDay 0 0 0))
4162 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4163 , Format.Ledger.posting_tags = Data.Map.fromList
4164 [ ("date":|[], ["2001/01/01"])
4168 , " (A:B:C) = Right (A:B:C)" ~:
4169 (Data.Either.rights $
4170 [P.runParser_with_Error
4171 (Format.Ledger.Read.posting <* P.eof)
4172 ( Format.Ledger.Read.context () Format.Ledger.journal
4173 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4174 "" (" (A:B:C)"::Text)])
4176 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4177 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4179 , Posting.Posting_Type_Virtual
4182 , " [A:B:C] = Right [A:B:C]" ~:
4183 (Data.Either.rights $
4184 [P.runParser_with_Error
4185 (Format.Ledger.Read.posting <* P.eof)
4186 ( Format.Ledger.Read.context () Format.Ledger.journal
4187 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4188 "" (" [A:B:C]"::Text)])
4190 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4191 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4193 , Posting.Posting_Type_Virtual_Balanced
4197 , "transaction" ~: TestList
4198 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
4199 (Data.Either.rights $
4200 [P.runParser_with_Error
4201 (Format.Ledger.Read.transaction <* P.eof)
4202 ( Format.Ledger.Read.context () Format.Ledger.journal
4203 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4204 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
4206 [ Format.Ledger.transaction
4207 { Format.Ledger.transaction_dates=
4208 ( Time.zonedTimeToUTC $
4211 (Time.fromGregorian 2000 01 01)
4212 (Time.TimeOfDay 0 0 0))
4215 , Format.Ledger.transaction_description="some description"
4216 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4217 [ (Format.Ledger.posting ("A":|["B", "C"]))
4218 { Format.Ledger.posting_amounts = Data.Map.fromList
4220 { Amount.quantity = 1
4221 , Amount.style = Amount.Style.nil
4222 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4223 , Amount.Style.unit_spaced = Just False
4228 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4230 , (Format.Ledger.posting ("a":|["b", "c"]))
4231 { Format.Ledger.posting_amounts = Data.Map.fromList
4233 { Amount.quantity = -1
4234 , Amount.style = Amount.Style.nil
4235 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4236 , Amount.Style.unit_spaced = Just False
4241 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4244 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4247 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
4248 (Data.Either.rights $
4249 [P.runParser_with_Error
4250 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
4251 ( Format.Ledger.Read.context () Format.Ledger.journal
4252 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4253 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
4255 [ Format.Ledger.transaction
4256 { Format.Ledger.transaction_dates=
4257 ( Time.zonedTimeToUTC $
4260 (Time.fromGregorian 2000 01 01)
4261 (Time.TimeOfDay 0 0 0))
4264 , Format.Ledger.transaction_description="some description"
4265 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4266 [ (Format.Ledger.posting ("A":|["B", "C"]))
4267 { Format.Ledger.posting_amounts = Data.Map.fromList
4269 { Amount.quantity = 1
4270 , Amount.style = Amount.Style.nil
4271 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4272 , Amount.Style.unit_spaced = Just False
4277 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4279 , (Format.Ledger.posting ("a":|["b", "c"]))
4280 { Format.Ledger.posting_amounts = Data.Map.fromList
4282 { Amount.quantity = -1
4283 , Amount.style = Amount.Style.nil
4284 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4285 , Amount.Style.unit_spaced = Just False
4290 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4293 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4296 , "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" ~:
4297 (Data.Either.rights $
4298 [P.runParser_with_Error
4299 (Format.Ledger.Read.transaction <* P.eof)
4300 ( Format.Ledger.Read.context () Format.Ledger.journal
4301 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4302 "" ("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)])
4304 [ Format.Ledger.transaction
4305 { Format.Ledger.transaction_comments_after =
4307 , " some other;comment"
4309 , " some last comment"
4311 , Format.Ledger.transaction_dates=
4312 ( Time.zonedTimeToUTC $
4315 (Time.fromGregorian 2000 01 01)
4316 (Time.TimeOfDay 0 0 0))
4319 , Format.Ledger.transaction_description="some description"
4320 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4321 [ (Format.Ledger.posting ("A":|["B", "C"]))
4322 { Format.Ledger.posting_amounts = Data.Map.fromList
4324 { Amount.quantity = 1
4325 , Amount.style = Amount.Style.nil
4326 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4327 , Amount.Style.unit_spaced = Just False
4332 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4334 , (Format.Ledger.posting ("a":|["b", "c"]))
4335 { Format.Ledger.posting_amounts = Data.Map.fromList
4337 { Amount.quantity = -1
4338 , Amount.style = Amount.Style.nil
4339 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4340 , Amount.Style.unit_spaced = Just False
4345 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4348 , Format.Ledger.transaction_tags = Data.Map.fromList
4351 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4355 , "journal" ~: TestList
4356 [ "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
4358 P.runParserT_with_Error
4359 (Format.Ledger.Read.journal "" {-<* P.eof-})
4360 ( Format.Ledger.Read.context () Format.Ledger.journal
4361 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4362 "" ("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)
4364 (\j -> j{Format.Ledger.journal_last_read_time=Date.nil}) $
4365 Data.Either.rights [jnl])
4367 [ Format.Ledger.journal
4368 { Format.Ledger.journal_transactions =
4369 [ Format.Ledger.transaction
4370 { Format.Ledger.transaction_dates=
4371 ( Time.zonedTimeToUTC $
4374 (Time.fromGregorian 2000 01 02)
4375 (Time.TimeOfDay 0 0 0))
4378 , Format.Ledger.transaction_description="2° description"
4379 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4380 [ (Format.Ledger.posting ("A":|["B", "C"]))
4381 { Format.Ledger.posting_amounts = Data.Map.fromList
4383 { Amount.quantity = 1
4384 , Amount.style = Amount.Style.nil
4385 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4386 , Amount.Style.unit_spaced = Just False
4391 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4393 , (Format.Ledger.posting ("x":|["y", "z"]))
4394 { Format.Ledger.posting_amounts = Data.Map.fromList
4396 { Amount.quantity = -1
4397 , Amount.style = Amount.Style.nil
4398 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4399 , Amount.Style.unit_spaced = Just False
4404 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4407 , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1
4409 , Format.Ledger.transaction
4410 { Format.Ledger.transaction_dates=
4411 ( Time.zonedTimeToUTC $
4414 (Time.fromGregorian 2000 01 01)
4415 (Time.TimeOfDay 0 0 0))
4418 , Format.Ledger.transaction_description="1° description"
4419 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4420 [ (Format.Ledger.posting ("A":|["B", "C"]))
4421 { Format.Ledger.posting_amounts = Data.Map.fromList
4423 { Amount.quantity = 1
4424 , Amount.style = Amount.Style.nil
4425 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4426 , Amount.Style.unit_spaced = Just False
4431 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4433 , (Format.Ledger.posting ("a":|["b", "c"]))
4434 { Format.Ledger.posting_amounts = Data.Map.fromList
4436 { Amount.quantity = -1
4437 , Amount.style = Amount.Style.nil
4438 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4439 , Amount.Style.unit_spaced = Just False
4444 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4447 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4454 , "Write" ~: TestList
4455 [ "account" ~: TestList
4457 ((Format.Ledger.Write.show
4458 Format.Ledger.Write.Style
4459 { Format.Ledger.Write.style_color=False
4460 , Format.Ledger.Write.style_align=True
4462 Format.Ledger.Write.account Posting.Posting_Type_Regular $
4467 ((Format.Ledger.Write.show
4468 Format.Ledger.Write.Style
4469 { Format.Ledger.Write.style_color=False
4470 , Format.Ledger.Write.style_align=True
4472 Format.Ledger.Write.account Posting.Posting_Type_Regular $
4477 ((Format.Ledger.Write.show
4478 Format.Ledger.Write.Style
4479 { Format.Ledger.Write.style_color=False
4480 , Format.Ledger.Write.style_align=True
4482 Format.Ledger.Write.account Posting.Posting_Type_Virtual $
4487 ((Format.Ledger.Write.show
4488 Format.Ledger.Write.Style
4489 { Format.Ledger.Write.style_color=False
4490 , Format.Ledger.Write.style_align=True
4492 Format.Ledger.Write.account Posting.Posting_Type_Virtual_Balanced $
4497 , "transaction" ~: TestList
4499 ((Format.Ledger.Write.show
4500 Format.Ledger.Write.Style
4501 { Format.Ledger.Write.style_color=False
4502 , Format.Ledger.Write.style_align=True
4504 Format.Ledger.Write.transaction
4505 Format.Ledger.transaction)
4508 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\ta:b:c\\n\\t ; first comment\\n\\t ; second comment\\n\\t ; third comment\\n" ~:
4509 ((Format.Ledger.Write.show
4510 Format.Ledger.Write.Style
4511 { Format.Ledger.Write.style_color=False
4512 , Format.Ledger.Write.style_align=True
4514 Format.Ledger.Write.transaction $
4515 Format.Ledger.transaction
4516 { Format.Ledger.transaction_dates=
4517 ( Time.zonedTimeToUTC $
4520 (Time.fromGregorian 2000 01 01)
4521 (Time.TimeOfDay 0 0 0))
4524 , Format.Ledger.transaction_description="some description"
4525 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4526 [ (Format.Ledger.posting ("A":|["B", "C"]))
4527 { Format.Ledger.posting_amounts = Data.Map.fromList
4529 { Amount.quantity = 1
4530 , Amount.style = Amount.Style.nil
4531 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4532 , Amount.Style.unit_spaced = Just False
4538 , (Format.Ledger.posting ("a":|["b", "c"]))
4539 { Format.Ledger.posting_comments = ["first comment","second comment","third comment"]
4544 "2000/01/01 some description\n\tA:B:C $1\n\ta:b:c\n\t ; first comment\n\t ; second comment\n\t ; third comment\n")
4545 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
4546 ((Format.Ledger.Write.show
4547 Format.Ledger.Write.Style
4548 { Format.Ledger.Write.style_color=False
4549 , Format.Ledger.Write.style_align=True
4551 Format.Ledger.Write.transaction $
4552 Format.Ledger.transaction
4553 { Format.Ledger.transaction_dates=
4554 ( Time.zonedTimeToUTC $
4557 (Time.fromGregorian 2000 01 01)
4558 (Time.TimeOfDay 0 0 0))
4561 , Format.Ledger.transaction_description="some description"
4562 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4563 [ (Format.Ledger.posting ("A":|["B", "C"]))
4564 { Format.Ledger.posting_amounts = Data.Map.fromList
4566 { Amount.quantity = 1
4567 , Amount.style = Amount.Style.nil
4568 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4569 , Amount.Style.unit_spaced = Just False
4575 , (Format.Ledger.posting ("AA":|["BB", "CC"]))
4576 { Format.Ledger.posting_amounts = Data.Map.fromList
4578 { Amount.quantity = 123
4579 , Amount.style = Amount.Style.nil
4580 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4581 , Amount.Style.unit_spaced = Just False
4590 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123\n")