]> Git — Sourcephile - comptalang.git/blob - lib/Test/Main.hs
Ajout : Filter : Filter_Transaction_Posting : joint les tests sur le même Posting.
[comptalang.git] / lib / Test / Main.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TupleSections #-}
5
6 import Prelude
7 import Test.HUnit hiding ((~?))
8 import Test.Framework.Providers.HUnit (hUnitTestToTests)
9 import Test.Framework.Runners.Console (defaultMain)
10
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
29
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
54
55 main :: IO ()
56 main = defaultMain $ hUnitTestToTests test_Hcompta
57
58 (~?) :: String -> Bool -> Test
59 (~?) s b = s ~: (b ~?= True)
60
61 test_Hcompta :: Test
62 test_Hcompta =
63 TestList
64 [ "Lib" ~: TestList
65 [ "TreeMap" ~: TestList
66 [ "insert" ~: TestList
67 [ "[] 0" ~:
68 (Lib.TreeMap.insert const ((0::Int):|[]) () Lib.TreeMap.empty)
69 ~?=
70 (Lib.TreeMap.TreeMap $
71 Data.Map.fromList
72 [ ((0::Int), Lib.TreeMap.leaf ())
73 ])
74 , "[] 0/1" ~:
75 (Lib.TreeMap.insert const ((0::Int):|1:[]) () Lib.TreeMap.empty)
76 ~?=
77 (Lib.TreeMap.TreeMap $
78 Data.Map.fromList
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):|[]) ()
84 })
85 ])
86 ]
87 , "union" ~: TestList
88 [
89 ]
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 ->
94 Data.Map.foldl'
95 (\acc v -> (++) acc $
96 Strict.fromMaybe undefined $
97 Lib.TreeMap.node_value v
98 )
99 (Strict.fromMaybe [] value)
100 (Lib.TreeMap.nodes descendants)
101 ) $
102 Lib.TreeMap.from_List const
103 [ (((0::Integer):|[]), [0])
104 , ((0:|1:[]), [0,1])
105 , ((0:|1:2:[]), [0,1,2])
106 , ((1:|[]), [1])
107 , ((1:|2:3:[]), [1,2,3])
108 ]
109 )
110 ~?=
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])
118 ])
119 , "[0/0]" ~:
120 (Lib.TreeMap.map_by_depth_first
121 (\descendants value ->
122 Data.Map.foldl'
123 (\acc v -> (++) acc $
124 Strict.fromMaybe undefined $
125 Lib.TreeMap.node_value v
126 )
127 (Strict.fromMaybe [] value)
128 (Lib.TreeMap.nodes descendants)
129 ) $
130 Lib.TreeMap.from_List const
131 [ (((0::Integer):|0:[]), [0,0])
132 ]
133 )
134 ~?=
135 (Lib.TreeMap.from_List const
136 [ ((0:|[]), [0,0])
137 , ((0:|0:[]), [0,0])
138 ])
139 ]
140 , "flatten" ~: TestList
141 [ "[0, 0/1, 0/1/2]" ~:
142 (Lib.TreeMap.flatten id $
143 Lib.TreeMap.from_List const
144 [ (((0::Integer):|[]), ())
145 , ((0:|1:[]), ())
146 , ((0:|1:2:[]), ())
147 ]
148 )
149 ~?=
150 (Data.Map.fromList
151 [ ((0:|[]), ())
152 , ((0:|1:[]), ())
153 , ((0:|1:2:[]), ())
154 ])
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
158 [ ((1:|[]), ())
159 , ((1:|2:[]), ())
160 , ((1:|22:[]), ())
161 , ((1:|2:3:[]), ())
162 , ((1:|2:33:[]), ())
163 , ((11:|[]), ())
164 , ((11:|2:[]), ())
165 , ((11:|2:3:[]), ())
166 , ((11:|2:33:[]), ())
167 ]
168 )
169 ~?=
170 (Data.Map.fromList
171 [ (((1::Integer):|[]), ())
172 , ((1:|2:[]), ())
173 , ((1:|22:[]), ())
174 , ((1:|2:3:[]), ())
175 , ((1:|2:33:[]), ())
176 , ((11:|[]), ())
177 , ((11:|2:[]), ())
178 , ((11:|2:3:[]), ())
179 , ((11:|2:33:[]), ())
180 ])
181 ]
182 ]
183 , "Foldable" ~: TestList
184 [ "accumLeftsAndFoldrRights" ~: TestList
185 [ "Left" ~:
186 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
187 [Left [0]])
188 ~?=
189 (([(0::Integer)], [(""::String)]))
190 , "repeat Left" ~:
191 ((take 1 *** take 0) $
192 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
193 ( repeat (Left [0]) ))
194 ~?=
195 ([(0::Integer)], ([]::[String]))
196 , "Right:Left:Right:Left" ~:
197 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
198 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
199 ~?=
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]) ))
205 ~?=
206 (([1]::[Integer]), (["2", "1"]::[String]))
207 ]
208 ]
209 , "Interval" ~: TestList
210 [ "position" ~: TestList $
211 concatMap
212 (\(mi, mj, p) ->
213 let i = fromJust mi in
214 let j = fromJust mj in
215 let (le, ge) =
216 case p of
217 Lib.Interval.Equal -> (EQ, EQ)
218 _ -> (LT, GT) in
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)
221 ]
222 )
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 )
253 ]
254 , "intersection" ~: TestList $
255 concatMap
256 (\(mi, mj, e) ->
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
261 ]
262 )
263 [ ( (Lib.Interval.<..<) 0 (4::Integer)
264 , (Lib.Interval.<..<) 5 9
265 , Nothing )
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 )
293 ]
294 , "union" ~: TestList $
295 concatMap
296 (\(mi, mj, e) ->
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
301 ]
302 )
303 [ ( (Lib.Interval.<..<) 0 (4::Integer)
304 , (Lib.Interval.<..<) 5 9
305 , Nothing )
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 )
330 ]
331 , "Sieve" ~: TestList $
332 [ "union" ~: TestList $
333 Data.List.concatMap
334 (\(mis, me) ->
335 let is = map (fromJust) mis in
336 let e = map (fromJust) me in
337 let sil = foldl
338 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
339 Lib.Interval.Sieve.empty is in
340 let sir = foldr
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
347 ]
348 )
349 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer)
350 , (Lib.Interval.<=..<=) 5 9
351 ]
352 , [ (Lib.Interval.<=..<=) 0 9 ]
353 )
354 , ( [ (Lib.Interval.<=..<=) 0 5
355 , (Lib.Interval.<=..<=) 0 9
356 ]
357 , [ (Lib.Interval.<=..<=) 0 9 ]
358 )
359 , ( [ (Lib.Interval.<=..<=) 0 4
360 , (Lib.Interval.<=..<=) 5 9
361 , (Lib.Interval.<=..<=) 3 6
362 ]
363 , [ (Lib.Interval.<=..<=) 0 9 ]
364 )
365 , ( [ (Lib.Interval.<=..<=) 1 4
366 , (Lib.Interval.<=..<=) 5 8
367 ]
368 , [ (Lib.Interval.<=..<=) 1 4
369 , (Lib.Interval.<=..<=) 5 8
370 ]
371 )
372 , ( [ (Lib.Interval.<=..<=) 1 8
373 , (Lib.Interval.<=..<=) 0 9
374 ]
375 , [ (Lib.Interval.<=..<=) 0 9 ]
376 )
377 , ( [ (Lib.Interval.<=..<=) 1 4
378 , (Lib.Interval.<=..<=) 5 8
379 , (Lib.Interval.<=..<=) 0 9
380 ]
381 , [ (Lib.Interval.<=..<=) 0 9 ]
382 )
383 ]
384 ++ Data.List.concatMap
385 (\(mis, mjs, me) ->
386 let is = map fromJust mis in
387 let js = map fromJust mjs in
388 let e = map fromJust me in
389 let iu = foldl
390 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
391 Lib.Interval.Sieve.empty is in
392 let ju = foldl
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
401 ]
402 )
403 [ ( [ (Lib.Interval.<=..<=) 0 (1::Integer)
404 , (Lib.Interval.<=..<=) 2 4
405 ]
406 , [ (Lib.Interval.<=..<=) 0 3
407 ]
408 , [ (Lib.Interval.<=..<=) 0 4
409 ]
410 )
411 , ( [ (Lib.Interval.<=..<=) 0 1
412 , (Lib.Interval.<=..<=) 2 3
413 , (Lib.Interval.<=..<=) 4 5
414 , (Lib.Interval.<=..<=) 6 7
415 ]
416 , [ (Lib.Interval.<=..<=) 1 2
417 , (Lib.Interval.<=..<=) 3 4
418 , (Lib.Interval.<=..<=) 5 6
419 ]
420 , [ (Lib.Interval.<=..<=) 0 7
421 ]
422 )
423 , ( [ (Lib.Interval.<=..<=) 0 1
424 , (Lib.Interval.<=..<=) 2 3
425 ]
426 , [ (Lib.Interval.<=..<=) 4 5
427 ]
428 , [ (Lib.Interval.<=..<=) 0 1
429 , (Lib.Interval.<=..<=) 2 3
430 , (Lib.Interval.<=..<=) 4 5
431 ]
432 )
433 , ( [ (Lib.Interval.<=..<=) 0 1
434 , (Lib.Interval.<=..<=) 4 5
435 ]
436 , [ (Lib.Interval.<=..<=) 2 3
437 ]
438 , [ (Lib.Interval.<=..<=) 0 1
439 , (Lib.Interval.<=..<=) 2 3
440 , (Lib.Interval.<=..<=) 4 5
441 ]
442 )
443 ]
444 , "intersection" ~: TestList $
445 Data.List.concatMap
446 (\(mis, mjs, me) ->
447 let is = map (fromJust) mis in
448 let js = map (fromJust) mjs in
449 let e = map (fromJust) me in
450 let iu = foldl
451 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
452 Lib.Interval.Sieve.empty is in
453 let ju = foldl
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
462 ]
463 )
464 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) ]
465 , [ (Lib.Interval.<=..<=) 5 9 ]
466 , [ ]
467 )
468 , ( [ (Lib.Interval.<=..<=) 0 5 ]
469 , [ (Lib.Interval.<=..<=) 5 9 ]
470 , [ (Lib.Interval.<=..<=) 5 5 ]
471 )
472 , ( [ (Lib.Interval.<=..<=) 0 5 ]
473 , [ (Lib.Interval.<=..<=) 0 9 ]
474 , [ (Lib.Interval.<=..<=) 0 5 ]
475 )
476 , ( [ (Lib.Interval.<=..<=) 0 4
477 , (Lib.Interval.<=..<=) 5 9
478 ]
479 , [ (Lib.Interval.<=..<=) 3 6 ]
480 , [ (Lib.Interval.<=..<=) 3 4
481 , (Lib.Interval.<=..<=) 5 6
482 ]
483 )
484 , ( [ (Lib.Interval.<=..<=) 1 4
485 , (Lib.Interval.<=..<=) 6 8
486 ]
487 , [ (Lib.Interval.<=..<=) 2 3
488 , (Lib.Interval.<=..<=) 5 7
489 ]
490 , [ (Lib.Interval.<=..<=) 2 3
491 , (Lib.Interval.<=..<=) 6 7
492 ]
493 )
494 ]
495 , "complement" ~: TestList $
496 Data.List.concatMap
497 (\(mis, me) ->
498 let is = map fromJust mis in
499 let e = map fromJust me in
500 let iu = foldl
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
507 ]
508 )
509 [ ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 (5::Integer)
510 , ((Lib.Interval.<=..<=) `on` Lib.Interval.Limited) 5 9
511 ]
512 , [ Just $ (Lib.Interval...<) 0
513 , Just $ (Lib.Interval.<..) 9
514 ]
515 )
516 , ( [ Just $ Lib.Interval.unlimited ]
517 , [ ]
518 )
519 , ( [ ]
520 , [ Just $ Lib.Interval.unlimited ]
521 )
522 , ( [ Just $ (Lib.Interval...<) 0
523 , Just $ (Lib.Interval.<..) 0
524 ]
525 , [ Just $ Lib.Interval.point $ Lib.Interval.Limited 0
526 ]
527 )
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
531 ]
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
536 ]
537 )
538 ]
539 , "complement_with" ~: TestList $
540 Data.List.concatMap
541 (\(mib, mis, me) ->
542 let ib = fromJust mib in
543 let is = map fromJust mis in
544 let e = map fromJust me in
545 let iu = foldl
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
550 ]
551 )
552 [ ( (Lib.Interval.<=..<=) (-10) (10::Integer)
553 , [ (Lib.Interval.<=..<) 0 5
554 , (Lib.Interval.<=..<=) 5 9
555 ]
556 , [ (Lib.Interval.<=..<) (-10) 0
557 , (Lib.Interval.<..<=) 9 10
558 ]
559 )
560 , ( (Lib.Interval.<=..<=) (-10) 10
561 , [ (Lib.Interval.<=..<=) (-10) 10 ]
562 , [ ]
563 )
564 , ( (Lib.Interval.<=..<=) (-10) 10
565 , [ ]
566 , [ (Lib.Interval.<=..<=) (-10) 10 ]
567 )
568 , ( (Lib.Interval.<=..<=) (-10) 10
569 , [ (Lib.Interval.<=..<) (-10) 0
570 , (Lib.Interval.<..<=) 0 10
571 ]
572 , [ Just $ Lib.Interval.point 0
573 ]
574 )
575 , ( (Lib.Interval.<=..<=) (-10) 10
576 , [ Just $ Lib.Interval.point 0
577 ]
578 , [ (Lib.Interval.<=..<) (-10) 0
579 , (Lib.Interval.<..<=) 0 10
580 ]
581 )
582 , ( (Lib.Interval.<=..<=) 0 10
583 , [ (Lib.Interval.<..<=) 0 10
584 ]
585 , [ Just $ Lib.Interval.point 0
586 ]
587 )
588 , ( (Lib.Interval.<=..<=) 0 10
589 , [ (Lib.Interval.<=..<) 0 10
590 ]
591 , [ Just $ Lib.Interval.point 10
592 ]
593 )
594 , ( Just $ Lib.Interval.point 0
595 , [
596 ]
597 , [ Just $ Lib.Interval.point 0
598 ]
599 )
600 , ( Just $ Lib.Interval.point 0
601 , [ Just $ Lib.Interval.point 0
602 ]
603 , [
604 ]
605 )
606 ]
607 ]
608 ]
609 ]
610 , "Account" ~: TestList
611 [ "foldr" ~: TestList
612 [ "[A]" ~:
613 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
614 , "[A, B]" ~:
615 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
616 , "[A, B, C]" ~:
617 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
618 ]
619 , "ascending" ~: TestList
620 [ "[A]" ~:
621 Account.ascending ("A":|[]) ~?= Nothing
622 , "[A, B]" ~:
623 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
624 , "[A, B, C]" ~:
625 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
626 ]
627 , "Read" ~: TestList
628 [ "section" ~: TestList
629 [ "\"\"" ~:
630 (Data.Either.rights $
631 [P.runParser
632 (Account.Read.section <* P.eof)
633 () "" (""::Text)])
634 ~?=
635 []
636 , "\"A\"" ~:
637 (Data.Either.rights $
638 [P.runParser
639 (Account.Read.section <* P.eof)
640 () "" ("A"::Text)])
641 ~?=
642 ["A"]
643 , "\"AA\"" ~:
644 (Data.Either.rights $
645 [P.runParser
646 (Account.Read.section <* P.eof)
647 () "" ("AA"::Text)])
648 ~?=
649 ["AA"]
650 , "\" \"" ~:
651 (Data.Either.rights $
652 [P.runParser
653 (Account.Read.section <* P.eof)
654 () "" (" "::Text)])
655 ~?=
656 []
657 , "\":\"" ~:
658 (Data.Either.rights $
659 [P.runParser
660 (Account.Read.section <* P.eof)
661 () "" (":"::Text)])
662 ~?=
663 []
664 , "\"A:\"" ~:
665 (Data.Either.rights $
666 [P.runParser
667 (Account.Read.section <* P.eof)
668 () "" ("A:"::Text)])
669 ~?=
670 []
671 , "\":A\"" ~:
672 (Data.Either.rights $
673 [P.runParser
674 (Account.Read.section <* P.eof)
675 () "" (":A"::Text)])
676 ~?=
677 []
678 , "\"A \"" ~:
679 (Data.Either.rights $
680 [P.runParser
681 (Account.Read.section <* P.eof)
682 () "" ("A "::Text)])
683 ~?=
684 []
685 , "\"A \"" ~:
686 (Data.Either.rights $
687 [P.runParser
688 (Account.Read.section)
689 () "" ("A "::Text)])
690 ~?=
691 ["A"]
692 , "\"A A\"" ~:
693 (Data.Either.rights $
694 [P.runParser
695 (Account.Read.section <* P.eof)
696 () "" ("A A"::Text)])
697 ~?=
698 ["A A"]
699 , "\"A \"" ~:
700 (Data.Either.rights $
701 [P.runParser
702 (Account.Read.section <* P.eof)
703 () "" ("A "::Text)])
704 ~?=
705 []
706 , "\"A\t\"" ~:
707 (Data.Either.rights $
708 [P.runParser
709 (Account.Read.section <* P.eof)
710 () "" ("A\t"::Text)])
711 ~?=
712 []
713 , "\"A \\n\"" ~:
714 (Data.Either.rights $
715 [P.runParser
716 (Account.Read.section <* P.eof)
717 () "" ("A \n"::Text)])
718 ~?=
719 []
720 , "\"(A)A\"" ~:
721 (Data.Either.rights $
722 [P.runParser
723 (Account.Read.section <* P.eof)
724 () "" ("(A)A"::Text)])
725 ~?=
726 ["(A)A"]
727 , "\"( )A\"" ~:
728 (Data.Either.rights $
729 [P.runParser
730 (Account.Read.section <* P.eof)
731 () "" ("( )A"::Text)])
732 ~?=
733 ["( )A"]
734 , "\"(A) A\"" ~:
735 (Data.Either.rights $
736 [P.runParser
737 (Account.Read.section <* P.eof)
738 () "" ("(A) A"::Text)])
739 ~?=
740 ["(A) A"]
741 , "\"[ ]A\"" ~:
742 (Data.Either.rights $
743 [P.runParser
744 (Account.Read.section <* P.eof)
745 () "" ("[ ]A"::Text)])
746 ~?=
747 ["[ ]A"]
748 , "\"(A) \"" ~:
749 (Data.Either.rights $
750 [P.runParser
751 (Account.Read.section <* P.eof)
752 () "" ("(A) "::Text)])
753 ~?=
754 []
755 , "\"(A)\"" ~:
756 (Data.Either.rights $
757 [P.runParser
758 (Account.Read.section <* P.eof)
759 () "" ("(A)"::Text)])
760 ~?=
761 ["(A)"]
762 , "\"A(A)\"" ~:
763 (Data.Either.rights $
764 [P.runParser
765 (Account.Read.section <* P.eof)
766 () "" ("A(A)"::Text)])
767 ~?=
768 [("A(A)"::Text)]
769 , "\"[A]A\"" ~:
770 (Data.Either.rights $
771 [P.runParser
772 (Account.Read.section <* P.eof)
773 () "" ("[A]A"::Text)])
774 ~?=
775 ["[A]A"]
776 , "\"[A] A\"" ~:
777 (Data.Either.rights $
778 [P.runParser
779 (Account.Read.section <* P.eof)
780 () "" ("[A] A"::Text)])
781 ~?=
782 ["[A] A"]
783 , "\"[A] \"" ~:
784 (Data.Either.rights $
785 [P.runParser
786 (Account.Read.section <* P.eof)
787 () "" ("[A] "::Text)])
788 ~?=
789 []
790 , "\"[A]\"" ~:
791 (Data.Either.rights $
792 [P.runParser
793 (Account.Read.section <* P.eof)
794 () "" ("[A]"::Text)])
795 ~?=
796 ["[A]"]
797 ]
798 , "account" ~: TestList
799 [ "\"\"" ~:
800 (Data.Either.rights $
801 [P.runParser
802 (Account.Read.account <* P.eof)
803 () "" (""::Text)])
804 ~?=
805 []
806 , "\"A\"" ~:
807 (Data.Either.rights $
808 [P.runParser
809 (Account.Read.account <* P.eof)
810 () "" ("A"::Text)])
811 ~?=
812 ["A":|[]]
813 , "\"A:\"" ~:
814 (Data.Either.rights $
815 [P.runParser
816 (Account.Read.account <* P.eof)
817 () "" ("A:"::Text)])
818 ~?=
819 []
820 , "\":A\"" ~:
821 (Data.Either.rights $
822 [P.runParser
823 (Account.Read.account <* P.eof)
824 () "" (":A"::Text)])
825 ~?=
826 []
827 , "\"A \"" ~:
828 (Data.Either.rights $
829 [P.runParser
830 (Account.Read.account <* P.eof)
831 () "" ("A "::Text)])
832 ~?=
833 []
834 , "\" A\"" ~:
835 (Data.Either.rights $
836 [P.runParser
837 (Account.Read.account <* P.eof)
838 () "" (" A"::Text)])
839 ~?=
840 []
841 , "\"A:B\"" ~:
842 (Data.Either.rights $
843 [P.runParser
844 (Account.Read.account <* P.eof)
845 () "" ("A:B"::Text)])
846 ~?=
847 ["A":|["B"]]
848 , "\"A:B:C\"" ~:
849 (Data.Either.rights $
850 [P.runParser
851 (Account.Read.account <* P.eof)
852 () "" ("A:B:C"::Text)])
853 ~?=
854 ["A":|["B", "C"]]
855 , "\"Aa:Bbb:Cccc\"" ~:
856 (Data.Either.rights $
857 [P.runParser
858 (Account.Read.account <* P.eof)
859 () "" ("Aa:Bbb:Cccc"::Text)])
860 ~?=
861 ["Aa":|["Bbb", "Cccc"]]
862 , "\"A a : B b b : C c c c\"" ~:
863 (Data.Either.rights $
864 [P.runParser
865 (Account.Read.account <* P.eof)
866 () "" ("A a : B b b : C c c c"::Text)])
867 ~?=
868 ["A a ":|[" B b b ", " C c c c"]]
869 , "\"A: :C\"" ~:
870 (Data.Either.rights $
871 [P.runParser
872 (Account.Read.account <* P.eof)
873 () "" ("A: :C"::Text)])
874 ~?=
875 ["A":|[" ", "C"]]
876 , "\"A::C\"" ~:
877 (Data.Either.rights $
878 [P.runParser
879 (Account.Read.account <* P.eof)
880 () "" ("A::C"::Text)])
881 ~?=
882 []
883 , "\"A:B:(C)\"" ~:
884 (Data.Either.rights $
885 [P.runParser
886 (Account.Read.account <* P.eof)
887 () "" ("A:B:(C)"::Text)])
888 ~?=
889 ["A":|["B", "(C)"]]
890 ]
891 ]
892 ]
893 , "Amount" ~: TestList
894 [ "+" ~: TestList
895 [ "$1 + 1$ = $2" ~:
896 (+)
897 (Amount.nil
898 { Amount.quantity = Decimal 0 1
899 , Amount.style = Amount.Style.nil
900 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
901 }
902 , Amount.unit = "$"
903 })
904 (Amount.nil
905 { Amount.quantity = Decimal 0 1
906 , Amount.style = Amount.Style.nil
907 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
908 }
909 , Amount.unit = "$"
910 })
911 ~?=
912 (Amount.nil
913 { Amount.quantity = Decimal 0 2
914 , Amount.style = Amount.Style.nil
915 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
916 }
917 , Amount.unit = "$"
918 })
919 ]
920 , "from_List" ~: TestList
921 [ "from_List [$1, 1$] = $2" ~:
922 Amount.from_List
923 [ Amount.nil
924 { Amount.quantity = Decimal 0 1
925 , Amount.style = Amount.Style.nil
926 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
927 }
928 , Amount.unit = "$"
929 }
930 , Amount.nil
931 { Amount.quantity = Decimal 0 1
932 , Amount.style = Amount.Style.nil
933 { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
934 }
935 , Amount.unit = "$"
936 }
937 ]
938 ~?=
939 Data.Map.fromList
940 [ ("$", Amount.nil
941 { Amount.quantity = Decimal 0 2
942 , Amount.style = Amount.Style.nil
943 { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
944 }
945 , Amount.unit = "$"
946 })
947 ]
948 ]
949 , "Read" ~: TestList
950 [ "amount" ~: TestList
951 [ "\"\" = Left" ~:
952 (Data.Either.rights $
953 [P.runParser
954 (Amount.Read.amount <* P.eof)
955 () "" (""::Text)])
956 ~?=
957 []
958 , "\"0\" = Right 0" ~:
959 (Data.Either.rights $
960 [P.runParser
961 (Amount.Read.amount <* P.eof)
962 () "" ("0"::Text)])
963 ~?=
964 [Amount.nil
965 { Amount.quantity = Decimal 0 0
966 }]
967 , "\"00\" = Right 0" ~:
968 (Data.Either.rights $
969 [P.runParser
970 (Amount.Read.amount <* P.eof)
971 () "" ("00"::Text)])
972 ~?=
973 [Amount.nil
974 { Amount.quantity = Decimal 0 0
975 }]
976 , "\"0.\" = Right 0." ~:
977 (Data.Either.rights $
978 [P.runParser
979 (Amount.Read.amount <* P.eof)
980 () "" ("0."::Text)])
981 ~?=
982 [Amount.nil
983 { Amount.quantity = Decimal 0 0
984 , Amount.style =
985 Amount.Style.nil
986 { Amount.Style.fractioning = Just '.'
987 }
988 }]
989 , "\".0\" = Right 0.0" ~:
990 (Data.Either.rights $
991 [P.runParser
992 (Amount.Read.amount <* P.eof)
993 () "" (".0"::Text)])
994 ~?=
995 [Amount.nil
996 { Amount.quantity = Decimal 0 0
997 , Amount.style =
998 Amount.Style.nil
999 { Amount.Style.fractioning = Just '.'
1000 , Amount.Style.precision = 1
1001 }
1002 }]
1003 , "\"0,\" = Right 0," ~:
1004 (Data.Either.rights $
1005 [P.runParser
1006 (Amount.Read.amount <* P.eof)
1007 () "" ("0,"::Text)])
1008 ~?=
1009 [Amount.nil
1010 { Amount.quantity = Decimal 0 0
1011 , Amount.style =
1012 Amount.Style.nil
1013 { Amount.Style.fractioning = Just ','
1014 }
1015 }]
1016 , "\",0\" = Right 0,0" ~:
1017 (Data.Either.rights $
1018 [P.runParser
1019 (Amount.Read.amount <* P.eof)
1020 () "" (",0"::Text)])
1021 ~?=
1022 [Amount.nil
1023 { Amount.quantity = Decimal 0 0
1024 , Amount.style =
1025 Amount.Style.nil
1026 { Amount.Style.fractioning = Just ','
1027 , Amount.Style.precision = 1
1028 }
1029 }]
1030 , "\"0_\" = Left" ~:
1031 (Data.Either.rights $
1032 [P.runParser
1033 (Amount.Read.amount <* P.eof)
1034 () "" ("0_"::Text)])
1035 ~?=
1036 []
1037 , "\"_0\" = Left" ~:
1038 (Data.Either.rights $
1039 [P.runParser
1040 (Amount.Read.amount <* P.eof)
1041 () "" ("_0"::Text)])
1042 ~?=
1043 []
1044 , "\"0.0\" = Right 0.0" ~:
1045 (Data.Either.rights $
1046 [P.runParser
1047 (Amount.Read.amount <* P.eof)
1048 () "" ("0.0"::Text)])
1049 ~?=
1050 [Amount.nil
1051 { Amount.quantity = Decimal 0 0
1052 , Amount.style =
1053 Amount.Style.nil
1054 { Amount.Style.fractioning = Just '.'
1055 , Amount.Style.precision = 1
1056 }
1057 }]
1058 , "\"00.00\" = Right 0.00" ~:
1059 (Data.Either.rights $
1060 [P.runParser
1061 (Amount.Read.amount <* P.eof)
1062 () "" ("00.00"::Text)])
1063 ~?=
1064 [Amount.nil
1065 { Amount.quantity = Decimal 0 0
1066 , Amount.style =
1067 Amount.Style.nil
1068 { Amount.Style.fractioning = Just '.'
1069 , Amount.Style.precision = 2
1070 }
1071 }]
1072 , "\"0,0\" = Right 0,0" ~:
1073 (Data.Either.rights $
1074 [P.runParser
1075 (Amount.Read.amount <* P.eof)
1076 () "" ("0,0"::Text)])
1077 ~?=
1078 [Amount.nil
1079 { Amount.quantity = Decimal 0 0
1080 , Amount.style =
1081 Amount.Style.nil
1082 { Amount.Style.fractioning = Just ','
1083 , Amount.Style.precision = 1
1084 }
1085 }]
1086 , "\"00,00\" = Right 0,00" ~:
1087 (Data.Either.rights $
1088 [P.runParser
1089 (Amount.Read.amount <* P.eof)
1090 () "" ("00,00"::Text)])
1091 ~?=
1092 [Amount.nil
1093 { Amount.quantity = Decimal 0 0
1094 , Amount.style =
1095 Amount.Style.nil
1096 { Amount.Style.fractioning = Just ','
1097 , Amount.Style.precision = 2
1098 }
1099 }]
1100 , "\"0_0\" = Right 0" ~:
1101 (Data.Either.rights $
1102 [P.runParser
1103 (Amount.Read.amount <* P.eof)
1104 () "" ("0_0"::Text)])
1105 ~?=
1106 [Amount.nil
1107 { Amount.quantity = Decimal 0 0
1108 , Amount.style =
1109 Amount.Style.nil
1110 { Amount.Style.fractioning = Nothing
1111 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1112 , Amount.Style.precision = 0
1113 }
1114 }]
1115 , "\"00_00\" = Right 0" ~:
1116 (Data.Either.rights $
1117 [P.runParser
1118 (Amount.Read.amount <* P.eof)
1119 () "" ("00_00"::Text)])
1120 ~?=
1121 [Amount.nil
1122 { Amount.quantity = Decimal 0 0
1123 , Amount.style =
1124 Amount.Style.nil
1125 { Amount.Style.fractioning = Nothing
1126 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1127 , Amount.Style.precision = 0
1128 }
1129 }]
1130 , "\"0,000.00\" = Right 0,000.00" ~:
1131 (Data.Either.rights $
1132 [P.runParser
1133 (Amount.Read.amount <* P.eof)
1134 () "" ("0,000.00"::Text)])
1135 ~?=
1136 [Amount.nil
1137 { Amount.quantity = Decimal 0 0
1138 , Amount.style =
1139 Amount.Style.nil
1140 { Amount.Style.fractioning = Just '.'
1141 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1142 , Amount.Style.precision = 2
1143 }
1144 }]
1145 , "\"0.000,00\" = Right 0.000,00" ~:
1146 (Data.Either.rights $
1147 [P.runParser
1148 (Amount.Read.amount)
1149 () "" ("0.000,00"::Text)])
1150 ~?=
1151 [Amount.nil
1152 { Amount.quantity = Decimal 0 0
1153 , Amount.style =
1154 Amount.Style.nil
1155 { Amount.Style.fractioning = Just ','
1156 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1157 , Amount.Style.precision = 2
1158 }
1159 }]
1160 , "\"1,000.00\" = Right 1,000.00" ~:
1161 (Data.Either.rights $
1162 [P.runParser
1163 (Amount.Read.amount <* P.eof)
1164 () "" ("1,000.00"::Text)])
1165 ~?=
1166 [Amount.nil
1167 { Amount.quantity = Decimal 0 1000
1168 , Amount.style =
1169 Amount.Style.nil
1170 { Amount.Style.fractioning = Just '.'
1171 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1172 , Amount.Style.precision = 2
1173 }
1174 }]
1175 , "\"1.000,00\" = Right 1.000,00" ~:
1176 (Data.Either.rights $
1177 [P.runParser
1178 (Amount.Read.amount)
1179 () "" ("1.000,00"::Text)])
1180 ~?=
1181 [Amount.nil
1182 { Amount.quantity = Decimal 0 1000
1183 , Amount.style =
1184 Amount.Style.nil
1185 { Amount.Style.fractioning = Just ','
1186 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1187 , Amount.Style.precision = 2
1188 }
1189 }]
1190 , "\"1,000.00.\" = Left" ~:
1191 (Data.Either.rights $
1192 [P.runParser
1193 (Amount.Read.amount)
1194 () "" ("1,000.00."::Text)])
1195 ~?=
1196 []
1197 , "\"1.000,00,\" = Left" ~:
1198 (Data.Either.rights $
1199 [P.runParser
1200 (Amount.Read.amount)
1201 () "" ("1.000,00,"::Text)])
1202 ~?=
1203 []
1204 , "\"1,000.00_\" = Left" ~:
1205 (Data.Either.rights $
1206 [P.runParser
1207 (Amount.Read.amount)
1208 () "" ("1,000.00_"::Text)])
1209 ~?=
1210 []
1211 , "\"12\" = Right 12" ~:
1212 (Data.Either.rights $
1213 [P.runParser
1214 (Amount.Read.amount <* P.eof)
1215 () "" ("123"::Text)])
1216 ~?=
1217 [Amount.nil
1218 { Amount.quantity = Decimal 0 123
1219 }]
1220 , "\"1.2\" = Right 1.2" ~:
1221 (Data.Either.rights $
1222 [P.runParser
1223 (Amount.Read.amount <* P.eof)
1224 () "" ("1.2"::Text)])
1225 ~?=
1226 [Amount.nil
1227 { Amount.quantity = Decimal 1 12
1228 , Amount.style =
1229 Amount.Style.nil
1230 { Amount.Style.fractioning = Just '.'
1231 , Amount.Style.precision = 1
1232 }
1233 }]
1234 , "\"1,2\" = Right 1,2" ~:
1235 (Data.Either.rights $
1236 [P.runParser
1237 (Amount.Read.amount <* P.eof)
1238 () "" ("1,2"::Text)])
1239 ~?=
1240 [Amount.nil
1241 { Amount.quantity = Decimal 1 12
1242 , Amount.style =
1243 Amount.Style.nil
1244 { Amount.Style.fractioning = Just ','
1245 , Amount.Style.precision = 1
1246 }
1247 }]
1248 , "\"12.23\" = Right 12.23" ~:
1249 (Data.Either.rights $
1250 [P.runParser
1251 (Amount.Read.amount <* P.eof)
1252 () "" ("12.34"::Text)])
1253 ~?=
1254 [Amount.nil
1255 { Amount.quantity = Decimal 2 1234
1256 , Amount.style =
1257 Amount.Style.nil
1258 { Amount.Style.fractioning = Just '.'
1259 , Amount.Style.precision = 2
1260 }
1261 }]
1262 , "\"12,23\" = Right 12,23" ~:
1263 (Data.Either.rights $
1264 [P.runParser
1265 (Amount.Read.amount <* P.eof)
1266 () "" ("12,34"::Text)])
1267 ~?=
1268 [Amount.nil
1269 { Amount.quantity = Decimal 2 1234
1270 , Amount.style =
1271 Amount.Style.nil
1272 { Amount.Style.fractioning = Just ','
1273 , Amount.Style.precision = 2
1274 }
1275 }]
1276 , "\"1_2\" = Right 1_2" ~:
1277 (Data.Either.rights $
1278 [P.runParser
1279 (Amount.Read.amount <* P.eof)
1280 () "" ("1_2"::Text)])
1281 ~?=
1282 [Amount.nil
1283 { Amount.quantity = Decimal 0 12
1284 , Amount.style =
1285 Amount.Style.nil
1286 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1287 , Amount.Style.precision = 0
1288 }
1289 }]
1290 , "\"1_23\" = Right 1_23" ~:
1291 (Data.Either.rights $
1292 [P.runParser
1293 (Amount.Read.amount <* P.eof)
1294 () "" ("1_23"::Text)])
1295 ~?=
1296 [Amount.nil
1297 { Amount.quantity = Decimal 0 123
1298 , Amount.style =
1299 Amount.Style.nil
1300 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1301 , Amount.Style.precision = 0
1302 }
1303 }]
1304 , "\"1_23_456\" = Right 1_23_456" ~:
1305 (Data.Either.rights $
1306 [P.runParser
1307 (Amount.Read.amount <* P.eof)
1308 () "" ("1_23_456"::Text)])
1309 ~?=
1310 [Amount.nil
1311 { Amount.quantity = Decimal 0 123456
1312 , Amount.style =
1313 Amount.Style.nil
1314 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1315 , Amount.Style.precision = 0
1316 }
1317 }]
1318 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1319 (Data.Either.rights $
1320 [P.runParser
1321 (Amount.Read.amount <* P.eof)
1322 () "" ("1_23_456.7890_12345_678901"::Text)])
1323 ~?=
1324 [Amount.nil
1325 { Amount.quantity = Decimal 15 123456789012345678901
1326 , Amount.style =
1327 Amount.Style.nil
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
1332 }
1333 }]
1334 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1335 (Data.Either.rights $
1336 [P.runParser
1337 (Amount.Read.amount <* P.eof)
1338 () "" ("123456_78901_2345.678_90_1"::Text)])
1339 ~?=
1340 [Amount.nil
1341 { Amount.quantity = Decimal 6 123456789012345678901
1342 , Amount.style =
1343 Amount.Style.nil
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
1348 }
1349 }]
1350 , "\"$1\" = Right $1" ~:
1351 (Data.Either.rights $
1352 [P.runParser
1353 (Amount.Read.amount <* P.eof)
1354 () "" ("$1"::Text)])
1355 ~?=
1356 [Amount.nil
1357 { Amount.quantity = Decimal 0 1
1358 , Amount.style =
1359 Amount.Style.nil
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
1366 }
1367 , Amount.unit = "$"
1368 }]
1369 , "\"1$\" = Right 1$" ~:
1370 (Data.Either.rights $
1371 [P.runParser
1372 (Amount.Read.amount <* P.eof)
1373 () "" ("1$"::Text)])
1374 ~?=
1375 [Amount.nil
1376 { Amount.quantity = Decimal 0 1
1377 , Amount.style =
1378 Amount.Style.nil
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
1385 }
1386 , Amount.unit = "$"
1387 }]
1388 , "\"$ 1\" = Right $ 1" ~:
1389 (Data.Either.rights $
1390 [P.runParser
1391 (Amount.Read.amount <* P.eof)
1392 () "" ("$ 1"::Text)])
1393 ~?=
1394 [Amount.nil
1395 { Amount.quantity = Decimal 0 1
1396 , Amount.style =
1397 Amount.Style.nil
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
1404 }
1405 , Amount.unit = "$"
1406 }]
1407 , "\"1 $\" = Right 1 $" ~:
1408 (Data.Either.rights $
1409 [P.runParser
1410 (Amount.Read.amount <* P.eof)
1411 () "" ("1 $"::Text)])
1412 ~?=
1413 [Amount.nil
1414 { Amount.quantity = Decimal 0 1
1415 , Amount.style =
1416 Amount.Style.nil
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
1423 }
1424 , Amount.unit = "$"
1425 }]
1426 , "\"-$1\" = Right $-1" ~:
1427 (Data.Either.rights $
1428 [P.runParser
1429 (Amount.Read.amount <* P.eof)
1430 () "" ("-$1"::Text)])
1431 ~?=
1432 [Amount.nil
1433 { Amount.quantity = Decimal 0 (-1)
1434 , Amount.style =
1435 Amount.Style.nil
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
1442 }
1443 , Amount.unit = "$"
1444 }]
1445 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1446 (Data.Either.rights $
1447 [P.runParser
1448 (Amount.Read.amount <* P.eof)
1449 () "" ("\"4 2\"1"::Text)])
1450 ~?=
1451 [Amount.nil
1452 { Amount.quantity = Decimal 0 1
1453 , Amount.style =
1454 Amount.Style.nil
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
1461 }
1462 , Amount.unit = "4 2"
1463 }]
1464 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1465 (Data.Either.rights $
1466 [P.runParser
1467 (Amount.Read.amount <* P.eof)
1468 () "" ("1\"4 2\""::Text)])
1469 ~?=
1470 [Amount.nil
1471 { Amount.quantity = Decimal 0 1
1472 , Amount.style =
1473 Amount.Style.nil
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
1480 }
1481 , Amount.unit = "4 2"
1482 }]
1483 , "\"$1.000,00\" = Right $1.000,00" ~:
1484 (Data.Either.rights $
1485 [P.runParser
1486 (Amount.Read.amount <* P.eof)
1487 () "" ("$1.000,00"::Text)])
1488 ~?=
1489 [Amount.nil
1490 { Amount.quantity = Decimal 0 1000
1491 , Amount.style =
1492 Amount.Style.nil
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
1499 }
1500 , Amount.unit = "$"
1501 }]
1502 , "\"1.000,00$\" = Right 1.000,00$" ~:
1503 (Data.Either.rights $
1504 [P.runParser
1505 (Amount.Read.amount <* P.eof)
1506 () "" ("1.000,00$"::Text)])
1507 ~?=
1508 [Amount.nil
1509 { Amount.quantity = Decimal 0 1000
1510 , Amount.style =
1511 Amount.Style.nil
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
1518 }
1519 , Amount.unit = "$"
1520 }]
1521 ]
1522 ]
1523 , "Write" ~: TestList
1524 [ "amount" ~: TestList
1525 [ "nil" ~:
1526 ((Format.Ledger.Write.show
1527 Format.Ledger.Write.Style
1528 { Format.Ledger.Write.style_color=False
1529 , Format.Ledger.Write.style_align=True
1530 } $
1531 Amount.Write.amount
1532 Amount.nil)
1533 ~?=
1534 "0")
1535 , "nil @ prec=2" ~:
1536 ((Format.Ledger.Write.show
1537 Format.Ledger.Write.Style
1538 { Format.Ledger.Write.style_color=False
1539 , Format.Ledger.Write.style_align=True
1540 } $
1541 Amount.Write.amount
1542 Amount.nil
1543 { Amount.style = Amount.Style.nil
1544 { Amount.Style.precision = 2 }
1545 })
1546 ~?=
1547 "0.00")
1548 , "123" ~:
1549 ((Format.Ledger.Write.show
1550 Format.Ledger.Write.Style
1551 { Format.Ledger.Write.style_color=False
1552 , Format.Ledger.Write.style_align=True
1553 } $
1554 Amount.Write.amount
1555 Amount.nil
1556 { Amount.quantity = Decimal 0 123
1557 })
1558 ~?=
1559 "123")
1560 , "-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
1565 } $
1566 Amount.Write.amount
1567 Amount.nil
1568 { Amount.quantity = Decimal 0 (- 123)
1569 })
1570 ~?=
1571 "-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
1577 } $
1578 Amount.Write.amount
1579 Amount.nil
1580 { Amount.quantity = Decimal 1 123
1581 , Amount.style = Amount.Style.nil
1582 { Amount.Style.fractioning = Just '.'
1583 }
1584 })
1585 ~?=
1586 "12")
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
1592 } $
1593 Amount.Write.amount
1594 Amount.nil
1595 { Amount.quantity = Decimal 1 125
1596 , Amount.style = Amount.Style.nil
1597 { Amount.Style.fractioning = Just '.'
1598 }
1599 })
1600 ~?=
1601 "13")
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
1607 } $
1608 Amount.Write.amount
1609 Amount.nil
1610 { Amount.quantity = Decimal 1 123
1611 , Amount.style = Amount.Style.nil
1612 { Amount.Style.fractioning = Just '.'
1613 , Amount.Style.precision = 1
1614 }
1615 })
1616 ~?=
1617 "12.3")
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
1623 } $
1624 Amount.Write.amount
1625 Amount.nil
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]
1631 }
1632 })
1633 ~?=
1634 "1,234.56")
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
1640 } $
1641 Amount.Write.amount
1642 Amount.nil
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]
1648 }
1649 })
1650 ~?=
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
1657 } $
1658 Amount.Write.amount
1659 Amount.nil
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]
1665 }
1666 })
1667 ~?=
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
1674 } $
1675 Amount.Write.amount
1676 Amount.nil
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]
1682 }
1683 })
1684 ~?=
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
1691 } $
1692 Amount.Write.amount
1693 Amount.nil
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]
1699 }
1700 })
1701 ~?=
1702 "1234567.890,12,3,4,5,6,7,8,9")
1703 ]
1704 , "amount_length" ~: TestList
1705 [ "nil" ~:
1706 ((Amount.Write.amount_length
1707 Amount.nil)
1708 ~?=
1709 1)
1710 , "nil @ prec=2" ~:
1711 ((Amount.Write.amount_length
1712 Amount.nil
1713 { Amount.style = Amount.Style.nil
1714 { Amount.Style.precision = 2 }
1715 })
1716 ~?=
1717 4)
1718 , "123" ~:
1719 ((Amount.Write.amount_length
1720 Amount.nil
1721 { Amount.quantity = Decimal 0 123
1722 })
1723 ~?=
1724 3)
1725 , "-123" ~:
1726 ((Amount.Write.amount_length
1727 Amount.nil
1728 { Amount.quantity = Decimal 0 (- 123)
1729 })
1730 ~?=
1731 4)
1732 , "12.3 @ prec=0" ~:
1733 ((Amount.Write.amount_length
1734 Amount.nil
1735 { Amount.quantity = Decimal 1 123
1736 , Amount.style = Amount.Style.nil
1737 { Amount.Style.fractioning = Just '.'
1738 }
1739 })
1740 ~?=
1741 2)
1742 , "12.5 @ prec=0" ~:
1743 ((Amount.Write.amount_length
1744 Amount.nil
1745 { Amount.quantity = Decimal 1 125
1746 , Amount.style = Amount.Style.nil
1747 { Amount.Style.fractioning = Just '.'
1748 }
1749 })
1750 ~?=
1751 2)
1752 , "12.3 @ prec=1" ~:
1753 ((Amount.Write.amount_length
1754 Amount.nil
1755 { Amount.quantity = Decimal 1 123
1756 , Amount.style = Amount.Style.nil
1757 { Amount.Style.fractioning = Just '.'
1758 , Amount.Style.precision = 1
1759 }
1760 })
1761 ~?=
1762 4)
1763 , "1,234.56 @ prec=2" ~:
1764 ((Amount.Write.amount_length
1765 Amount.nil
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]
1771 }
1772 })
1773 ~?=
1774 8)
1775 , "123,456,789,01,2.3456789 @ prec=7" ~:
1776 ((Amount.Write.amount_length
1777 Amount.nil
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]
1783 }
1784 })
1785 ~?=
1786 24)
1787 , "1234567.8,90,123,456,789 @ prec=12" ~:
1788 ((Amount.Write.amount_length
1789 Amount.nil
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]
1795 }
1796 })
1797 ~?=
1798 24)
1799 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
1800 ((Amount.Write.amount_length
1801 Amount.nil
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]
1807 }
1808 })
1809 ~?=
1810 28)
1811 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
1812 ((Amount.Write.amount_length
1813 Amount.nil
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]
1819 }
1820 })
1821 ~?=
1822 28)
1823 , "1000000.000,00,0,0,0,0,0,0,0 @ prec=12" ~:
1824 ((Amount.Write.amount_length
1825 Amount.nil
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]
1831 }
1832 })
1833 ~?=
1834 28)
1835 , "999 @ prec=0" ~:
1836 ((Amount.Write.amount_length $
1837 Amount.nil
1838 { Amount.quantity = Decimal 0 999
1839 , Amount.style = Amount.Style.nil
1840 { Amount.Style.precision = 0
1841 }
1842 })
1843 ~?=
1844 3)
1845 , "1000 @ prec=0" ~:
1846 ((Amount.Write.amount_length $
1847 Amount.nil
1848 { Amount.quantity = Decimal 0 1000
1849 , Amount.style = Amount.Style.nil
1850 { Amount.Style.precision = 0
1851 }
1852 })
1853 ~?=
1854 4)
1855 , "10,00€ @ prec=2" ~:
1856 ((Amount.Write.amount_length $ Amount.eur 10)
1857 ~?=
1858 6)
1859 ]
1860 ]
1861 ]
1862 , "Date" ~: TestList
1863 [ "Read" ~: TestList
1864 [ "date" ~: TestList
1865 [ "2000/01/01" ~:
1866 (Data.Either.rights $
1867 [P.runParser_with_Error
1868 (Date.Read.date id Nothing <* P.eof)
1869 () "" ("2000/01/01"::Text)])
1870 ~?=
1871 [ Time.zonedTimeToUTC $
1872 Time.ZonedTime
1873 (Time.LocalTime
1874 (Time.fromGregorian 2000 01 01)
1875 (Time.TimeOfDay 0 0 0))
1876 (Time.utc)]
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)])
1882 ~?=
1883 [ Time.zonedTimeToUTC $
1884 Time.ZonedTime
1885 (Time.LocalTime
1886 (Time.fromGregorian 2000 01 01)
1887 (Time.TimeOfDay 0 0 0))
1888 (Time.utc)]
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)])
1894 ~?=
1895 [ Time.zonedTimeToUTC $
1896 Time.ZonedTime
1897 (Time.LocalTime
1898 (Time.fromGregorian 2000 01 01)
1899 (Time.TimeOfDay 12 34 0))
1900 (Time.utc)]
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)])
1906 ~?=
1907 [ Time.zonedTimeToUTC $
1908 Time.ZonedTime
1909 (Time.LocalTime
1910 (Time.fromGregorian 2000 01 01)
1911 (Time.TimeOfDay 12 34 56))
1912 (Time.utc)]
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)])
1918 ~?=
1919 [ Time.zonedTimeToUTC $
1920 Time.ZonedTime
1921 (Time.LocalTime
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)])
1930 ~?=
1931 [ Time.zonedTimeToUTC $
1932 Time.ZonedTime
1933 (Time.LocalTime
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)])
1942 ~?=
1943 [ Time.zonedTimeToUTC $
1944 Time.ZonedTime
1945 (Time.LocalTime
1946 (Time.fromGregorian 2000 01 01)
1947 (Time.TimeOfDay 12 34 56))
1948 (Time.TimeZone 60 True "CET")]
1949 , "2001/02/29" ~:
1950 (Data.Either.rights $
1951 [P.runParser_with_Error
1952 (Date.Read.date id Nothing <* P.eof)
1953 () "" ("2001/02/29"::Text)])
1954 ~?=
1955 []
1956 , "01/01" ~:
1957 (Data.Either.rights $
1958 [P.runParser_with_Error
1959 (Date.Read.date id (Just 2000) <* P.eof)
1960 () "" ("01/01"::Text)])
1961 ~?=
1962 [ Time.zonedTimeToUTC $
1963 Time.ZonedTime
1964 (Time.LocalTime
1965 (Time.fromGregorian 2000 01 01)
1966 (Time.TimeOfDay 0 0 0))
1967 (Time.utc)]
1968 ]
1969 ]
1970 , "Write" ~: TestList
1971 [ "date" ~: TestList
1972 [ "nil" ~:
1973 ((Format.Ledger.Write.show
1974 Format.Ledger.Write.Style
1975 { Format.Ledger.Write.style_color=False
1976 , Format.Ledger.Write.style_align=True
1977 } $
1978 Date.Write.date
1979 Date.nil)
1980 ~?=
1981 "1970/01/01")
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
1987 } $
1988 Date.Write.date $
1989 Time.zonedTimeToUTC $
1990 Time.ZonedTime
1991 (Time.LocalTime
1992 (Time.fromGregorian 2000 01 01)
1993 (Time.TimeOfDay 12 34 51))
1994 (Time.TimeZone 60 False "CET"))
1995 ~?=
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
2002 } $
2003 Date.Write.date $
2004 Time.zonedTimeToUTC $
2005 Time.ZonedTime
2006 (Time.LocalTime
2007 (Time.fromGregorian 2000 01 01)
2008 (Time.TimeOfDay 12 34 51))
2009 (Time.TimeZone 60 False ""))
2010 ~?=
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
2017 } $
2018 Date.Write.date $
2019 Time.zonedTimeToUTC $
2020 Time.ZonedTime
2021 (Time.LocalTime
2022 (Time.fromGregorian 2000 01 01)
2023 (Time.TimeOfDay 1 2 3))
2024 (Time.utc))
2025 ~?=
2026 "2000/01/01_01:02:03"
2027 , "01/01_01:02" ~:
2028 (Format.Ledger.Write.show
2029 Format.Ledger.Write.Style
2030 { Format.Ledger.Write.style_color=False
2031 , Format.Ledger.Write.style_align=True
2032 } $
2033 Date.Write.date $
2034 Time.zonedTimeToUTC $
2035 Time.ZonedTime
2036 (Time.LocalTime
2037 (Time.fromGregorian 0 01 01)
2038 (Time.TimeOfDay 1 2 0))
2039 (Time.utc))
2040 ~?=
2041 "01/01_01:02"
2042 , "01/01_01:00" ~:
2043 (Format.Ledger.Write.show
2044 Format.Ledger.Write.Style
2045 { Format.Ledger.Write.style_color=False
2046 , Format.Ledger.Write.style_align=True
2047 } $
2048 Date.Write.date $
2049 Time.zonedTimeToUTC $
2050 Time.ZonedTime
2051 (Time.LocalTime
2052 (Time.fromGregorian 0 01 01)
2053 (Time.TimeOfDay 1 0 0))
2054 (Time.utc))
2055 ~?=
2056 "01/01_01:00"
2057 , "01/01_00:01" ~:
2058 (Format.Ledger.Write.show
2059 Format.Ledger.Write.Style
2060 { Format.Ledger.Write.style_color=False
2061 , Format.Ledger.Write.style_align=True
2062 } $
2063 Date.Write.date $
2064 Time.zonedTimeToUTC $
2065 Time.ZonedTime
2066 (Time.LocalTime
2067 (Time.fromGregorian 0 01 01)
2068 (Time.TimeOfDay 0 1 0))
2069 (Time.utc))
2070 ~?=
2071 "01/01_00:01"
2072 , "01/01" ~:
2073 (Format.Ledger.Write.show
2074 Format.Ledger.Write.Style
2075 { Format.Ledger.Write.style_color=False
2076 , Format.Ledger.Write.style_align=True
2077 } $
2078 Date.Write.date $
2079 Time.zonedTimeToUTC $
2080 Time.ZonedTime
2081 (Time.LocalTime
2082 (Time.fromGregorian 0 01 01)
2083 (Time.TimeOfDay 0 0 0))
2084 (Time.utc))
2085 ~?=
2086 "01/01"
2087 ]
2088 ]
2089 ]
2090 , "Filter" ~: TestList
2091 [ "test" ~: TestList
2092 [ "Filter_Account" ~: TestList
2093 [ "A A" ~?
2094 Filter.test
2095 (Filter.Filter_Account Filter.Eq
2096 [ Filter.Filter_Account_Section_Text
2097 (Filter.Filter_Text_Exact "A")
2098 ])
2099 (("A":|[]::Account))
2100 , "* A" ~?
2101 Filter.test
2102 (Filter.Filter_Account Filter.Eq
2103 [ Filter.Filter_Account_Section_Any
2104 ])
2105 (("A":|[]::Account))
2106 , ": A" ~?
2107 Filter.test
2108 (Filter.Filter_Account Filter.Eq
2109 [ Filter.Filter_Account_Section_Many
2110 ])
2111 (("A":|[]::Account))
2112 , ":A A" ~?
2113 Filter.test
2114 (Filter.Filter_Account Filter.Eq
2115 [ Filter.Filter_Account_Section_Many
2116 , Filter.Filter_Account_Section_Text
2117 (Filter.Filter_Text_Exact "A")
2118 ])
2119 (("A":|[]::Account))
2120 , "A: A" ~?
2121 Filter.test
2122 (Filter.Filter_Account Filter.Eq
2123 [ Filter.Filter_Account_Section_Text
2124 (Filter.Filter_Text_Exact "A")
2125 , Filter.Filter_Account_Section_Many
2126 ])
2127 (("A":|[]::Account))
2128 , "A: A:B" ~?
2129 Filter.test
2130 (Filter.Filter_Account Filter.Eq
2131 [ Filter.Filter_Account_Section_Text
2132 (Filter.Filter_Text_Exact "A")
2133 , Filter.Filter_Account_Section_Many
2134 ])
2135 (("A":|"B":[]::Account))
2136 , "A:B A:B" ~?
2137 Filter.test
2138 (Filter.Filter_Account Filter.Eq
2139 [ Filter.Filter_Account_Section_Text
2140 (Filter.Filter_Text_Exact "A")
2141 , Filter.Filter_Account_Section_Text
2142 (Filter.Filter_Text_Exact "B")
2143 ])
2144 (("A":|"B":[]::Account))
2145 , "A::B A:B" ~?
2146 Filter.test
2147 (Filter.Filter_Account Filter.Eq
2148 [ Filter.Filter_Account_Section_Text
2149 (Filter.Filter_Text_Exact "A")
2150 , Filter.Filter_Account_Section_Many
2151 , Filter.Filter_Account_Section_Many
2152 , Filter.Filter_Account_Section_Text
2153 (Filter.Filter_Text_Exact "B")
2154 ])
2155 (("A":|"B":[]::Account))
2156 , ":B: A:B:C" ~?
2157 Filter.test
2158 (Filter.Filter_Account Filter.Eq
2159 [ Filter.Filter_Account_Section_Many
2160 , Filter.Filter_Account_Section_Text
2161 (Filter.Filter_Text_Exact "B")
2162 , Filter.Filter_Account_Section_Many
2163 ])
2164 (("A":|"B":"C":[]::Account))
2165 , ":C A:B:C" ~?
2166 Filter.test
2167 (Filter.Filter_Account Filter.Eq
2168 [ Filter.Filter_Account_Section_Many
2169 , Filter.Filter_Account_Section_Text
2170 (Filter.Filter_Text_Exact "C")
2171 ])
2172 (("A":|"B":"C":[]::Account))
2173 , "<A:B:C::D A:B" ~?
2174 Filter.test
2175 (Filter.Filter_Account Filter.Lt
2176 [ Filter.Filter_Account_Section_Text
2177 (Filter.Filter_Text_Exact "A")
2178 , Filter.Filter_Account_Section_Text
2179 (Filter.Filter_Text_Exact "B")
2180 , Filter.Filter_Account_Section_Text
2181 (Filter.Filter_Text_Exact "C")
2182 , Filter.Filter_Account_Section_Many
2183 , Filter.Filter_Account_Section_Text
2184 (Filter.Filter_Text_Exact "D")
2185 ])
2186 (("A":|"B":[]::Account))
2187 , ">A:B:C::D A:B:C:CC:CCC:D:E" ~?
2188 Filter.test
2189 (Filter.Filter_Account Filter.Gt
2190 [ Filter.Filter_Account_Section_Text
2191 (Filter.Filter_Text_Exact "A")
2192 , Filter.Filter_Account_Section_Text
2193 (Filter.Filter_Text_Exact "B")
2194 , Filter.Filter_Account_Section_Text
2195 (Filter.Filter_Text_Exact "C")
2196 , Filter.Filter_Account_Section_Many
2197 , Filter.Filter_Account_Section_Text
2198 (Filter.Filter_Text_Exact "D")
2199 ])
2200 (("A":|"B":"C":"CC":"CCC":"D":"E":[]::Account))
2201 ]
2202 , "Filter_Bool" ~: TestList
2203 [ "Any A" ~?
2204 Filter.test
2205 (Filter.Any::Filter.Filter_Bool Filter.Filter_Account)
2206 (("A":|[]::Account))
2207 ]
2208 , "Filter_Ord" ~: TestList
2209 [ "0 < (1, 2)" ~?
2210 Filter.test
2211 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer))
2212 (fromJust $ (Lib.Interval.<=..<=) 1 2)
2213 , "(-2, -1) < 0" ~?
2214 Filter.test
2215 (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer))
2216 (fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
2217 , "not (1 < (0, 2))" ~?
2218 (not $ Filter.test
2219 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer))
2220 (fromJust $ (Lib.Interval.<=..<=) 0 2))
2221 ]
2222 ]
2223 , "Read" ~: TestList
2224 [ "filter_account" ~: TestList
2225 [ "*" ~:
2226 (Data.Either.rights $
2227 [P.runParser
2228 (Filter.Read.filter_account <* P.eof)
2229 () "" ("*"::Text)])
2230 ~?=
2231 map (Filter.Filter_Posting_Type_Any,)
2232 [ Filter.Filter_Account Filter.Eq
2233 [ Filter.Filter_Account_Section_Any ]
2234 ]
2235 , "A" ~:
2236 (Data.Either.rights $
2237 [P.runParser
2238 (Filter.Read.filter_account <* P.eof)
2239 () "" ("A"::Text)])
2240 ~?=
2241 map (Filter.Filter_Posting_Type_Any,)
2242 [ Filter.Filter_Account Filter.Eq
2243 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ]
2244 ]
2245 , "AA" ~:
2246 (Data.Either.rights $
2247 [P.runParser
2248 (Filter.Read.filter_account <* P.eof)
2249 () "" ("AA"::Text)])
2250 ~?=
2251 map (Filter.Filter_Posting_Type_Any,)
2252 [ Filter.Filter_Account Filter.Eq
2253 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "AA") ]
2254 ]
2255 , "::A" ~:
2256 (Data.Either.rights $
2257 [P.runParser
2258 (Filter.Read.filter_account <* P.eof)
2259 () "" ("::A"::Text)])
2260 ~?=
2261 map (Filter.Filter_Posting_Type_Any,)
2262 [ Filter.Filter_Account Filter.Eq
2263 [ Filter.Filter_Account_Section_Many
2264 , Filter.Filter_Account_Section_Many
2265 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2266 ]
2267 ]
2268 , ":A" ~:
2269 (Data.Either.rights $
2270 [P.runParser
2271 (Filter.Read.filter_account <* P.eof)
2272 () "" (":A"::Text)])
2273 ~?=
2274 map (Filter.Filter_Posting_Type_Any,)
2275 [ Filter.Filter_Account Filter.Eq
2276 [ Filter.Filter_Account_Section_Many
2277 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2278 ]
2279 ]
2280 , "A:" ~:
2281 (Data.Either.rights $
2282 [P.runParser
2283 (Filter.Read.filter_account <* P.eof)
2284 () "" ("A:"::Text)])
2285 ~?=
2286 map (Filter.Filter_Posting_Type_Any,)
2287 [ Filter.Filter_Account Filter.Eq
2288 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2289 , Filter.Filter_Account_Section_Many
2290 ]
2291 ]
2292 , "A::" ~:
2293 (Data.Either.rights $
2294 [P.runParser
2295 (Filter.Read.filter_account <* P.eof)
2296 () "" ("A::"::Text)])
2297 ~?=
2298 map (Filter.Filter_Posting_Type_Any,)
2299 [ Filter.Filter_Account Filter.Eq
2300 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2301 , Filter.Filter_Account_Section_Many
2302 , Filter.Filter_Account_Section_Many
2303 ]
2304 ]
2305 , "A:B" ~:
2306 (Data.Either.rights $
2307 [P.runParser
2308 (Filter.Read.filter_account <* P.eof)
2309 () "" ("A:B"::Text)])
2310 ~?=
2311 map (Filter.Filter_Posting_Type_Any,)
2312 [ Filter.Filter_Account Filter.Eq
2313 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2314 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2315 ]
2316 ]
2317 , "A::B" ~:
2318 (Data.Either.rights $
2319 [P.runParser
2320 (Filter.Read.filter_account <* P.eof)
2321 () "" ("A::B"::Text)])
2322 ~?=
2323 map (Filter.Filter_Posting_Type_Any,)
2324 [ Filter.Filter_Account Filter.Eq
2325 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2326 , Filter.Filter_Account_Section_Many
2327 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2328 ]
2329 ]
2330 , "A:::B" ~:
2331 (Data.Either.rights $
2332 [P.runParser
2333 (Filter.Read.filter_account <* P.eof)
2334 () "" ("A:::B"::Text)])
2335 ~?=
2336 map (Filter.Filter_Posting_Type_Any,)
2337 [ Filter.Filter_Account Filter.Eq
2338 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2339 , Filter.Filter_Account_Section_Many
2340 , Filter.Filter_Account_Section_Many
2341 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2342 ]
2343 ]
2344 , "A: " ~:
2345 (Data.Either.rights $
2346 [P.runParser
2347 (Filter.Read.filter_account <* P.char ' ' <* P.eof)
2348 () "" ("A: "::Text)])
2349 ~?=
2350 map (Filter.Filter_Posting_Type_Any,)
2351 [ Filter.Filter_Account Filter.Eq
2352 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2353 , Filter.Filter_Account_Section_Many
2354 ]
2355 ]
2356 , "<=A:B" ~:
2357 (Data.Either.rights $
2358 [P.runParser
2359 (Filter.Read.filter_account <* P.eof)
2360 () "" ("<=A:B"::Text)])
2361 ~?=
2362 map (Filter.Filter_Posting_Type_Any,)
2363 [ Filter.Filter_Account Filter.Le
2364 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2365 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2366 ]
2367 ]
2368 , ">=A:B" ~:
2369 (Data.Either.rights $
2370 [P.runParser
2371 (Filter.Read.filter_account <* P.eof)
2372 () "" (">=A:B"::Text)])
2373 ~?=
2374 map (Filter.Filter_Posting_Type_Any,)
2375 [ Filter.Filter_Account Filter.Ge
2376 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2377 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2378 ]
2379 ]
2380 , "<A:B" ~:
2381 (Data.Either.rights $
2382 [P.runParser
2383 (Filter.Read.filter_account <* P.eof)
2384 () "" ("<A:B"::Text)])
2385 ~?=
2386 map (Filter.Filter_Posting_Type_Any,)
2387 [ Filter.Filter_Account Filter.Lt
2388 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2389 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2390 ]
2391 ]
2392 , ">A:B" ~:
2393 (Data.Either.rights $
2394 [P.runParser
2395 (Filter.Read.filter_account <* P.eof)
2396 () "" (">A:B"::Text)])
2397 ~?=
2398 map (Filter.Filter_Posting_Type_Any,)
2399 [ Filter.Filter_Account Filter.Gt
2400 [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
2401 , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
2402 ]
2403 ]
2404 ]
2405 , "filter_bool" ~: TestList
2406 [ "( E )" ~:
2407 (Data.Either.rights $
2408 [P.runParser
2409 (Filter.Read.filter_bool
2410 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2411 <* P.eof)
2412 () "" ("( E )"::Text)])
2413 ~?=
2414 [ Filter.And (Filter.Bool True) Filter.Any
2415 ]
2416 , "( ( E ) )" ~:
2417 (Data.Either.rights $
2418 [P.runParser
2419 (Filter.Read.filter_bool
2420 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2421 <* P.eof)
2422 () "" ("( ( E ) )"::Text)])
2423 ~?=
2424 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
2425 ]
2426 , "( E ) & ( E )" ~:
2427 (Data.Either.rights $
2428 [P.runParser
2429 (Filter.Read.filter_bool
2430 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2431 <* P.eof)
2432 () "" ("( E ) & ( E )"::Text)])
2433 ~?=
2434 [ Filter.And
2435 (Filter.And (Filter.Bool True) Filter.Any)
2436 (Filter.And (Filter.Bool True) Filter.Any)
2437 ]
2438 , "( E ) + ( E )" ~:
2439 (Data.Either.rights $
2440 [P.runParser
2441 (Filter.Read.filter_bool
2442 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2443 <* P.eof)
2444 () "" ("( E ) + ( E )"::Text)])
2445 ~?=
2446 [ Filter.Or
2447 (Filter.And (Filter.Bool True) Filter.Any)
2448 (Filter.And (Filter.Bool True) Filter.Any)
2449 ]
2450 , "( E ) - ( E )" ~:
2451 (Data.Either.rights $
2452 [P.runParser
2453 (Filter.Read.filter_bool
2454 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2455 <* P.eof)
2456 () "" ("( E ) - ( E )"::Text)])
2457 ~?=
2458 [ Filter.And
2459 (Filter.And (Filter.Bool True) Filter.Any)
2460 (Filter.Not (Filter.And (Filter.Bool True) Filter.Any))
2461 ]
2462 , "(- E )" ~:
2463 (Data.Either.rights $
2464 [P.runParser
2465 (Filter.Read.filter_bool
2466 [ P.char 'E' >> return (return $ Filter.Bool True) ]
2467 <* P.eof)
2468 () "" ("(- E )"::Text)])
2469 ~?=
2470 [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any
2471 ]
2472 ]
2473 ]
2474 ]
2475 , "Balance" ~: TestList
2476 [ "balance" ~: TestList
2477 [ "[A+$1] = A+$1 & $+1" ~:
2478 (Balance.cons
2479 (Format.Ledger.posting ("A":|[]))
2480 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2481 }
2482 Balance.empty)
2483 ~?=
2484 Balance.Balance
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 $
2491 Data.Map.fromList $
2492 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2493 [ Balance.Unit_Sum
2494 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2495 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2496 ["A":|[]]
2497 }
2498 ]
2499 }
2500 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
2501 (Data.List.foldl
2502 (flip Balance.cons)
2503 Balance.empty
2504 [ (Format.Ledger.posting ("A":|[]))
2505 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2506 }
2507 , (Format.Ledger.posting ("A":|[]))
2508 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2509 }
2510 ])
2511 ~?=
2512 Balance.Balance
2513 { Balance.balance_by_account =
2514 Lib.TreeMap.from_List const $
2515 [ ( "A":|[]
2516 , Balance.Account_Sum $
2517 Data.Map.fromListWith const $
2518 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance s, s))
2519 [ Amount.Sum_Both
2520 (Amount.usd $ -1)
2521 (Amount.usd $ 1)
2522 ]
2523 ) ]
2524 , Balance.balance_by_unit =
2525 Balance.Balance_by_Unit $
2526 Data.Map.fromList $
2527 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2528 [ Balance.Unit_Sum
2529 { Balance.unit_sum_amount = Amount.Sum_Both
2530 (Amount.usd $ -1)
2531 (Amount.usd $ 1)
2532 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2533 ["A":|[]]
2534 }
2535 ]
2536 }
2537 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
2538 (Data.List.foldl
2539 (flip Balance.cons)
2540 Balance.empty
2541 [ (Format.Ledger.posting ("A":|[]))
2542 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2543 }
2544 , (Format.Ledger.posting ("A":|[]))
2545 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.eur $ -1 ]
2546 }
2547 ])
2548 ~?=
2549 Balance.Balance
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 $
2556 Data.Map.fromList $
2557 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2558 [ Balance.Unit_Sum
2559 { Balance.unit_sum_amount = Amount.Sum_Positive (Amount.usd $ 1)
2560 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2561 ["A":|[]]
2562 }
2563 , Balance.Unit_Sum
2564 { Balance.unit_sum_amount = Amount.Sum_Negative (Amount.eur $ -1)
2565 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2566 ["A":|[]]
2567 }
2568 ]
2569 }
2570 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
2571 (Data.List.foldl
2572 (flip Balance.cons)
2573 Balance.empty
2574 [ (Format.Ledger.posting ("A":|[]))
2575 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2576 }
2577 , (Format.Ledger.posting ("B":|[]))
2578 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1 ]
2579 }
2580 ])
2581 ~?=
2582 Balance.Balance
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 ])
2588 ]
2589 , Balance.balance_by_unit =
2590 Balance.Balance_by_Unit $
2591 Data.Map.fromList $
2592 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2593 [ Balance.Unit_Sum
2594 { Balance.unit_sum_amount = Amount.Sum_Both
2595 (Amount.usd $ -1)
2596 (Amount.usd $ 1)
2597 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2598 ["A":|[], "B":|[]]
2599 }
2600 ]
2601 }
2602 , "[A+$1, B+$1]" ~:
2603 (Data.List.foldl
2604 (flip Balance.cons)
2605 Balance.empty
2606 [ (Format.Ledger.posting ("A":|[]))
2607 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2608 }
2609 , (Format.Ledger.posting ("B":|[]))
2610 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1 ]
2611 }
2612 ])
2613 ~?=
2614 Balance.Balance
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 ])
2620 ]
2621 , Balance.balance_by_unit =
2622 Balance.Balance_by_Unit $
2623 Data.Map.fromList $
2624 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2625 [ Balance.Unit_Sum
2626 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2627 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2628 ["A":|[], "B":|[]]
2629 }
2630 ]
2631 }
2632 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
2633 (Data.List.foldl
2634 (flip Balance.cons)
2635 Balance.empty
2636 [ (Format.Ledger.posting ("A":|[]))
2637 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
2638 }
2639 , (Format.Ledger.posting ("A":|[]))
2640 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
2641 }
2642 ])
2643 ~?=
2644 Balance.Balance
2645 { Balance.balance_by_account =
2646 Lib.TreeMap.from_List const $
2647 [ ("A":|[]
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)
2653 ]
2654 )
2655 ]
2656 , Balance.balance_by_unit =
2657 Balance.Balance_by_Unit $
2658 Data.Map.fromList $
2659 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2660 [ Balance.Unit_Sum
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 (,())
2663 ["A":|[]]
2664 }
2665 , Balance.Unit_Sum
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 (,())
2668 ["A":|[]]
2669 }
2670 ]
2671 }
2672 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
2673 (Data.List.foldl
2674 (flip Balance.cons)
2675 Balance.empty
2676 [ (Format.Ledger.posting ("A":|[]))
2677 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
2678 }
2679 , (Format.Ledger.posting ("B":|[]))
2680 { Format.Ledger.posting_amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
2681 }
2682 ])
2683 ~?=
2684 Balance.Balance
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 ])
2690 ]
2691 , Balance.balance_by_unit =
2692 Balance.Balance_by_Unit $
2693 Data.Map.fromList $
2694 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2695 [ Balance.Unit_Sum
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 (,())
2698 ["A":|[], "B":|[]]
2699 }
2700 , Balance.Unit_Sum
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 (,())
2703 ["A":|[], "B":|[]]
2704 }
2705 , Balance.Unit_Sum
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 (,())
2708 ["A":|[], "B":|[]]
2709 }
2710 ]
2711 }
2712 ]
2713 , "union" ~: TestList
2714 [ "empty empty = empty" ~:
2715 Balance.union Balance.empty Balance.empty
2716 ~?=
2717 (Balance.empty::Balance.Balance Amount)
2718 , "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
2719 Balance.union
2720 (Balance.Balance
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 $
2727 Data.Map.fromList $
2728 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2729 [ Balance.Unit_Sum
2730 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2731 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2732 ["A":|[]]
2733 }
2734 ]
2735 })
2736 (Balance.Balance
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 $
2743 Data.Map.fromList $
2744 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2745 [ Balance.Unit_Sum
2746 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2747 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2748 ["A":|[]]
2749 }
2750 ]
2751 })
2752 ~?=
2753 Balance.Balance
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 $
2760 Data.Map.fromList $
2761 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2762 [ Balance.Unit_Sum
2763 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2764 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2765 ["A":|[]]
2766 }
2767 ]
2768 }
2769 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
2770 Balance.union
2771 (Balance.Balance
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 $
2778 Data.Map.fromList $
2779 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2780 [ Balance.Unit_Sum
2781 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2782 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2783 ["A":|[]]
2784 }
2785 ]
2786 })
2787 (Balance.Balance
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 $
2794 Data.Map.fromList $
2795 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2796 [ Balance.Unit_Sum
2797 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2798 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2799 ["B":|[]]
2800 }
2801 ]
2802 })
2803 ~?=
2804 Balance.Balance
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 $
2812 Data.Map.fromList $
2813 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2814 [ Balance.Unit_Sum
2815 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
2816 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2817 ["A":|[], "B":|[]]
2818 }
2819 ]
2820 }
2821 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
2822 Balance.union
2823 (Balance.Balance
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 $
2830 Data.Map.fromList $
2831 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2832 [ Balance.Unit_Sum
2833 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2834 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2835 ["A":|[]]
2836 }
2837 ]
2838 })
2839 (Balance.Balance
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 $
2846 Data.Map.fromList $
2847 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2848 [ Balance.Unit_Sum
2849 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2850 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2851 ["B":|[]]
2852 }
2853 ]
2854 })
2855 ~?=
2856 Balance.Balance
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 $
2864 Data.Map.fromList $
2865 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
2866 [ Balance.Unit_Sum
2867 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
2868 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2869 ["A":|[]]
2870 }
2871 , Balance.Unit_Sum
2872 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
2873 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
2874 ["B":|[]]
2875 }
2876 ]
2877 }
2878 ]
2879 , "expanded" ~: TestList
2880 [ "mempty" ~:
2881 Balance.expanded
2882 Lib.TreeMap.empty
2883 ~?=
2884 (Lib.TreeMap.empty::Balance.Expanded Amount)
2885 , "A+$1 = A+$1" ~:
2886 Balance.expanded
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 ]) ])
2890 ~?=
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 ]
2901 })
2902 ])
2903 , "A/A+$1 = A+$1 A/A+$1" ~:
2904 Balance.expanded
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 ]) ])
2908 ~?=
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 $
2918 Amount.from_List []
2919 })
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 ]
2929 })
2930 ])
2931 , "A/B+$1 = A+$1 A/B+$1" ~:
2932 Balance.expanded
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 ]) ])
2936 ~?=
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 $
2946 Amount.from_List []
2947 })
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 ]
2957 })
2958 ])
2959 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
2960 Balance.expanded
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 ]) ])
2964 ~?=
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 $
2974 Amount.from_List []
2975 })
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 $
2984 Amount.from_List []
2985 })
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 ]
2995 })
2996 ])
2997 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
2998 Balance.expanded
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 ])
3003 ])
3004 ~?=
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 ]
3015 })
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 ]
3025 })
3026 ])
3027 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
3028 Balance.expanded
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 ])
3034 ])
3035 ~?=
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 ]
3046 })
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 ]
3056 })
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 ]
3066 })
3067 ])
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" ~:
3069 Balance.expanded
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 ])
3076 ])
3077 ~?=
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 ]
3088 })
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 ]
3098 })
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 ]
3108 })
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 ]
3118 })
3119 ])
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" ~:
3121 Balance.expanded
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 ])
3128 ])
3129 ~?=
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 ]
3140 })
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 ]
3150 })
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 ]
3160 })
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 $
3169 Amount.from_List []
3170 })
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 ]
3180 })
3181 ])
3182 ]
3183 , "deviation" ~: TestList
3184 [ "{A+$1, $1}" ~:
3185 (Balance.deviation $
3186 Balance.Balance
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 [])
3192 ]
3193 , Balance.balance_by_unit =
3194 Balance.Balance_by_Unit $
3195 Data.Map.fromList $
3196 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3197 [ Balance.Unit_Sum
3198 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3199 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3200 ["A":|[]]
3201 }
3202 ]
3203 })
3204 ~?=
3205 (Balance.Deviation $
3206 Balance.Balance_by_Unit $
3207 Data.Map.fromList $
3208 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3209 [ Balance.Unit_Sum
3210 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3211 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3212 ["B":|[]]
3213 }
3214 ])
3215 , "{A+$1 B+$1, $2}" ~:
3216 (Balance.deviation $
3217 Balance.Balance
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 ])
3223 ]
3224 , Balance.balance_by_unit =
3225 Balance.Balance_by_Unit $
3226 Data.Map.fromList $
3227 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3228 [ Balance.Unit_Sum
3229 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3230 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3231 [ "A":|[]
3232 , "B":|[]
3233 ]
3234 }
3235 ]
3236 })
3237 ~?=
3238 (Balance.Deviation $
3239 Balance.Balance_by_Unit $
3240 Data.Map.fromList $
3241 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3242 [ Balance.Unit_Sum
3243 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3244 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3245 [
3246 ]
3247 }
3248 ])
3249 ]
3250 , "is_equilibrium_inferrable" ~: TestList
3251 [ "nil" ~: TestCase $
3252 (@=?) True $
3253 Balance.is_equilibrium_inferrable $
3254 Balance.deviation $
3255 (Balance.empty::Balance.Balance Amount.Amount)
3256 , "{A+$0, $+0}" ~: TestCase $
3257 (@=?) True $
3258 Balance.is_equilibrium_inferrable $
3259 Balance.deviation $
3260 Balance.Balance
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 ])
3265 ]
3266 , Balance.balance_by_unit =
3267 Balance.Balance_by_Unit $
3268 Data.Map.fromList $
3269 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3270 [ Balance.Unit_Sum
3271 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3272 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3273 ["A":|[]]
3274 }
3275 ]
3276 }
3277 , "{A+$1, $+1}" ~: TestCase $
3278 (@=?) False $
3279 Balance.is_equilibrium_inferrable $
3280 Balance.deviation $
3281 Balance.Balance
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 ])
3286 ]
3287 , Balance.balance_by_unit =
3288 Balance.Balance_by_Unit $
3289 Data.Map.fromList $
3290 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3291 [ Balance.Unit_Sum
3292 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3293 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3294 ["A":|[]]
3295 }
3296 ]
3297 }
3298 , "{A+$0+€0, $0 €+0}" ~: TestCase $
3299 (@=?) True $
3300 Balance.is_equilibrium_inferrable $
3301 Balance.deviation $
3302 Balance.Balance
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 ])
3307 ]
3308 , Balance.balance_by_unit =
3309 Balance.Balance_by_Unit $
3310 Data.Map.fromList $
3311 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3312 [ Balance.Unit_Sum
3313 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3314 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3315 ["A":|[]]
3316 }
3317 , Balance.Unit_Sum
3318 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3319 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3320 ["A":|[]]
3321 }
3322 ]
3323 }
3324 , "{A+$1, B-$1, $+0}" ~: TestCase $
3325 (@=?) True $
3326 Balance.is_equilibrium_inferrable $
3327 Balance.deviation $
3328 Balance.Balance
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 ])
3334 ]
3335 , Balance.balance_by_unit =
3336 Balance.Balance_by_Unit $
3337 Data.Map.fromList $
3338 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3339 [ Balance.Unit_Sum
3340 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3341 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3342 ["A":|[], "B":|[]]
3343 }
3344 ]
3345 }
3346 , "{A+$1 B, $+1}" ~: TestCase $
3347 (@=?) True $
3348 Balance.is_equilibrium_inferrable $
3349 Balance.deviation $
3350 Balance.Balance
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 [])
3356 ]
3357 , Balance.balance_by_unit =
3358 Balance.Balance_by_Unit $
3359 Data.Map.fromList $
3360 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3361 [ Balance.Unit_Sum
3362 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3363 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3364 ["A":|[]]
3365 }
3366 ]
3367 }
3368 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
3369 (@=?) True $
3370 Balance.is_equilibrium_inferrable $
3371 Balance.deviation $
3372 Balance.Balance
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 ])
3378 ]
3379 , Balance.balance_by_unit =
3380 Balance.Balance_by_Unit $
3381 Data.Map.fromList $
3382 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3383 [ Balance.Unit_Sum
3384 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 1
3385 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3386 ["A":|[]]
3387 }
3388 , Balance.Unit_Sum
3389 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3390 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3391 ["B":|[]]
3392 }
3393 ]
3394 }
3395 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
3396 (@=?) True $
3397 Balance.is_equilibrium_inferrable $
3398 Balance.deviation $
3399 Balance.Balance
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 ])
3405 ]
3406 , Balance.balance_by_unit =
3407 Balance.Balance_by_Unit $
3408 Data.Map.fromList $
3409 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3410 [ Balance.Unit_Sum
3411 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3412 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3413 ["A":|[], "B":|[]]
3414 }
3415 , Balance.Unit_Sum
3416 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 1
3417 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3418 ["B":|[]]
3419 }
3420 ]
3421 }
3422 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
3423 (@=?) True $
3424 Balance.is_equilibrium_inferrable $
3425 Balance.deviation $
3426 Balance.Balance
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 ])
3432 ]
3433 , Balance.balance_by_unit =
3434 Balance.Balance_by_Unit $
3435 Data.Map.fromList $
3436 Data.List.map (\s -> (Amount.unit $ Amount.sum_balance $ Balance.unit_sum_amount s, s))
3437 [ Balance.Unit_Sum
3438 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 0
3439 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3440 ["A":|[], "B":|[]]
3441 }
3442 , Balance.Unit_Sum
3443 { Balance.unit_sum_amount = Amount.sum $ Amount.eur $ 0
3444 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3445 ["A":|[], "B":|[]]
3446 }
3447 , Balance.Unit_Sum
3448 { Balance.unit_sum_amount = Amount.sum $ Amount.gbp $ 0
3449 , Balance.unit_sum_accounts = Data.Map.fromList $ Data.List.map (,())
3450 ["A":|[], "B":|[]]
3451 }
3452 ]
3453 }
3454 ]
3455 , "infer_equilibrium" ~: TestList
3456 [ "{A+$1 B}" ~:
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 [] }
3463 ])
3464 ~?=
3465 (Right $
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 ] }
3471 ])
3472 , "{A+$1 B-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 ] }
3479 ])
3480 ~?=
3481 (Right $
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 ] }
3487 ])
3488 , "{A+$1 B+$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 ] }
3495 ])
3496 ~?=
3497 (Left
3498 [ Balance.Unit_Sum
3499 { Balance.unit_sum_amount = Amount.sum $ Amount.usd $ 2
3500 , Balance.unit_sum_accounts = Data.Map.fromList []}
3501 ])
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 ] }
3509 ])
3510 ~?=
3511 (Right $
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 ] }
3517 ])
3518 ]
3519 ]
3520 , "Format" ~: TestList
3521 [ "Ledger" ~: TestList
3522 [ "Read" ~: TestList
3523 [ "posting_type" ~: TestList
3524 [ "A" ~:
3525 Format.Ledger.Read.posting_type
3526 ("A":|[])
3527 ~?=
3528 (Posting.Posting_Type_Regular, "A":|[])
3529 , "(" ~:
3530 Format.Ledger.Read.posting_type
3531 ("(":|[])
3532 ~?=
3533 (Posting.Posting_Type_Regular, "(":|[])
3534 , ")" ~:
3535 Format.Ledger.Read.posting_type
3536 (")":|[])
3537 ~?=
3538 (Posting.Posting_Type_Regular, ")":|[])
3539 , "()" ~:
3540 Format.Ledger.Read.posting_type
3541 ("()":|[])
3542 ~?=
3543 (Posting.Posting_Type_Regular, "()":|[])
3544 , "( )" ~:
3545 Format.Ledger.Read.posting_type
3546 ("( )":|[])
3547 ~?=
3548 (Posting.Posting_Type_Regular, "( )":|[])
3549 , "(A)" ~:
3550 Format.Ledger.Read.posting_type
3551 ("(A)":|[])
3552 ~?=
3553 (Posting.Posting_Type_Virtual, "A":|[])
3554 , "(A:B:C)" ~:
3555 Format.Ledger.Read.posting_type
3556 ("(A":|["B", "C)"])
3557 ~?=
3558 (Posting.Posting_Type_Virtual, "A":|["B", "C"])
3559 , "A:B:C" ~:
3560 Format.Ledger.Read.posting_type
3561 ("A":|["B", "C"])
3562 ~?=
3563 (Posting.Posting_Type_Regular, "A":|["B", "C"])
3564 , "(A):B:C" ~:
3565 Format.Ledger.Read.posting_type
3566 ("(A)":|["B", "C"])
3567 ~?=
3568 (Posting.Posting_Type_Regular, "(A)":|["B", "C"])
3569 , "A:(B):C" ~:
3570 Format.Ledger.Read.posting_type
3571 ("A":|["(B)", "C"])
3572 ~?=
3573 (Posting.Posting_Type_Regular, "A":|["(B)", "C"])
3574 , "A:B:(C)" ~:
3575 Format.Ledger.Read.posting_type
3576 ("A":|["B", "(C)"])
3577 ~?=
3578 (Posting.Posting_Type_Regular, "A":|["B", "(C)"])
3579 , "[" ~:
3580 Format.Ledger.Read.posting_type
3581 ("[":|[])
3582 ~?=
3583 (Posting.Posting_Type_Regular, "[":|[])
3584 , "]" ~:
3585 Format.Ledger.Read.posting_type
3586 ("]":|[])
3587 ~?=
3588 (Posting.Posting_Type_Regular, "]":|[])
3589 , "[]" ~:
3590 Format.Ledger.Read.posting_type
3591 ("[]":|[])
3592 ~?=
3593 (Posting.Posting_Type_Regular, "[]":|[])
3594 , "[ ]" ~:
3595 Format.Ledger.Read.posting_type
3596 ("[ ]":|[])
3597 ~?=
3598 (Posting.Posting_Type_Regular, "[ ]":|[])
3599 , "[A]" ~:
3600 Format.Ledger.Read.posting_type
3601 ("[A]":|[])
3602 ~?=
3603 (Posting.Posting_Type_Virtual_Balanced, "A":|[])
3604 , "[A:B:C]" ~:
3605 Format.Ledger.Read.posting_type
3606 ("[A":|["B", "C]"])
3607 ~?=
3608 (Posting.Posting_Type_Virtual_Balanced, "A":|["B", "C"])
3609 , "A:B:C" ~:
3610 Format.Ledger.Read.posting_type
3611 ("A":|["B", "C"])
3612 ~?=
3613 (Posting.Posting_Type_Regular, "A":|["B", "C"])
3614 , "[A]:B:C" ~:
3615 Format.Ledger.Read.posting_type
3616 ("[A]":|["B", "C"])
3617 ~?=
3618 (Posting.Posting_Type_Regular, "[A]":|["B", "C"])
3619 , "A:[B]:C" ~:
3620 Format.Ledger.Read.posting_type
3621 ("A":|["[B]", "C"])
3622 ~?=
3623 (Posting.Posting_Type_Regular, "A":|["[B]", "C"])
3624 , "A:B:[C]" ~:
3625 Format.Ledger.Read.posting_type
3626 ("A":|["B", "[C]"])
3627 ~?=
3628 (Posting.Posting_Type_Regular, "A":|["B", "[C]"])
3629 ]
3630 , "comment" ~: TestList
3631 [ "; some comment = Right \" some comment\"" ~:
3632 (Data.Either.rights $
3633 [P.runParser
3634 (Format.Ledger.Read.comment <* P.eof)
3635 () "" ("; some comment"::Text)])
3636 ~?=
3637 [ " some comment" ]
3638 , "; some comment \\n = Right \" some comment \"" ~:
3639 (Data.Either.rights $
3640 [P.runParser
3641 (Format.Ledger.Read.comment <* P.newline <* P.eof)
3642 () "" ("; some comment \n"::Text)])
3643 ~?=
3644 [ " some comment " ]
3645 , "; some comment \\r\\n = Right \" some comment \"" ~:
3646 (Data.Either.rights $
3647 [P.runParser
3648 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
3649 () "" ("; some comment \r\n"::Text)])
3650 ~?=
3651 [ " some comment " ]
3652 ]
3653 , "comments" ~: TestList
3654 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
3655 (Data.Either.rights $
3656 [P.runParser
3657 (Format.Ledger.Read.comments <* P.eof)
3658 () "" ("; some comment\n ; some other comment"::Text)])
3659 ~?=
3660 [ [" some comment", " some other comment"] ]
3661 , "; some comment \\n = Right \" some comment \"" ~:
3662 (Data.Either.rights $
3663 [P.runParser
3664 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
3665 () "" ("; some comment \n"::Text)])
3666 ~?=
3667 [ [" some comment "] ]
3668 ]
3669 , "tag_value" ~: TestList
3670 [ "," ~:
3671 (Data.Either.rights $
3672 [P.runParser
3673 (Format.Ledger.Read.tag_value <* P.eof)
3674 () "" (","::Text)])
3675 ~?=
3676 [","]
3677 , ",\\n" ~:
3678 (Data.Either.rights $
3679 [P.runParser
3680 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
3681 () "" (",\n"::Text)])
3682 ~?=
3683 [","]
3684 , ",x" ~:
3685 (Data.Either.rights $
3686 [P.runParser
3687 (Format.Ledger.Read.tag_value <* P.eof)
3688 () "" (",x"::Text)])
3689 ~?=
3690 [",x"]
3691 , ",x:" ~:
3692 (Data.Either.rights $
3693 [P.runParser
3694 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
3695 () "" (",x:"::Text)])
3696 ~?=
3697 [""]
3698 , "v, v, n:" ~:
3699 (Data.Either.rights $
3700 [P.runParser
3701 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
3702 () "" ("v, v, n:"::Text)])
3703 ~?=
3704 ["v, v"]
3705 ]
3706 , "tag" ~: TestList
3707 [ "Name:" ~:
3708 (Data.Either.rights $
3709 [P.runParser
3710 (Format.Ledger.Read.tag <* P.eof)
3711 () "" ("Name:"::Text)])
3712 ~?=
3713 [("Name", "")]
3714 , "Name:Value" ~:
3715 (Data.Either.rights $
3716 [P.runParser
3717 (Format.Ledger.Read.tag <* P.eof)
3718 () "" ("Name:Value"::Text)])
3719 ~?=
3720 [("Name", "Value")]
3721 , "Name:Value\\n" ~:
3722 (Data.Either.rights $
3723 [P.runParser
3724 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
3725 () "" ("Name:Value\n"::Text)])
3726 ~?=
3727 [("Name", "Value")]
3728 , "Name:Val ue" ~:
3729 (Data.Either.rights $
3730 [P.runParser
3731 (Format.Ledger.Read.tag <* P.eof)
3732 () "" ("Name:Val ue"::Text)])
3733 ~?=
3734 [("Name", "Val ue")]
3735 , "Name:," ~:
3736 (Data.Either.rights $
3737 [P.runParser
3738 (Format.Ledger.Read.tag <* P.eof)
3739 () "" ("Name:,"::Text)])
3740 ~?=
3741 [("Name", ",")]
3742 , "Name:Val,ue" ~:
3743 (Data.Either.rights $
3744 [P.runParser
3745 (Format.Ledger.Read.tag <* P.eof)
3746 () "" ("Name:Val,ue"::Text)])
3747 ~?=
3748 [("Name", "Val,ue")]
3749 , "Name:Val,ue:" ~:
3750 (Data.Either.rights $
3751 [P.runParser
3752 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
3753 () "" ("Name:Val,ue:"::Text)])
3754 ~?=
3755 [("Name", "Val")]
3756 ]
3757 , "tags" ~: TestList
3758 [ "Name:" ~:
3759 (Data.Either.rights $
3760 [P.runParser
3761 (Format.Ledger.Read.tags <* P.eof)
3762 () "" ("Name:"::Text)])
3763 ~?=
3764 [Data.Map.fromList
3765 [ ("Name", [""])
3766 ]
3767 ]
3768 , "Name:," ~:
3769 (Data.Either.rights $
3770 [P.runParser
3771 (Format.Ledger.Read.tags <* P.eof)
3772 () "" ("Name:,"::Text)])
3773 ~?=
3774 [Data.Map.fromList
3775 [ ("Name", [","])
3776 ]
3777 ]
3778 , "Name:,Name:" ~:
3779 (Data.Either.rights $
3780 [P.runParser
3781 (Format.Ledger.Read.tags <* P.eof)
3782 () "" ("Name:,Name:"::Text)])
3783 ~?=
3784 [Data.Map.fromList
3785 [ ("Name", ["", ""])
3786 ]
3787 ]
3788 , "Name:,Name2:" ~:
3789 (Data.Either.rights $
3790 [P.runParser
3791 (Format.Ledger.Read.tags <* P.eof)
3792 () "" ("Name:,Name2:"::Text)])
3793 ~?=
3794 [Data.Map.fromList
3795 [ ("Name", [""])
3796 , ("Name2", [""])
3797 ]
3798 ]
3799 , "Name: , Name2:" ~:
3800 (Data.Either.rights $
3801 [P.runParser
3802 (Format.Ledger.Read.tags <* P.eof)
3803 () "" ("Name: , Name2:"::Text)])
3804 ~?=
3805 [Data.Map.fromList
3806 [ ("Name", [" "])
3807 , ("Name2", [""])
3808 ]
3809 ]
3810 , "Name:,Name2:,Name3:" ~:
3811 (Data.Either.rights $
3812 [P.runParser
3813 (Format.Ledger.Read.tags <* P.eof)
3814 () "" ("Name:,Name2:,Name3:"::Text)])
3815 ~?=
3816 [Data.Map.fromList
3817 [ ("Name", [""])
3818 , ("Name2", [""])
3819 , ("Name3", [""])
3820 ]
3821 ]
3822 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
3823 (Data.Either.rights $
3824 [P.runParser
3825 (Format.Ledger.Read.tags <* P.eof)
3826 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
3827 ~?=
3828 [Data.Map.fromList
3829 [ ("Name", ["Val ue"])
3830 , ("Name2", ["V a l u e"])
3831 , ("Name3", ["V al ue"])
3832 ]
3833 ]
3834 ]
3835 , "posting" ~: TestList
3836 [ " A:B:C = Right A:B:C" ~:
3837 (Data.Either.rights $
3838 [P.runParser_with_Error
3839 (Format.Ledger.Read.posting <* P.eof)
3840 ( Format.Ledger.Read.context () Format.Ledger.journal
3841 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3842 "" (" A:B:C"::Text)])
3843 ~?=
3844 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
3845 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3846 }
3847 , Posting.Posting_Type_Regular
3848 )
3849 ]
3850 , " !A:B:C = Right !A:B:C" ~:
3851 (Data.List.map fst $
3852 Data.Either.rights $
3853 [P.runParser_with_Error
3854 (Format.Ledger.Read.posting <* P.eof)
3855 ( Format.Ledger.Read.context () Format.Ledger.journal
3856 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3857 "" (" !A:B:C"::Text)])
3858 ~?=
3859 [ (Format.Ledger.posting ("A":|["B", "C"]))
3860 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3861 , Format.Ledger.posting_status = True
3862 }
3863 ]
3864 , " *A:B:C = Right *A:B:C" ~:
3865 (Data.List.map fst $
3866 Data.Either.rights $
3867 [P.runParser_with_Error
3868 (Format.Ledger.Read.posting <* P.eof)
3869 ( Format.Ledger.Read.context () Format.Ledger.journal
3870 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3871 "" (" *A:B:C"::Text)])
3872 ~?=
3873 [ (Format.Ledger.posting ("A":|["B", "C"]))
3874 { Format.Ledger.posting_amounts = Data.Map.fromList []
3875 , Format.Ledger.posting_comments = []
3876 , Format.Ledger.posting_dates = []
3877 , Format.Ledger.posting_status = True
3878 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3879 , Format.Ledger.posting_tags = Data.Map.fromList []
3880 }
3881 ]
3882 , " A:B:C $1 = Right A:B:C $1" ~:
3883 (Data.List.map fst $
3884 Data.Either.rights $
3885 [P.runParser_with_Error
3886 (Format.Ledger.Read.posting <* P.eof)
3887 ( Format.Ledger.Read.context () Format.Ledger.journal
3888 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3889 "" (" A:B:C $1"::Text)])
3890 ~?=
3891 [ (Format.Ledger.posting ("A":|["B","C $1"]))
3892 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3893 }
3894 ]
3895 , " A:B:C $1 = Right A:B:C $1" ~:
3896 (Data.List.map fst $
3897 Data.Either.rights $
3898 [P.runParser_with_Error
3899 (Format.Ledger.Read.posting <* P.eof)
3900 ( Format.Ledger.Read.context () Format.Ledger.journal
3901 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3902 "" (" A:B:C $1"::Text)])
3903 ~?=
3904 [ (Format.Ledger.posting ("A":|["B", "C"]))
3905 { Format.Ledger.posting_amounts = Data.Map.fromList
3906 [ ("$", Amount.nil
3907 { Amount.quantity = 1
3908 , Amount.style = Amount.Style.nil
3909 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3910 , Amount.Style.unit_spaced = Just False
3911 }
3912 , Amount.unit = "$"
3913 })
3914 ]
3915 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3916 }
3917 ]
3918 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
3919 (Data.List.map fst $
3920 Data.Either.rights $
3921 [P.runParser_with_Error
3922 (Format.Ledger.Read.posting <* P.eof)
3923 ( Format.Ledger.Read.context () Format.Ledger.journal
3924 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3925 "" (" A:B:C $1 + 1€"::Text)])
3926 ~?=
3927 [ (Format.Ledger.posting ("A":|["B", "C"]))
3928 { Format.Ledger.posting_amounts = Data.Map.fromList
3929 [ ("$", Amount.nil
3930 { Amount.quantity = 1
3931 , Amount.style = Amount.Style.nil
3932 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3933 , Amount.Style.unit_spaced = Just False
3934 }
3935 , Amount.unit = "$"
3936 })
3937 , ("€", Amount.nil
3938 { Amount.quantity = 1
3939 , Amount.style = Amount.Style.nil
3940 { Amount.Style.unit_side = Just Amount.Style.Side_Right
3941 , Amount.Style.unit_spaced = Just False
3942 }
3943 , Amount.unit = "€"
3944 })
3945 ]
3946 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3947 }
3948 ]
3949 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
3950 (Data.List.map fst $
3951 Data.Either.rights $
3952 [P.runParser_with_Error
3953 (Format.Ledger.Read.posting <* P.eof)
3954 ( Format.Ledger.Read.context () Format.Ledger.journal
3955 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3956 "" (" A:B:C $1 + 1$"::Text)])
3957 ~?=
3958 [ (Format.Ledger.posting ("A":|["B", "C"]))
3959 { Format.Ledger.posting_amounts = Data.Map.fromList
3960 [ ("$", Amount.nil
3961 { Amount.quantity = 2
3962 , Amount.style = Amount.Style.nil
3963 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3964 , Amount.Style.unit_spaced = Just False
3965 }
3966 , Amount.unit = "$"
3967 })
3968 ]
3969 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3970 }
3971 ]
3972 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
3973 (Data.List.map fst $
3974 Data.Either.rights $
3975 [P.runParser_with_Error
3976 (Format.Ledger.Read.posting <* P.eof)
3977 ( Format.Ledger.Read.context () Format.Ledger.journal
3978 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
3979 "" (" A:B:C $1 + 1$ + 1$"::Text)])
3980 ~?=
3981 [ (Format.Ledger.posting ("A":|["B", "C"]))
3982 { Format.Ledger.posting_amounts = Data.Map.fromList
3983 [ ("$", Amount.nil
3984 { Amount.quantity = 3
3985 , Amount.style = Amount.Style.nil
3986 { Amount.Style.unit_side = Just Amount.Style.Side_Left
3987 , Amount.Style.unit_spaced = Just False
3988 }
3989 , Amount.unit = "$"
3990 })
3991 ]
3992 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
3993 }
3994 ]
3995 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
3996 (Data.List.map fst $
3997 Data.Either.rights $
3998 [P.runParser_with_Error
3999 (Format.Ledger.Read.posting <* P.eof)
4000 ( Format.Ledger.Read.context () Format.Ledger.journal
4001 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4002 "" (" A:B:C ; some comment"::Text)])
4003 ~?=
4004 [ (Format.Ledger.posting ("A":|["B", "C"]))
4005 { Format.Ledger.posting_amounts = Data.Map.fromList []
4006 , Format.Ledger.posting_comments = [" some comment"]
4007 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4008 }
4009 ]
4010 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
4011 (Data.List.map fst $
4012 Data.Either.rights $
4013 [P.runParser_with_Error
4014 (Format.Ledger.Read.posting <* P.eof)
4015 ( Format.Ledger.Read.context () Format.Ledger.journal
4016 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4017 "" (" A:B:C ; some comment\n ; some other comment"::Text)])
4018 ~?=
4019 [ (Format.Ledger.posting ("A":|["B", "C"]))
4020 { Format.Ledger.posting_amounts = Data.Map.fromList []
4021 , Format.Ledger.posting_comments = [" some comment", " some other comment"]
4022 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4023 }
4024 ]
4025 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
4026 (Data.List.map fst $
4027 Data.Either.rights $
4028 [P.runParser_with_Error
4029 (Format.Ledger.Read.posting)
4030 ( Format.Ledger.Read.context () Format.Ledger.journal
4031 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4032 "" (" A:B:C $1 ; some comment"::Text)])
4033 ~?=
4034 [ (Format.Ledger.posting ("A":|["B", "C"]))
4035 { Format.Ledger.posting_amounts = Data.Map.fromList
4036 [ ("$", Amount.nil
4037 { Amount.quantity = 1
4038 , Amount.style = Amount.Style.nil
4039 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4040 , Amount.Style.unit_spaced = Just False
4041 }
4042 , Amount.unit = "$"
4043 })
4044 ]
4045 , Format.Ledger.posting_comments = [" some comment"]
4046 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4047 }
4048 ]
4049 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
4050 (Data.List.map fst $
4051 Data.Either.rights $
4052 [P.runParser_with_Error
4053 (Format.Ledger.Read.posting <* P.eof)
4054 ( Format.Ledger.Read.context () Format.Ledger.journal
4055 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4056 "" (" A:B:C ; N:V"::Text)])
4057 ~?=
4058 [ (Format.Ledger.posting ("A":|["B", "C"]))
4059 { Format.Ledger.posting_comments = [" N:V"]
4060 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4061 , Format.Ledger.posting_tags = Data.Map.fromList
4062 [ ("N", ["V"])
4063 ]
4064 }
4065 ]
4066 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
4067 (Data.List.map fst $
4068 Data.Either.rights $
4069 [P.runParser_with_Error
4070 (Format.Ledger.Read.posting <* P.eof)
4071 ( Format.Ledger.Read.context () Format.Ledger.journal
4072 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4073 "" (" A:B:C ; some comment N:V"::Text)])
4074 ~?=
4075 [ (Format.Ledger.posting ("A":|["B", "C"]))
4076 { Format.Ledger.posting_comments = [" some comment N:V"]
4077 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4078 , Format.Ledger.posting_tags = Data.Map.fromList
4079 [ ("N", ["V"])
4080 ]
4081 }
4082 ]
4083 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
4084 (Data.List.map fst $
4085 Data.Either.rights $
4086 [P.runParser_with_Error
4087 (Format.Ledger.Read.posting )
4088 ( Format.Ledger.Read.context () Format.Ledger.journal
4089 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4090 "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
4091 ~?=
4092 [ (Format.Ledger.posting ("A":|["B", "C"]))
4093 { Format.Ledger.posting_comments = [" some comment N:V v, N2:V2 v2"]
4094 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4095 , Format.Ledger.posting_tags = Data.Map.fromList
4096 [ ("N", ["V v"])
4097 , ("N2", ["V2 v2"])
4098 ]
4099 }
4100 ]
4101 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
4102 (Data.List.map fst $
4103 Data.Either.rights $
4104 [P.runParser_with_Error
4105 (Format.Ledger.Read.posting <* P.eof)
4106 ( Format.Ledger.Read.context () Format.Ledger.journal
4107 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4108 "" (" A:B:C ; N:V\n ; N:V2"::Text)])
4109 ~?=
4110 [ (Format.Ledger.posting ("A":|["B", "C"]))
4111 { Format.Ledger.posting_comments = [" N:V", " N:V2"]
4112 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4113 , Format.Ledger.posting_tags = Data.Map.fromList
4114 [ ("N", ["V", "V2"])
4115 ]
4116 }
4117 ]
4118 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
4119 (Data.List.map fst $
4120 Data.Either.rights $
4121 [P.runParser_with_Error
4122 (Format.Ledger.Read.posting <* P.eof)
4123 ( Format.Ledger.Read.context () Format.Ledger.journal
4124 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4125 "" (" A:B:C ; N:V\n ; N2:V"::Text)])
4126 ~?=
4127 [ (Format.Ledger.posting ("A":|["B", "C"]))
4128 { Format.Ledger.posting_comments = [" N:V", " N2:V"]
4129 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4130 , Format.Ledger.posting_tags = Data.Map.fromList
4131 [ ("N", ["V"])
4132 , ("N2", ["V"])
4133 ]
4134 }
4135 ]
4136 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
4137 (Data.List.map fst $
4138 Data.Either.rights $
4139 [P.runParser_with_Error
4140 (Format.Ledger.Read.posting <* P.eof)
4141 ( Format.Ledger.Read.context () Format.Ledger.journal
4142 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4143 "" (" A:B:C ; date:2001/01/01"::Text)])
4144 ~?=
4145 [ (Format.Ledger.posting ("A":|["B", "C"]))
4146 { Format.Ledger.posting_comments = [" date:2001/01/01"]
4147 , Format.Ledger.posting_dates =
4148 [ Time.zonedTimeToUTC $
4149 Time.ZonedTime
4150 (Time.LocalTime
4151 (Time.fromGregorian 2001 01 01)
4152 (Time.TimeOfDay 0 0 0))
4153 Time.utc
4154 ]
4155 , Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4156 , Format.Ledger.posting_tags = Data.Map.fromList
4157 [ ("date", ["2001/01/01"])
4158 ]
4159 }
4160 ]
4161 , " (A:B:C) = Right (A:B:C)" ~:
4162 (Data.Either.rights $
4163 [P.runParser_with_Error
4164 (Format.Ledger.Read.posting <* P.eof)
4165 ( Format.Ledger.Read.context () Format.Ledger.journal
4166 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4167 "" (" (A:B:C)"::Text)])
4168 ~?=
4169 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4170 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4171 }
4172 , Posting.Posting_Type_Virtual
4173 )
4174 ]
4175 , " [A:B:C] = Right [A:B:C]" ~:
4176 (Data.Either.rights $
4177 [P.runParser_with_Error
4178 (Format.Ledger.Read.posting <* P.eof)
4179 ( Format.Ledger.Read.context () Format.Ledger.journal
4180 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4181 "" (" [A:B:C]"::Text)])
4182 ~?=
4183 [ ( (Format.Ledger.posting ("A":|["B", "C"]))
4184 { Format.Ledger.posting_sourcepos = P.newPos "" 1 1
4185 }
4186 , Posting.Posting_Type_Virtual_Balanced
4187 )
4188 ]
4189 ]
4190 , "transaction" ~: TestList
4191 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
4192 (Data.Either.rights $
4193 [P.runParser_with_Error
4194 (Format.Ledger.Read.transaction <* P.eof)
4195 ( Format.Ledger.Read.context () Format.Ledger.journal
4196 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4197 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
4198 ~?=
4199 [ Format.Ledger.transaction
4200 { Format.Ledger.transaction_dates=
4201 ( Time.zonedTimeToUTC $
4202 Time.ZonedTime
4203 (Time.LocalTime
4204 (Time.fromGregorian 2000 01 01)
4205 (Time.TimeOfDay 0 0 0))
4206 (Time.utc)
4207 , [] )
4208 , Format.Ledger.transaction_description="some description"
4209 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4210 [ (Format.Ledger.posting ("A":|["B", "C"]))
4211 { Format.Ledger.posting_amounts = Data.Map.fromList
4212 [ ("$", Amount.nil
4213 { Amount.quantity = 1
4214 , Amount.style = Amount.Style.nil
4215 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4216 , Amount.Style.unit_spaced = Just False
4217 }
4218 , Amount.unit = "$"
4219 })
4220 ]
4221 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4222 }
4223 , (Format.Ledger.posting ("a":|["b", "c"]))
4224 { Format.Ledger.posting_amounts = Data.Map.fromList
4225 [ ("$", Amount.nil
4226 { Amount.quantity = -1
4227 , Amount.style = Amount.Style.nil
4228 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4229 , Amount.Style.unit_spaced = Just False
4230 }
4231 , Amount.unit = "$"
4232 })
4233 ]
4234 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4235 }
4236 ]
4237 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4238 }
4239 ]
4240 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
4241 (Data.Either.rights $
4242 [P.runParser_with_Error
4243 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
4244 ( Format.Ledger.Read.context () Format.Ledger.journal
4245 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4246 "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
4247 ~?=
4248 [ Format.Ledger.transaction
4249 { Format.Ledger.transaction_dates=
4250 ( Time.zonedTimeToUTC $
4251 Time.ZonedTime
4252 (Time.LocalTime
4253 (Time.fromGregorian 2000 01 01)
4254 (Time.TimeOfDay 0 0 0))
4255 (Time.utc)
4256 , [] )
4257 , Format.Ledger.transaction_description="some description"
4258 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4259 [ (Format.Ledger.posting ("A":|["B", "C"]))
4260 { Format.Ledger.posting_amounts = Data.Map.fromList
4261 [ ("$", Amount.nil
4262 { Amount.quantity = 1
4263 , Amount.style = Amount.Style.nil
4264 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4265 , Amount.Style.unit_spaced = Just False
4266 }
4267 , Amount.unit = "$"
4268 })
4269 ]
4270 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4271 }
4272 , (Format.Ledger.posting ("a":|["b", "c"]))
4273 { Format.Ledger.posting_amounts = Data.Map.fromList
4274 [ ("$", Amount.nil
4275 { Amount.quantity = -1
4276 , Amount.style = Amount.Style.nil
4277 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4278 , Amount.Style.unit_spaced = Just False
4279 }
4280 , Amount.unit = "$"
4281 })
4282 ]
4283 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4284 }
4285 ]
4286 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4287 }
4288 ]
4289 , "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" ~:
4290 (Data.Either.rights $
4291 [P.runParser_with_Error
4292 (Format.Ledger.Read.transaction <* P.eof)
4293 ( Format.Ledger.Read.context () Format.Ledger.journal
4294 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4295 "" ("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)])
4296 ~?=
4297 [ Format.Ledger.transaction
4298 { Format.Ledger.transaction_comments_after =
4299 [ " some comment"
4300 , " some other;comment"
4301 , " some Tag:"
4302 , " some last comment"
4303 ]
4304 , Format.Ledger.transaction_dates=
4305 ( Time.zonedTimeToUTC $
4306 Time.ZonedTime
4307 (Time.LocalTime
4308 (Time.fromGregorian 2000 01 01)
4309 (Time.TimeOfDay 0 0 0))
4310 (Time.utc)
4311 , [] )
4312 , Format.Ledger.transaction_description="some description"
4313 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4314 [ (Format.Ledger.posting ("A":|["B", "C"]))
4315 { Format.Ledger.posting_amounts = Data.Map.fromList
4316 [ ("$", Amount.nil
4317 { Amount.quantity = 1
4318 , Amount.style = Amount.Style.nil
4319 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4320 , Amount.Style.unit_spaced = Just False
4321 }
4322 , Amount.unit = "$"
4323 })
4324 ]
4325 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4326 }
4327 , (Format.Ledger.posting ("a":|["b", "c"]))
4328 { Format.Ledger.posting_amounts = Data.Map.fromList
4329 [ ("$", Amount.nil
4330 { Amount.quantity = -1
4331 , Amount.style = Amount.Style.nil
4332 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4333 , Amount.Style.unit_spaced = Just False
4334 }
4335 , Amount.unit = "$"
4336 })
4337 ]
4338 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4339 }
4340 ]
4341 , Format.Ledger.transaction_tags = Data.Map.fromList
4342 [ ("Tag", [""])
4343 ]
4344 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4345 }
4346 ]
4347 ]
4348 , "journal" ~: TestList
4349 [ "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
4350 jnl <- liftIO $
4351 P.runParserT_with_Error
4352 (Format.Ledger.Read.journal "" {-<* P.eof-})
4353 ( Format.Ledger.Read.context () Format.Ledger.journal
4354 ::Format.Ledger.Read.Context () [] Format.Ledger.Transaction)
4355 "" ("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)
4356 (Data.List.map
4357 (\j -> j{Format.Ledger.journal_last_read_time=Date.nil}) $
4358 Data.Either.rights [jnl])
4359 @?=
4360 [ Format.Ledger.journal
4361 { Format.Ledger.journal_transactions =
4362 [ Format.Ledger.transaction
4363 { Format.Ledger.transaction_dates=
4364 ( Time.zonedTimeToUTC $
4365 Time.ZonedTime
4366 (Time.LocalTime
4367 (Time.fromGregorian 2000 01 02)
4368 (Time.TimeOfDay 0 0 0))
4369 (Time.utc)
4370 , [] )
4371 , Format.Ledger.transaction_description="2° description"
4372 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4373 [ (Format.Ledger.posting ("A":|["B", "C"]))
4374 { Format.Ledger.posting_amounts = Data.Map.fromList
4375 [ ("$", Amount.nil
4376 { Amount.quantity = 1
4377 , Amount.style = Amount.Style.nil
4378 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4379 , Amount.Style.unit_spaced = Just False
4380 }
4381 , Amount.unit = "$"
4382 })
4383 ]
4384 , Format.Ledger.posting_sourcepos = P.newPos "" 5 1
4385 }
4386 , (Format.Ledger.posting ("x":|["y", "z"]))
4387 { Format.Ledger.posting_amounts = Data.Map.fromList
4388 [ ("$", Amount.nil
4389 { Amount.quantity = -1
4390 , Amount.style = Amount.Style.nil
4391 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4392 , Amount.Style.unit_spaced = Just False
4393 }
4394 , Amount.unit = "$"
4395 })
4396 ]
4397 , Format.Ledger.posting_sourcepos = P.newPos "" 6 1
4398 }
4399 ]
4400 , Format.Ledger.transaction_sourcepos = P.newPos "" 4 1
4401 }
4402 , Format.Ledger.transaction
4403 { Format.Ledger.transaction_dates=
4404 ( Time.zonedTimeToUTC $
4405 Time.ZonedTime
4406 (Time.LocalTime
4407 (Time.fromGregorian 2000 01 01)
4408 (Time.TimeOfDay 0 0 0))
4409 (Time.utc)
4410 , [] )
4411 , Format.Ledger.transaction_description="1° description"
4412 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4413 [ (Format.Ledger.posting ("A":|["B", "C"]))
4414 { Format.Ledger.posting_amounts = Data.Map.fromList
4415 [ ("$", Amount.nil
4416 { Amount.quantity = 1
4417 , Amount.style = Amount.Style.nil
4418 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4419 , Amount.Style.unit_spaced = Just False
4420 }
4421 , Amount.unit = "$"
4422 })
4423 ]
4424 , Format.Ledger.posting_sourcepos = P.newPos "" 2 1
4425 }
4426 , (Format.Ledger.posting ("a":|["b", "c"]))
4427 { Format.Ledger.posting_amounts = Data.Map.fromList
4428 [ ("$", Amount.nil
4429 { Amount.quantity = -1
4430 , Amount.style = Amount.Style.nil
4431 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4432 , Amount.Style.unit_spaced = Just False
4433 }
4434 , Amount.unit = "$"
4435 })
4436 ]
4437 , Format.Ledger.posting_sourcepos = P.newPos "" 3 1
4438 }
4439 ]
4440 , Format.Ledger.transaction_sourcepos = P.newPos "" 1 1
4441 }
4442 ]
4443 }
4444 ]
4445 ]
4446 ]
4447 , "Write" ~: TestList
4448 [ "account" ~: TestList
4449 [ "A" ~:
4450 ((Format.Ledger.Write.show
4451 Format.Ledger.Write.Style
4452 { Format.Ledger.Write.style_color=False
4453 , Format.Ledger.Write.style_align=True
4454 } $
4455 Format.Ledger.Write.account Posting.Posting_Type_Regular $
4456 "A":|[])
4457 ~?=
4458 "A")
4459 , "A:B:C" ~:
4460 ((Format.Ledger.Write.show
4461 Format.Ledger.Write.Style
4462 { Format.Ledger.Write.style_color=False
4463 , Format.Ledger.Write.style_align=True
4464 } $
4465 Format.Ledger.Write.account Posting.Posting_Type_Regular $
4466 "A":|["B", "C"])
4467 ~?=
4468 "A:B:C")
4469 , "(A:B:C)" ~:
4470 ((Format.Ledger.Write.show
4471 Format.Ledger.Write.Style
4472 { Format.Ledger.Write.style_color=False
4473 , Format.Ledger.Write.style_align=True
4474 } $
4475 Format.Ledger.Write.account Posting.Posting_Type_Virtual $
4476 "A":|["B", "C"])
4477 ~?=
4478 "(A:B:C)")
4479 , "[A:B:C]" ~:
4480 ((Format.Ledger.Write.show
4481 Format.Ledger.Write.Style
4482 { Format.Ledger.Write.style_color=False
4483 , Format.Ledger.Write.style_align=True
4484 } $
4485 Format.Ledger.Write.account Posting.Posting_Type_Virtual_Balanced $
4486 "A":|["B", "C"])
4487 ~?=
4488 "[A:B:C]")
4489 ]
4490 , "transaction" ~: TestList
4491 [ "nil" ~:
4492 ((Format.Ledger.Write.show
4493 Format.Ledger.Write.Style
4494 { Format.Ledger.Write.style_color=False
4495 , Format.Ledger.Write.style_align=True
4496 } $
4497 Format.Ledger.Write.transaction
4498 Format.Ledger.transaction)
4499 ~?=
4500 "1970/01/01\n\n")
4501 , "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" ~:
4502 ((Format.Ledger.Write.show
4503 Format.Ledger.Write.Style
4504 { Format.Ledger.Write.style_color=False
4505 , Format.Ledger.Write.style_align=True
4506 } $
4507 Format.Ledger.Write.transaction $
4508 Format.Ledger.transaction
4509 { Format.Ledger.transaction_dates=
4510 ( Time.zonedTimeToUTC $
4511 Time.ZonedTime
4512 (Time.LocalTime
4513 (Time.fromGregorian 2000 01 01)
4514 (Time.TimeOfDay 0 0 0))
4515 (Time.utc)
4516 , [] )
4517 , Format.Ledger.transaction_description="some description"
4518 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4519 [ (Format.Ledger.posting ("A":|["B", "C"]))
4520 { Format.Ledger.posting_amounts = Data.Map.fromList
4521 [ ("$", Amount.nil
4522 { Amount.quantity = 1
4523 , Amount.style = Amount.Style.nil
4524 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4525 , Amount.Style.unit_spaced = Just False
4526 }
4527 , Amount.unit = "$"
4528 })
4529 ]
4530 }
4531 , (Format.Ledger.posting ("a":|["b", "c"]))
4532 { Format.Ledger.posting_comments = ["first comment","second comment","third comment"]
4533 }
4534 ]
4535 })
4536 ~?=
4537 "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")
4538 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
4539 ((Format.Ledger.Write.show
4540 Format.Ledger.Write.Style
4541 { Format.Ledger.Write.style_color=False
4542 , Format.Ledger.Write.style_align=True
4543 } $
4544 Format.Ledger.Write.transaction $
4545 Format.Ledger.transaction
4546 { Format.Ledger.transaction_dates=
4547 ( Time.zonedTimeToUTC $
4548 Time.ZonedTime
4549 (Time.LocalTime
4550 (Time.fromGregorian 2000 01 01)
4551 (Time.TimeOfDay 0 0 0))
4552 (Time.utc)
4553 , [] )
4554 , Format.Ledger.transaction_description="some description"
4555 , Format.Ledger.transaction_postings = Format.Ledger.posting_by_Account
4556 [ (Format.Ledger.posting ("A":|["B", "C"]))
4557 { Format.Ledger.posting_amounts = Data.Map.fromList
4558 [ ("$", Amount.nil
4559 { Amount.quantity = 1
4560 , Amount.style = Amount.Style.nil
4561 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4562 , Amount.Style.unit_spaced = Just False
4563 }
4564 , Amount.unit = "$"
4565 })
4566 ]
4567 }
4568 , (Format.Ledger.posting ("AA":|["BB", "CC"]))
4569 { Format.Ledger.posting_amounts = Data.Map.fromList
4570 [ ("$", Amount.nil
4571 { Amount.quantity = 123
4572 , Amount.style = Amount.Style.nil
4573 { Amount.Style.unit_side = Just Amount.Style.Side_Left
4574 , Amount.Style.unit_spaced = Just False
4575 }
4576 , Amount.unit = "$"
4577 })
4578 ]
4579 }
4580 ]
4581 })
4582 ~?=
4583 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123\n")
4584 ]
4585 ]
4586 ]
4587 ]
4588 ]