]> Git — Sourcephile - comptalang.git/blob - lib/Test/Main.hs
Déplace hcompta-calculus vers lol-calculus et lol-typing
[comptalang.git] / lib / Test / Main.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TupleSections #-}
5 {-# LANGUAGE TypeFamilies #-}
6
7 import Prelude
8 import Test.HUnit hiding ((~?), test)
9 import Test.Framework.Providers.HUnit (hUnitTestToTests)
10 import Test.Framework.Runners.Console (defaultMain)
11
12 -- import Control.Applicative (Const(..))
13 import Control.Arrow ((***))
14 import Data.Data ()
15 -- import qualified Data.Either
16 import Data.Function (on)
17 -- import Data.Functor.Compose (Compose(..))
18 import qualified Data.List as List
19 import Data.List.NonEmpty (NonEmpty(..))
20 import qualified Data.Map.Strict as Map
21 import Data.Maybe (fromJust)
22 import qualified Data.Strict.Maybe as Strict
23 import Data.Text (Text)
24 -- import qualified Text.Parsec as P hiding (char, space, spaces, string)
25
26 import qualified Hcompta.Account as Account
27 import qualified Hcompta.Balance as Balance
28 -- import qualified Hcompta.Filter as Filter
29 -- import qualified Hcompta.Filter.Read as Filter.Read
30 import qualified Hcompta.Lib.Foldable as Lib.Foldable
31 import qualified Hcompta.Lib.Interval as Lib.Interval
32 import qualified Hcompta.Lib.Interval.Sieve as Lib.Interval.Sieve
33 -- import qualified Hcompta.Lib.Parsec as P
34 import qualified Hcompta.Lib.TreeMap as TreeMap
35 import qualified Hcompta.Polarize as Polarize
36 import qualified Hcompta.Quantity as Quantity
37 -- import qualified Hcompta.Tag as Tag
38
39 -- (~?) :: String -> Bool -> Test
40 -- (~?) s b = s ~: (b ~?= True)
41
42 amounts :: (Quantity.Addable q, Ord u) => [(u, q)] -> Map.Map u q
43 amounts = Map.fromListWith Quantity.quantity_add
44 amount_usd = (("$"::Text),)
45 amount_eur = (("€"::Text),)
46 amount_gbp = (("£"::Text),)
47
48 main :: IO ()
49 main = defaultMain $ hUnitTestToTests test
50
51 type instance
52
53
54
55 test :: Test
56 test = TestList
57 [
58 ]
59 {-
60 [ "Lib" ~: TestList
61 [ "TreeMap" ~: TestList
62 [ "insert" ~: TestList
63 [ "[] 0" ~:
64 (TreeMap.insert const ((0::Int):|[]) () TreeMap.empty)
65 ~?=
66 (TreeMap.TreeMap $
67 Map.fromList
68 [ ((0::Int), TreeMap.leaf ())
69 ])
70 , "[] 0/1" ~:
71 (TreeMap.insert const ((0::Int):|1:[]) () TreeMap.empty)
72 ~?=
73 (TreeMap.TreeMap $
74 Map.fromList
75 [ ((0::Int), TreeMap.Node
76 { TreeMap.node_value = Strict.Nothing
77 , TreeMap.node_size = 1
78 , TreeMap.node_descendants =
79 TreeMap.singleton ((1::Int):|[]) ()
80 })
81 ])
82 ]
83 , "union" ~: TestList
84 [
85 ]
86 , "map_by_depth_first" ~: TestList
87 [ "[0, 0/1, 0/1/2, 1, 1/2/3]" ~:
88 (TreeMap.map_by_depth_first
89 (\descendants value ->
90 Map.foldl'
91 (\acc v -> (++) acc $
92 Strict.fromMaybe undefined $
93 TreeMap.node_value v
94 )
95 (Strict.fromMaybe [] value)
96 (TreeMap.nodes descendants)
97 ) $
98 TreeMap.from_List const
99 [ (((0::Integer):|[]), [0])
100 , ((0:|1:[]), [0,1])
101 , ((0:|1:2:[]), [0,1,2])
102 , ((1:|[]), [1])
103 , ((1:|2:3:[]), [1,2,3])
104 ]
105 )
106 ~?=
107 (TreeMap.from_List const
108 [ ((0:|[]), [0,0,1,0,1,2])
109 , ((0:|1:[]), [0,1,0,1,2])
110 , ((0:|1:2:[]), [0,1,2])
111 , ((1:|[]), [1,1,2,3])
112 , ((1:|2:[]), [1,2,3])
113 , ((1:|2:3:[]), [1,2,3])
114 ])
115 , "[0/0]" ~:
116 (TreeMap.map_by_depth_first
117 (\descendants value ->
118 Map.foldl'
119 (\acc v -> (++) acc $
120 Strict.fromMaybe undefined $
121 TreeMap.node_value v
122 )
123 (Strict.fromMaybe [] value)
124 (TreeMap.nodes descendants)
125 ) $
126 TreeMap.from_List const
127 [ (((0::Integer):|0:[]), [0,0])
128 ]
129 )
130 ~?=
131 (TreeMap.from_List const
132 [ ((0:|[]), [0,0])
133 , ((0:|0:[]), [0,0])
134 ])
135 ]
136 , "flatten" ~: TestList
137 [ "[0, 0/1, 0/1/2]" ~:
138 (TreeMap.flatten id $
139 TreeMap.from_List const
140 [ (((0::Integer):|[]), ())
141 , ((0:|1:[]), ())
142 , ((0:|1:2:[]), ())
143 ]
144 )
145 ~?=
146 (Map.fromList
147 [ ((0:|[]), ())
148 , ((0:|1:[]), ())
149 , ((0:|1:2:[]), ())
150 ])
151 , "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" ~:
152 (TreeMap.flatten id $
153 TreeMap.from_List const
154 [ ((1:|[]), ())
155 , ((1:|2:[]), ())
156 , ((1:|22:[]), ())
157 , ((1:|2:3:[]), ())
158 , ((1:|2:33:[]), ())
159 , ((11:|[]), ())
160 , ((11:|2:[]), ())
161 , ((11:|2:3:[]), ())
162 , ((11:|2:33:[]), ())
163 ]
164 )
165 ~?=
166 (Map.fromList
167 [ (((1::Integer):|[]), ())
168 , ((1:|2:[]), ())
169 , ((1:|22:[]), ())
170 , ((1:|2:3:[]), ())
171 , ((1:|2:33:[]), ())
172 , ((11:|[]), ())
173 , ((11:|2:[]), ())
174 , ((11:|2:3:[]), ())
175 , ((11:|2:33:[]), ())
176 ])
177 ]
178 , "find_along" ~: TestList
179 [ "0/1/2/3 [0, 0/1, 0/1/2, 0/1/2/3]" ~:
180 (TreeMap.find_along
181 (0:|[1,2,3]) $
182 TreeMap.from_List const
183 [ (((0::Integer):|[]), [0])
184 , ((0:|1:[]), [0,1])
185 , ((0:|1:2:[]), [0,1,2])
186 , ((0:|1:2:3:[]), [0,1,2,3])
187 ]
188 )
189 ~?=
190 [ [0]
191 , [0,1]
192 , [0,1,2]
193 , [0,1,2,3]
194 ]
195 , "0/1/2/3 [0, 0/1]" ~:
196 (TreeMap.find_along
197 (0:|[1,2,3]) $
198 TreeMap.from_List const
199 [ (((0::Integer):|[]), [0])
200 , ((0:|1:[]), [0,1])
201 ]
202 )
203 ~?=
204 [ [0]
205 , [0,1]
206 ]
207 ]
208 ]
209 , "Foldable" ~: TestList
210 [ "accumLeftsAndFoldrRights" ~: TestList
211 [ "Left" ~:
212 (Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
213 [Left [0]])
214 ~?=
215 (([(0::Integer)], [(""::String)]))
216 , "repeat Left" ~:
217 ((take 1 *** take 0) $
218 Lib.Foldable.accumLeftsAndFoldrRights (++) [""] $
219 ( repeat (Left [0]) ))
220 ~?=
221 ([(0::Integer)], ([]::[String]))
222 , "Right:Left:Right:Left" ~:
223 (Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
224 ( Right ["2"]:Left [1]:Right ["1"]:Left [0]:[] ))
225 ~?=
226 (([1, 0]::[Integer]), (["2", "1", "0"]::[String]))
227 , "Right:Left:Right:repeat Left" ~:
228 ((take 1 *** take 2) $
229 Lib.Foldable.accumLeftsAndFoldrRights (++) ["0"] $
230 ( Right ["2"]:Left [1]:Right ["1"]:repeat (Left [0]) ))
231 ~?=
232 (([1]::[Integer]), (["2", "1"]::[String]))
233 ]
234 ]
235 , "Interval" ~: TestList
236 [ "position" ~: TestList $
237 concatMap
238 (\(mi, mj, p) ->
239 let i = fromJust mi in
240 let j = fromJust mj in
241 let (le, ge) =
242 case p of
243 Lib.Interval.Equal -> (EQ, EQ)
244 _ -> (LT, GT) in
245 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.position i j ~?= (p, le)
246 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.position j i ~?= (p, ge)
247 ]
248 )
249 [ ( (Lib.Interval.<..<) 0 (4::Integer)
250 , (Lib.Interval.<..<) 5 9
251 , Lib.Interval.Away )
252 , ( (Lib.Interval.<..<) 0 4
253 , (Lib.Interval.<=..<) 4 9
254 , Lib.Interval.Adjacent )
255 , ( (Lib.Interval.<..<) 0 5
256 , (Lib.Interval.<..<) 4 9
257 , Lib.Interval.Overlap )
258 , ( (Lib.Interval.<..<) 0 5
259 , (Lib.Interval.<..<) 0 9
260 , Lib.Interval.Prefix )
261 , ( (Lib.Interval.<..<) 0 9
262 , (Lib.Interval.<..<) 1 8
263 , Lib.Interval.Include )
264 , ( (Lib.Interval.<..<) 0 9
265 , (Lib.Interval.<..<) 5 9
266 , Lib.Interval.Suffixed )
267 , ( (Lib.Interval.<..<) 0 9
268 , (Lib.Interval.<..<) 0 9
269 , Lib.Interval.Equal )
270 , ( (Lib.Interval.<..<) 0 9
271 , (Lib.Interval.<..<=) 0 9
272 , Lib.Interval.Prefix )
273 , ( (Lib.Interval.<=..<) 0 9
274 , (Lib.Interval.<..<) 0 9
275 , Lib.Interval.Suffixed )
276 , ( (Lib.Interval.<=..<=) 0 9
277 , (Lib.Interval.<..<) 0 9
278 , Lib.Interval.Include )
279 ]
280 , "intersection" ~: TestList $
281 concatMap
282 (\(mi, mj, e) ->
283 let i = fromJust mi in
284 let j = fromJust mj in
285 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.intersection i j ~?= e
286 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.intersection j i ~?= e
287 ]
288 )
289 [ ( (Lib.Interval.<..<) 0 (4::Integer)
290 , (Lib.Interval.<..<) 5 9
291 , Nothing )
292 , ( (Lib.Interval.<..<=) 0 5
293 , (Lib.Interval.<=..<) 5 9
294 , (Lib.Interval.<=..<=) 5 5 )
295 , ( (Lib.Interval.<..<) 0 6
296 , (Lib.Interval.<..<) 4 9
297 , (Lib.Interval.<..<) 4 6 )
298 , ( (Lib.Interval.<..<=) 0 6
299 , (Lib.Interval.<=..<) 4 9
300 , (Lib.Interval.<=..<=) 4 6 )
301 , ( (Lib.Interval.<..<) 0 6
302 , (Lib.Interval.<=..<) 4 9
303 , (Lib.Interval.<=..<) 4 6 )
304 , ( (Lib.Interval.<..<=) 0 6
305 , (Lib.Interval.<..<) 4 9
306 , (Lib.Interval.<..<=) 4 6 )
307 , ( (Lib.Interval.<..<) 0 9
308 , (Lib.Interval.<..<) 0 9
309 , (Lib.Interval.<..<) 0 9 )
310 , ( (Lib.Interval.<=..<) 0 9
311 , (Lib.Interval.<..<=) 0 9
312 , (Lib.Interval.<..<) 0 9 )
313 , ( (Lib.Interval.<..<=) 0 9
314 , (Lib.Interval.<=..<) 0 9
315 , (Lib.Interval.<..<) 0 9 )
316 , ( (Lib.Interval.<=..<=) 0 9
317 , (Lib.Interval.<=..<=) 0 9
318 , (Lib.Interval.<=..<=) 0 9 )
319 ]
320 , "union" ~: TestList $
321 concatMap
322 (\(mi, mj, e) ->
323 let i = fromJust mi in
324 let j = fromJust mj in
325 [ ((show . Lib.Interval.Pretty) i ++ " " ++ (show . Lib.Interval.Pretty) j) ~: Lib.Interval.union i j ~?= e
326 , ((show . Lib.Interval.Pretty) j ++ " " ++ (show . Lib.Interval.Pretty) i) ~: Lib.Interval.union j i ~?= e
327 ]
328 )
329 [ ( (Lib.Interval.<..<) 0 (4::Integer)
330 , (Lib.Interval.<..<) 5 9
331 , Nothing )
332 , ( (Lib.Interval.<..<=) 0 5
333 , (Lib.Interval.<..<) 5 9
334 , (Lib.Interval.<..<) 0 9 )
335 , ( (Lib.Interval.<..<) 0 5
336 , (Lib.Interval.<=..<) 5 9
337 , (Lib.Interval.<..<) 0 9 )
338 , ( (Lib.Interval.<..<=) 0 5
339 , (Lib.Interval.<=..<) 5 9
340 , (Lib.Interval.<..<) 0 9 )
341 , ( (Lib.Interval.<..<) 0 6
342 , (Lib.Interval.<..<) 4 9
343 , (Lib.Interval.<..<) 0 9 )
344 , ( (Lib.Interval.<..<) 0 9
345 , (Lib.Interval.<..<) 0 9
346 , (Lib.Interval.<..<) 0 9 )
347 , ( (Lib.Interval.<=..<) 0 9
348 , (Lib.Interval.<..<=) 0 9
349 , (Lib.Interval.<=..<=) 0 9 )
350 , ( (Lib.Interval.<..<=) 0 9
351 , (Lib.Interval.<=..<) 0 9
352 , (Lib.Interval.<=..<=) 0 9 )
353 , ( (Lib.Interval.<=..<=) 0 9
354 , (Lib.Interval.<=..<=) 0 9
355 , (Lib.Interval.<=..<=) 0 9 )
356 ]
357 , "Sieve" ~: TestList $
358 [ "union" ~: TestList $
359 List.concatMap
360 (\(mis, me) ->
361 let is = map (fromJust) mis in
362 let e = map (fromJust) me in
363 let sil = foldl
364 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
365 Lib.Interval.Sieve.empty is in
366 let sir = foldr
367 (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton)
368 Lib.Interval.Sieve.empty is in
369 [ (List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ~:
370 Lib.Interval.Sieve.intervals sil ~?= e
371 , (List.intercalate " " $ map (show . Lib.Interval.Pretty) $ reverse is) ~:
372 Lib.Interval.Sieve.intervals sir ~?= e
373 ]
374 )
375 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer)
376 , (Lib.Interval.<=..<=) 5 9
377 ]
378 , [ (Lib.Interval.<=..<=) 0 9 ]
379 )
380 , ( [ (Lib.Interval.<=..<=) 0 5
381 , (Lib.Interval.<=..<=) 0 9
382 ]
383 , [ (Lib.Interval.<=..<=) 0 9 ]
384 )
385 , ( [ (Lib.Interval.<=..<=) 0 4
386 , (Lib.Interval.<=..<=) 5 9
387 , (Lib.Interval.<=..<=) 3 6
388 ]
389 , [ (Lib.Interval.<=..<=) 0 9 ]
390 )
391 , ( [ (Lib.Interval.<=..<=) 1 4
392 , (Lib.Interval.<=..<=) 5 8
393 ]
394 , [ (Lib.Interval.<=..<=) 1 4
395 , (Lib.Interval.<=..<=) 5 8
396 ]
397 )
398 , ( [ (Lib.Interval.<=..<=) 1 8
399 , (Lib.Interval.<=..<=) 0 9
400 ]
401 , [ (Lib.Interval.<=..<=) 0 9 ]
402 )
403 , ( [ (Lib.Interval.<=..<=) 1 4
404 , (Lib.Interval.<=..<=) 5 8
405 , (Lib.Interval.<=..<=) 0 9
406 ]
407 , [ (Lib.Interval.<=..<=) 0 9 ]
408 )
409 ]
410 ++ List.concatMap
411 (\(mis, mjs, me) ->
412 let is = map fromJust mis in
413 let js = map fromJust mjs in
414 let e = map fromJust me in
415 let iu = foldl
416 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
417 Lib.Interval.Sieve.empty is in
418 let ju = foldl
419 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
420 Lib.Interval.Sieve.empty js in
421 [ ((List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " u " ++
422 (List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
423 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union iu ju) ~?= e
424 , ((List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " u " ++
425 (List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
426 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.union ju iu) ~?= e
427 ]
428 )
429 [ ( [ (Lib.Interval.<=..<=) 0 (1::Integer)
430 , (Lib.Interval.<=..<=) 2 4
431 ]
432 , [ (Lib.Interval.<=..<=) 0 3
433 ]
434 , [ (Lib.Interval.<=..<=) 0 4
435 ]
436 )
437 , ( [ (Lib.Interval.<=..<=) 0 1
438 , (Lib.Interval.<=..<=) 2 3
439 , (Lib.Interval.<=..<=) 4 5
440 , (Lib.Interval.<=..<=) 6 7
441 ]
442 , [ (Lib.Interval.<=..<=) 1 2
443 , (Lib.Interval.<=..<=) 3 4
444 , (Lib.Interval.<=..<=) 5 6
445 ]
446 , [ (Lib.Interval.<=..<=) 0 7
447 ]
448 )
449 , ( [ (Lib.Interval.<=..<=) 0 1
450 , (Lib.Interval.<=..<=) 2 3
451 ]
452 , [ (Lib.Interval.<=..<=) 4 5
453 ]
454 , [ (Lib.Interval.<=..<=) 0 1
455 , (Lib.Interval.<=..<=) 2 3
456 , (Lib.Interval.<=..<=) 4 5
457 ]
458 )
459 , ( [ (Lib.Interval.<=..<=) 0 1
460 , (Lib.Interval.<=..<=) 4 5
461 ]
462 , [ (Lib.Interval.<=..<=) 2 3
463 ]
464 , [ (Lib.Interval.<=..<=) 0 1
465 , (Lib.Interval.<=..<=) 2 3
466 , (Lib.Interval.<=..<=) 4 5
467 ]
468 )
469 ]
470 , "intersection" ~: TestList $
471 List.concatMap
472 (\(mis, mjs, me) ->
473 let is = map (fromJust) mis in
474 let js = map (fromJust) mjs in
475 let e = map (fromJust) me in
476 let iu = foldl
477 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
478 Lib.Interval.Sieve.empty is in
479 let ju = foldl
480 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
481 Lib.Interval.Sieve.empty js in
482 [ ((List.intercalate " " $ map (show . Lib.Interval.Pretty) is) ++ " n " ++
483 (List.intercalate " " $ map (show . Lib.Interval.Pretty) js)) ~:
484 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection iu ju) ~?= e
485 , ((List.intercalate " " $ map (show . Lib.Interval.Pretty) $ js) ++ " n " ++
486 (List.intercalate " " $ map (show . Lib.Interval.Pretty) $ is)) ~:
487 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.intersection ju iu) ~?= e
488 ]
489 )
490 [ ( [ (Lib.Interval.<=..<) 0 (5::Integer) ]
491 , [ (Lib.Interval.<=..<=) 5 9 ]
492 , [ ]
493 )
494 , ( [ (Lib.Interval.<=..<=) 0 5 ]
495 , [ (Lib.Interval.<=..<=) 5 9 ]
496 , [ (Lib.Interval.<=..<=) 5 5 ]
497 )
498 , ( [ (Lib.Interval.<=..<=) 0 5 ]
499 , [ (Lib.Interval.<=..<=) 0 9 ]
500 , [ (Lib.Interval.<=..<=) 0 5 ]
501 )
502 , ( [ (Lib.Interval.<=..<=) 0 4
503 , (Lib.Interval.<=..<=) 5 9
504 ]
505 , [ (Lib.Interval.<=..<=) 3 6 ]
506 , [ (Lib.Interval.<=..<=) 3 4
507 , (Lib.Interval.<=..<=) 5 6
508 ]
509 )
510 , ( [ (Lib.Interval.<=..<=) 1 4
511 , (Lib.Interval.<=..<=) 6 8
512 ]
513 , [ (Lib.Interval.<=..<=) 2 3
514 , (Lib.Interval.<=..<=) 5 7
515 ]
516 , [ (Lib.Interval.<=..<=) 2 3
517 , (Lib.Interval.<=..<=) 6 7
518 ]
519 )
520 ]
521 , "complement" ~: TestList $
522 List.concatMap
523 (\(mis, me) ->
524 let is = map fromJust mis in
525 let e = map fromJust me in
526 let iu = foldl
527 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
528 Lib.Interval.Sieve.empty is in
529 [ show (Lib.Interval.Pretty $
530 Lib.Interval.Sieve.fmap_interval
531 (Lib.Interval.fmap_unsafe $ Lib.Interval.Pretty) iu) ~:
532 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement iu) ~?= e
533 ]
534 )
535 [ ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 (5::Integer)
536 , ((Lib.Interval.<=..<=) `on` Lib.Interval.Limited) 5 9
537 ]
538 , [ Just $ (Lib.Interval...<) 0
539 , Just $ (Lib.Interval.<..) 9
540 ]
541 )
542 , ( [ Just $ Lib.Interval.unlimited ]
543 , [ ]
544 )
545 , ( [ ]
546 , [ Just $ Lib.Interval.unlimited ]
547 )
548 , ( [ Just $ (Lib.Interval...<) 0
549 , Just $ (Lib.Interval.<..) 0
550 ]
551 , [ Just $ Lib.Interval.point $ Lib.Interval.Limited 0
552 ]
553 )
554 , ( [ ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 0 1
555 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 2 3
556 , ((Lib.Interval.<..<=) `on` Lib.Interval.Limited) 3 4
557 ]
558 , [ Just $ (Lib.Interval...<) 0
559 , ((Lib.Interval.<=..<) `on` Lib.Interval.Limited) 1 2
560 , Just $ Lib.Interval.point $ Lib.Interval.Limited 3
561 , Just $ (Lib.Interval.<..) 4
562 ]
563 )
564 ]
565 , "complement_with" ~: TestList $
566 List.concatMap
567 (\(mib, mis, me) ->
568 let ib = fromJust mib in
569 let is = map fromJust mis in
570 let e = map fromJust me in
571 let iu = foldl
572 (flip (Lib.Interval.Sieve.union . Lib.Interval.Sieve.singleton))
573 Lib.Interval.Sieve.empty is in
574 [ show (Lib.Interval.Pretty iu) ~:
575 Lib.Interval.Sieve.intervals (Lib.Interval.Sieve.complement_with ib iu) ~?= e
576 ]
577 )
578 [ ( (Lib.Interval.<=..<=) (-10) (10::Integer)
579 , [ (Lib.Interval.<=..<) 0 5
580 , (Lib.Interval.<=..<=) 5 9
581 ]
582 , [ (Lib.Interval.<=..<) (-10) 0
583 , (Lib.Interval.<..<=) 9 10
584 ]
585 )
586 , ( (Lib.Interval.<=..<=) (-10) 10
587 , [ (Lib.Interval.<=..<=) (-10) 10 ]
588 , [ ]
589 )
590 , ( (Lib.Interval.<=..<=) (-10) 10
591 , [ ]
592 , [ (Lib.Interval.<=..<=) (-10) 10 ]
593 )
594 , ( (Lib.Interval.<=..<=) (-10) 10
595 , [ (Lib.Interval.<=..<) (-10) 0
596 , (Lib.Interval.<..<=) 0 10
597 ]
598 , [ Just $ Lib.Interval.point 0
599 ]
600 )
601 , ( (Lib.Interval.<=..<=) (-10) 10
602 , [ Just $ Lib.Interval.point 0
603 ]
604 , [ (Lib.Interval.<=..<) (-10) 0
605 , (Lib.Interval.<..<=) 0 10
606 ]
607 )
608 , ( (Lib.Interval.<=..<=) 0 10
609 , [ (Lib.Interval.<..<=) 0 10
610 ]
611 , [ Just $ Lib.Interval.point 0
612 ]
613 )
614 , ( (Lib.Interval.<=..<=) 0 10
615 , [ (Lib.Interval.<=..<) 0 10
616 ]
617 , [ Just $ Lib.Interval.point 10
618 ]
619 )
620 , ( Just $ Lib.Interval.point 0
621 , [
622 ]
623 , [ Just $ Lib.Interval.point 0
624 ]
625 )
626 , ( Just $ Lib.Interval.point 0
627 , [ Just $ Lib.Interval.point 0
628 ]
629 , [
630 ]
631 )
632 ]
633 ]
634 ]
635 ]
636 , "Account" ~: TestList
637 [ "foldr" ~: TestList
638 [ "[A]" ~:
639 (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
640 , "[A, B]" ~:
641 (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
642 , "[A, B, C]" ~:
643 (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
644 ]
645 , "ascending" ~: TestList
646 [ "[A]" ~:
647 Account.ascending ("A":|[]) ~?= Nothing
648 , "[A, B]" ~:
649 Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
650 , "[A, B, C]" ~:
651 Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
652 ]
653 ]
654 , "Filter" ~: TestList
655 [ "test" ~: TestList
656 [ "Filter_Path" ~: TestList
657 [ "A A" ~?
658 Filter.test
659 (Filter.Filter_Path Filter.Eq
660 [ Filter.Filter_Path_Section_Text
661 (Filter.Filter_Text_Exact "A")
662 ])
663 ((("A"::Text):|[]))
664 , "* A" ~?
665 Filter.test
666 (Filter.Filter_Path Filter.Eq
667 [ Filter.Filter_Path_Section_Any
668 ])
669 ((("A"::Text):|[]))
670 , ": A" ~?
671 Filter.test
672 (Filter.Filter_Path Filter.Eq
673 [ Filter.Filter_Path_Section_Many
674 ])
675 ((("A"::Text):|[]))
676 , ":A A" ~?
677 Filter.test
678 (Filter.Filter_Path Filter.Eq
679 [ Filter.Filter_Path_Section_Many
680 , Filter.Filter_Path_Section_Text
681 (Filter.Filter_Text_Exact "A")
682 ])
683 ((("A"::Text):|[]))
684 , "A: A" ~?
685 Filter.test
686 (Filter.Filter_Path Filter.Eq
687 [ Filter.Filter_Path_Section_Text
688 (Filter.Filter_Text_Exact "A")
689 , Filter.Filter_Path_Section_Many
690 ])
691 ((("A"::Text):|[]))
692 , "A: A:B" ~?
693 Filter.test
694 (Filter.Filter_Path Filter.Eq
695 [ Filter.Filter_Path_Section_Text
696 (Filter.Filter_Text_Exact "A")
697 , Filter.Filter_Path_Section_Many
698 ])
699 ((("A"::Text):|"B":[]))
700 , "A:B A:B" ~?
701 Filter.test
702 (Filter.Filter_Path Filter.Eq
703 [ Filter.Filter_Path_Section_Text
704 (Filter.Filter_Text_Exact "A")
705 , Filter.Filter_Path_Section_Text
706 (Filter.Filter_Text_Exact "B")
707 ])
708 ((("A"::Text):|"B":[]))
709 , "A::B A:B" ~?
710 Filter.test
711 (Filter.Filter_Path Filter.Eq
712 [ Filter.Filter_Path_Section_Text
713 (Filter.Filter_Text_Exact "A")
714 , Filter.Filter_Path_Section_Many
715 , Filter.Filter_Path_Section_Many
716 , Filter.Filter_Path_Section_Text
717 (Filter.Filter_Text_Exact "B")
718 ])
719 ((("A"::Text):|"B":[]))
720 , ":B: A:B:C" ~?
721 Filter.test
722 (Filter.Filter_Path Filter.Eq
723 [ Filter.Filter_Path_Section_Many
724 , Filter.Filter_Path_Section_Text
725 (Filter.Filter_Text_Exact "B")
726 , Filter.Filter_Path_Section_Many
727 ])
728 ((("A"::Text):|"B":"C":[]))
729 , ":C A:B:C" ~?
730 Filter.test
731 (Filter.Filter_Path Filter.Eq
732 [ Filter.Filter_Path_Section_Many
733 , Filter.Filter_Path_Section_Text
734 (Filter.Filter_Text_Exact "C")
735 ])
736 ((("A"::Text):|"B":"C":[]))
737 , "<A:B:C::D A:B" ~?
738 Filter.test
739 (Filter.Filter_Path Filter.Lt
740 [ Filter.Filter_Path_Section_Text
741 (Filter.Filter_Text_Exact "A")
742 , Filter.Filter_Path_Section_Text
743 (Filter.Filter_Text_Exact "B")
744 , Filter.Filter_Path_Section_Text
745 (Filter.Filter_Text_Exact "C")
746 , Filter.Filter_Path_Section_Many
747 , Filter.Filter_Path_Section_Text
748 (Filter.Filter_Text_Exact "D")
749 ])
750 ((("A"::Text):|"B":[]))
751 , ">A:B:C::D A:B:C:CC:CCC:D:E" ~?
752 Filter.test
753 (Filter.Filter_Path Filter.Gt
754 [ Filter.Filter_Path_Section_Text
755 (Filter.Filter_Text_Exact "A")
756 , Filter.Filter_Path_Section_Text
757 (Filter.Filter_Text_Exact "B")
758 , Filter.Filter_Path_Section_Text
759 (Filter.Filter_Text_Exact "C")
760 , Filter.Filter_Path_Section_Many
761 , Filter.Filter_Path_Section_Text
762 (Filter.Filter_Text_Exact "D")
763 ])
764 ((("A"::Text):|"B":"C":"CC":"CCC":"D":"E":[]))
765 ]
766 , "Filter_Bool" ~: TestList
767 [ "Any A" ~?
768 Filter.test
769 (Filter.Any::Filter.Filter_Bool (Filter.Filter_Account (Tag.Tags, NonEmpty Text)))
770 (mempty, ("A":|[]))
771 ]
772 , "Filter_Ord" ~: TestList
773 [ "0 < (1, 2)" ~?
774 Filter.test
775 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer))
776 (fromJust $ (Lib.Interval.<=..<=) 1 2)
777 , "(-2, -1) < 0" ~?
778 Filter.test
779 (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer))
780 (fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
781 , "not (1 < (0, 2))" ~?
782 (not $ Filter.test
783 (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer))
784 (fromJust $ (Lib.Interval.<=..<=) 0 2))
785 ]
786 ]
787 , "Read" ~: TestList
788 [ "filter_account" ~: TestList
789 [ "*" ~:
790 (Data.Either.rights $
791 [P.runParser
792 (Filter.Read.filter_account_path <* P.eof)
793 () "" ("*"::Text)])
794 ~?=
795 [ Filter.Filter_Path Filter.Eq
796 [ Filter.Filter_Path_Section_Any ]
797 ]
798 , "A" ~:
799 (Data.Either.rights $
800 [P.runParser
801 (Filter.Read.filter_account_path <* P.eof)
802 () "" ("A"::Text)])
803 ~?=
804 [ Filter.Filter_Path Filter.Eq
805 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A") ]
806 ]
807 , "AA" ~:
808 (Data.Either.rights $
809 [P.runParser
810 (Filter.Read.filter_account_path <* P.eof)
811 () "" ("AA"::Text)])
812 ~?=
813 [ Filter.Filter_Path Filter.Eq
814 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "AA") ]
815 ]
816 , "::A" ~:
817 (Data.Either.rights $
818 [P.runParser
819 (Filter.Read.filter_account_path <* P.eof)
820 () "" ("::A"::Text)])
821 ~?=
822 [ Filter.Filter_Path Filter.Eq
823 [ Filter.Filter_Path_Section_Many
824 , Filter.Filter_Path_Section_Many
825 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
826 ]
827 ]
828 , ":A" ~:
829 (Data.Either.rights $
830 [P.runParser
831 (Filter.Read.filter_account_path <* P.eof)
832 () "" (":A"::Text)])
833 ~?=
834 [ Filter.Filter_Path Filter.Eq
835 [ Filter.Filter_Path_Section_Many
836 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
837 ]
838 ]
839 , "A:" ~:
840 (Data.Either.rights $
841 [P.runParser
842 (Filter.Read.filter_account_path <* P.eof)
843 () "" ("A:"::Text)])
844 ~?=
845 [ Filter.Filter_Path Filter.Eq
846 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
847 , Filter.Filter_Path_Section_Many
848 ]
849 ]
850 , "A::" ~:
851 (Data.Either.rights $
852 [P.runParser
853 (Filter.Read.filter_account_path <* P.eof)
854 () "" ("A::"::Text)])
855 ~?=
856 [ Filter.Filter_Path Filter.Eq
857 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
858 , Filter.Filter_Path_Section_Many
859 , Filter.Filter_Path_Section_Many
860 ]
861 ]
862 , "A:B" ~:
863 (Data.Either.rights $
864 [P.runParser
865 (Filter.Read.filter_account_path <* P.eof)
866 () "" ("A:B"::Text)])
867 ~?=
868 [ Filter.Filter_Path Filter.Eq
869 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
870 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
871 ]
872 ]
873 , "A::B" ~:
874 (Data.Either.rights $
875 [P.runParser
876 (Filter.Read.filter_account_path <* P.eof)
877 () "" ("A::B"::Text)])
878 ~?=
879 [ Filter.Filter_Path Filter.Eq
880 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
881 , Filter.Filter_Path_Section_Many
882 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
883 ]
884 ]
885 , "A:::B" ~:
886 (Data.Either.rights $
887 [P.runParser
888 (Filter.Read.filter_account_path <* P.eof)
889 () "" ("A:::B"::Text)])
890 ~?=
891 [ Filter.Filter_Path Filter.Eq
892 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
893 , Filter.Filter_Path_Section_Many
894 , Filter.Filter_Path_Section_Many
895 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
896 ]
897 ]
898 , "A: " ~:
899 (Data.Either.rights $
900 [P.runParser
901 (Filter.Read.filter_account_path <* P.char ' ' <* P.eof)
902 () "" ("A: "::Text)])
903 ~?=
904 [ Filter.Filter_Path Filter.Eq
905 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
906 , Filter.Filter_Path_Section_Many
907 ]
908 ]
909 , "<=A:B" ~:
910 (Data.Either.rights $
911 [P.runParser
912 (Filter.Read.filter_account_path <* P.eof)
913 () "" ("<=A:B"::Text)])
914 ~?=
915 [ Filter.Filter_Path Filter.Le
916 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
917 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
918 ]
919 ]
920 , ">=A:B" ~:
921 (Data.Either.rights $
922 [P.runParser
923 (Filter.Read.filter_account_path <* P.eof)
924 () "" (">=A:B"::Text)])
925 ~?=
926 [ Filter.Filter_Path Filter.Ge
927 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
928 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
929 ]
930 ]
931 , "<A:B" ~:
932 (Data.Either.rights $
933 [P.runParser
934 (Filter.Read.filter_account_path <* P.eof)
935 () "" ("<A:B"::Text)])
936 ~?=
937 [ Filter.Filter_Path Filter.Lt
938 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
939 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
940 ]
941 ]
942 , ">A:B" ~:
943 (Data.Either.rights $
944 [P.runParser
945 (Filter.Read.filter_account_path <* P.eof)
946 () "" (">A:B"::Text)])
947 ~?=
948 [ Filter.Filter_Path Filter.Gt
949 [ Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "A")
950 , Filter.Filter_Path_Section_Text (Filter.Filter_Text_Exact "B")
951 ]
952 ]
953 ]
954 , "filter_bool" ~: TestList
955 [ "( E )" ~:
956 (Data.Either.rights $
957 [P.runParser
958 (Filter.Read.filter_bool
959 [ P.char 'E' >> return (return $ Filter.Bool True) ]
960 <* P.eof)
961 () "" ("( E )"::Text)])
962 ~?=
963 [ Filter.And (Filter.Bool True) Filter.Any
964 ]
965 , "( ( E ) )" ~:
966 (Data.Either.rights $
967 [P.runParser
968 (Filter.Read.filter_bool
969 [ P.char 'E' >> return (return $ Filter.Bool True) ]
970 <* P.eof)
971 () "" ("( ( E ) )"::Text)])
972 ~?=
973 [ Filter.And (Filter.And (Filter.Bool True) Filter.Any) Filter.Any
974 ]
975 , "( E ) & ( E )" ~:
976 (Data.Either.rights $
977 [P.runParser
978 (Filter.Read.filter_bool
979 [ P.char 'E' >> return (return $ Filter.Bool True) ]
980 <* P.eof)
981 () "" ("( E ) & ( E )"::Text)])
982 ~?=
983 [ Filter.And
984 (Filter.And (Filter.Bool True) Filter.Any)
985 (Filter.And (Filter.Bool True) Filter.Any)
986 ]
987 , "( E ) + ( E )" ~:
988 (Data.Either.rights $
989 [P.runParser
990 (Filter.Read.filter_bool
991 [ P.char 'E' >> return (return $ Filter.Bool True) ]
992 <* P.eof)
993 () "" ("( E ) + ( E )"::Text)])
994 ~?=
995 [ Filter.Or
996 (Filter.And (Filter.Bool True) Filter.Any)
997 (Filter.And (Filter.Bool True) Filter.Any)
998 ]
999 , "( E ) - ( E )" ~:
1000 (Data.Either.rights $
1001 [P.runParser
1002 (Filter.Read.filter_bool
1003 [ P.char 'E' >> return (return $ Filter.Bool True) ]
1004 <* P.eof)
1005 () "" ("( E ) - ( E )"::Text)])
1006 ~?=
1007 [ Filter.And
1008 (Filter.And (Filter.Bool True) Filter.Any)
1009 (Filter.Not (Filter.And (Filter.Bool True) Filter.Any))
1010 ]
1011 , "(- E )" ~:
1012 (Data.Either.rights $
1013 [P.runParser
1014 (Filter.Read.filter_bool
1015 [ P.char 'E' >> return (return $ Filter.Bool True) ]
1016 <* P.eof)
1017 () "" ("(- E )"::Text)])
1018 ~?=
1019 [ Filter.And (Filter.Not (Filter.Bool True)) Filter.Any
1020 ]
1021 ]
1022 ]
1023 ]
1024 , "Balance" ~: TestList
1025 [ "balance" ~:
1026 TestList
1027 [ "[A+$1] = A+$1 & $+1" ~:
1028 (Balance.cons
1029 ( (("A"::Text):|[])
1030 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1031 )
1032 Balance.empty)
1033 ~?=
1034 (Balance.Balance
1035 { Balance.balance_by_account =
1036 TreeMap.from_List const $
1037 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1038 [ ("A":|[], amounts [ amount_usd $ 1 ]) ]
1039 , Balance.balance_by_unit =
1040 Balance.Balance_by_Unit $
1041 Map.fromList $
1042 [ amount_usd $ Balance.Unit_Sum
1043 { Balance.unit_sum_quantity = Polarize.polarize $ 1
1044 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1045 ["A":|[]]
1046 }
1047 ]
1048 }
1049 )
1050 , "[A+$1, A-$1] = {A+$0, $+0}" ~:
1051 (List.foldl (flip Balance.cons)
1052 Balance.empty
1053 [ ( (("A"::Text):|[])
1054 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1055 )
1056 , ( ("A":|[])
1057 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1 ]
1058 )
1059 ])
1060 ~?=
1061 Balance.Balance
1062 { Balance.balance_by_account =
1063 TreeMap.from_List const $
1064 [ ( "A":|[]
1065 , Balance.Account_Sum $
1066 Map.fromListWith const $
1067 [ amount_usd $ Polarize.Polarized_Both (-1) ( 1)
1068 ]
1069 ) ]
1070 , Balance.balance_by_unit =
1071 Balance.Balance_by_Unit $ Map.fromList $
1072 [ amount_usd $ Balance.Unit_Sum
1073 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) ( 1)
1074 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1075 ["A":|[]]
1076 }
1077 ]
1078 }
1079 , "[A+$1, A-€1] = {A+$1-€1, $+1 €-1}" ~:
1080 (List.foldl (flip Balance.cons)
1081 Balance.empty
1082 [ ( (("A"::Text):|[])
1083 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1084 )
1085 , ( ("A":|[])
1086 , Map.map Polarize.polarize $ amounts [ amount_eur $ -1 ]
1087 )
1088 ])
1089 ~?=
1090 Balance.Balance
1091 { Balance.balance_by_account =
1092 TreeMap.from_List const $
1093 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1094 [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ -1 ]) ]
1095 , Balance.balance_by_unit =
1096 Balance.Balance_by_Unit $ Map.fromList $
1097 [ amount_usd $ Balance.Unit_Sum
1098 { Balance.unit_sum_quantity = Polarize.Polarized_Positive 1
1099 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1100 ["A":|[]]
1101 }
1102 , amount_eur $ Balance.Unit_Sum
1103 { Balance.unit_sum_quantity = Polarize.Polarized_Negative (-1)
1104 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1105 ["A":|[]]
1106 }
1107 ]
1108 }
1109 , "[A+$1, B-$1] = {A+$1 B-$1, $+0}" ~:
1110 (List.foldl (flip Balance.cons)
1111 Balance.empty
1112 [ ( (("A"::Text):|[])
1113 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1114 )
1115 , ( ("B":|[])
1116 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1 ]
1117 )
1118 ])
1119 ~?=
1120 Balance.Balance
1121 { Balance.balance_by_account =
1122 TreeMap.from_List const $
1123 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1124 [ ("A":|[], amounts [ amount_usd $ 1 ])
1125 , ("B":|[], amounts [ amount_usd $ -1 ])
1126 ]
1127 , Balance.balance_by_unit =
1128 Balance.Balance_by_Unit $ Map.fromList $
1129 [ amount_usd $ Balance.Unit_Sum
1130 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) 1
1131 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1132 ["A":|[], "B":|[]]
1133 }
1134 ]
1135 }
1136 , "[A+$1, B+$1]" ~:
1137 (List.foldl (flip Balance.cons)
1138 Balance.empty
1139 [ ( (("A"::Text):|[])
1140 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer) ]
1141 )
1142 , ( ("B":|[])
1143 , Map.map Polarize.polarize $ amounts [ amount_usd $ 1 ]
1144 )
1145 ])
1146 ~?=
1147 Balance.Balance
1148 { Balance.balance_by_account =
1149 TreeMap.from_List const $
1150 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1151 [ ("A":|[], amounts [ amount_usd $ 1 ])
1152 , ("B":|[], amounts [ amount_usd $ 1 ])
1153 ]
1154 , Balance.balance_by_unit =
1155 Balance.Balance_by_Unit $ Map.fromList $
1156 [ amount_usd $ Balance.Unit_Sum
1157 { Balance.unit_sum_quantity = Polarize.polarize 2
1158 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1159 ["A":|[], "B":|[]]
1160 }
1161 ]
1162 }
1163 , "[A+$1+€2, A-$1-€2] = {A+$0+€0, $+0 €+0}" ~:
1164 (List.foldl (flip Balance.cons)
1165 Balance.empty
1166 [ ( (("A"::Text):|[])
1167 , Map.map Polarize.polarize $ amounts [ amount_usd $ 1, amount_eur $ (2::Integer) ]
1168 )
1169 , ( ("A":|[])
1170 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1, amount_eur $ -2 ]
1171 )
1172 ])
1173 ~?=
1174 Balance.Balance
1175 { Balance.balance_by_account =
1176 TreeMap.from_List const $
1177 [ ("A":|[]
1178 , Balance.Account_Sum $
1179 Map.fromListWith const $
1180 [ amount_usd $ Polarize.Polarized_Both (-1) 1
1181 , amount_eur $ Polarize.Polarized_Both (-2) 2
1182 ]
1183 )
1184 ]
1185 , Balance.balance_by_unit =
1186 Balance.Balance_by_Unit $ Map.fromList $
1187 [ amount_usd $ Balance.Unit_Sum
1188 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) 1
1189 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1190 ["A":|[]]
1191 }
1192 , amount_eur $ Balance.Unit_Sum
1193 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-2) 2
1194 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1195 ["A":|[]]
1196 }
1197 ]
1198 }
1199 , "[A+$1+€2+£3, B-$1-2€-£3] = {A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~:
1200 (List.foldl (flip Balance.cons)
1201 Balance.empty
1202 [ ( (("A"::Text):|[])
1203 , Map.map Polarize.polarize $ amounts [ amount_usd $ (1::Integer), amount_eur $ 2, amount_gbp $ 3 ]
1204 )
1205 , ( ("B":|[])
1206 , Map.map Polarize.polarize $ amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ]
1207 )
1208 ])
1209 ~?=
1210 Balance.Balance
1211 { Balance.balance_by_account =
1212 TreeMap.from_List const $
1213 List.map (id *** Balance.Account_Sum . Map.map Polarize.polarize) $
1214 [ ("A":|[], amounts [ amount_usd $ 1, amount_eur $ 2, amount_gbp $ 3 ])
1215 , ("B":|[], amounts [ amount_usd $ -1, amount_eur $ -2, amount_gbp $ -3 ])
1216 ]
1217 , Balance.balance_by_unit =
1218 Balance.Balance_by_Unit $
1219 Map.fromList $
1220 [ amount_usd $ Balance.Unit_Sum
1221 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-1) 1
1222 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1223 ["A":|[], "B":|[]]
1224 }
1225 , amount_eur $ Balance.Unit_Sum
1226 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-2) 2
1227 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1228 ["A":|[], "B":|[]]
1229 }
1230 , amount_gbp $ Balance.Unit_Sum
1231 { Balance.unit_sum_quantity = Polarize.Polarized_Both (-3) 3
1232 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1233 ["A":|[], "B":|[]]
1234 }
1235 ]
1236 }
1237 ]
1238 , "union" ~: TestList
1239 [ "{A+$1, $+1} {A+$1, $+1} = {A+$2, $+2}" ~:
1240 Balance.union
1241 (Balance.Balance
1242 { Balance.balance_by_account =
1243 TreeMap.from_List const $
1244 [ ( "A":|[]
1245 , Balance.Account_Sum $
1246 Map.fromListWith const $
1247 [ amount_usd $ Polarize.polarize 1 ]
1248 )
1249 ]
1250 , Balance.balance_by_unit =
1251 Balance.Balance_by_Unit $ Map.fromList $
1252 [ amount_usd $ Balance.Unit_Sum
1253 { Balance.unit_sum_quantity = Polarize.polarize 1
1254 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1255 ["A":|[]]
1256 }
1257 ]
1258 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1259 (Balance.Balance
1260 { Balance.balance_by_account =
1261 TreeMap.from_List const $
1262 [ ( "A":|[]
1263 , Balance.Account_Sum $
1264 Map.fromListWith const $
1265 [ amount_usd $ Polarize.polarize 1 ]
1266 )
1267 ]
1268 , Balance.balance_by_unit =
1269 Balance.Balance_by_Unit $ Map.fromList $
1270 [ amount_usd $ Balance.Unit_Sum
1271 { Balance.unit_sum_quantity = Polarize.polarize 1
1272 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1273 ["A":|[]]
1274 }
1275 ]
1276 })
1277 ~?=
1278 Balance.Balance
1279 { Balance.balance_by_account =
1280 TreeMap.from_List const $
1281 [ ( ("A":|[])
1282 , Balance.Account_Sum $
1283 Map.fromListWith const $
1284 [ amount_usd $ Polarize.polarize 2 ]
1285 )
1286 ]
1287 , Balance.balance_by_unit =
1288 Balance.Balance_by_Unit $ Map.fromList $
1289 [ amount_usd $ Balance.Unit_Sum
1290 { Balance.unit_sum_quantity = Polarize.polarize 2
1291 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1292 ["A":|[]]
1293 }
1294 ]
1295 }
1296 , "{A+$1, $+1} {B+$1, $+1} = {A+$1 B+$1, $+2}" ~:
1297 Balance.union
1298 (Balance.Balance
1299 { Balance.balance_by_account =
1300 TreeMap.from_List const $
1301 [ ( ("A":|[])
1302 , Balance.Account_Sum $
1303 Map.fromListWith const $
1304 [ amount_usd $ Polarize.polarize 1 ]
1305 )
1306 ]
1307 , Balance.balance_by_unit =
1308 Balance.Balance_by_Unit $ Map.fromList $
1309 [ amount_usd $ Balance.Unit_Sum
1310 { Balance.unit_sum_quantity = Polarize.polarize 1
1311 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1312 ["A":|[]]
1313 }
1314 ]
1315 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1316 (Balance.Balance
1317 { Balance.balance_by_account =
1318 TreeMap.from_List const $
1319 [ ( ("B":|[])
1320 , Balance.Account_Sum $
1321 Map.fromListWith const $
1322 [ amount_usd $ Polarize.polarize 1 ]
1323 )
1324 ]
1325 , Balance.balance_by_unit =
1326 Balance.Balance_by_Unit $ Map.fromList $
1327 [ amount_usd $ Balance.Unit_Sum
1328 { Balance.unit_sum_quantity = Polarize.polarize 1
1329 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1330 ["B":|[]]
1331 }
1332 ]
1333 })
1334 ~?=
1335 Balance.Balance
1336 { Balance.balance_by_account =
1337 TreeMap.from_List const $
1338 [ ( ("A":|[])
1339 , Balance.Account_Sum $
1340 Map.fromListWith const $
1341 [ amount_usd $ Polarize.polarize 1 ]
1342 )
1343 , ( ("B":|[])
1344 , Balance.Account_Sum $
1345 Map.fromListWith const $
1346 [ amount_usd $ Polarize.polarize 1 ]
1347 )
1348 ]
1349 , Balance.balance_by_unit =
1350 Balance.Balance_by_Unit $ Map.fromList $
1351 [ amount_usd $ Balance.Unit_Sum
1352 { Balance.unit_sum_quantity = Polarize.polarize 2
1353 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1354 ["A":|[], "B":|[]]
1355 }
1356 ]
1357 }
1358 , "{A+$1, $+1} {B+€1, €+1} = {A+$1 B+€1, $+1 €+1}" ~:
1359 Balance.union
1360 (Balance.Balance
1361 { Balance.balance_by_account =
1362 TreeMap.from_List const $
1363 [ ( ("A":|[])
1364 , Balance.Account_Sum $
1365 Map.fromListWith const $
1366 [ amount_usd $ Polarize.polarize 1 ]
1367 )
1368 ]
1369 , Balance.balance_by_unit =
1370 Balance.Balance_by_Unit $ Map.fromList $
1371 [ amount_usd $ Balance.Unit_Sum
1372 { Balance.unit_sum_quantity = Polarize.polarize 1
1373 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1374 ["A":|[]]
1375 }
1376 ]
1377 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1378 (Balance.Balance
1379 { Balance.balance_by_account =
1380 TreeMap.from_List const $
1381 [ ( ("B":|[])
1382 , Balance.Account_Sum $
1383 Map.fromListWith const $
1384 [ amount_eur $ Polarize.polarize 1 ]
1385 )
1386 ]
1387 , Balance.balance_by_unit =
1388 Balance.Balance_by_Unit $ Map.fromList $
1389 [ amount_eur $ Balance.Unit_Sum
1390 { Balance.unit_sum_quantity = Polarize.polarize 1
1391 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1392 ["B":|[]]
1393 }
1394 ]
1395 })
1396 ~?=
1397 Balance.Balance
1398 { Balance.balance_by_account =
1399 TreeMap.from_List const $
1400 [ ( ("A":|[])
1401 , Balance.Account_Sum $
1402 Map.fromListWith const $
1403 [ amount_usd $ Polarize.polarize 1 ]
1404 )
1405 , ( ("B":|[])
1406 , Balance.Account_Sum $
1407 Map.fromListWith const $
1408 [ amount_eur $ Polarize.polarize 1 ]
1409 )
1410 ]
1411 , Balance.balance_by_unit =
1412 Balance.Balance_by_Unit $ Map.fromList $
1413 [ amount_usd $ Balance.Unit_Sum
1414 { Balance.unit_sum_quantity = Polarize.polarize 1
1415 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1416 ["A":|[]]
1417 }
1418 , amount_eur $ Balance.Unit_Sum
1419 { Balance.unit_sum_quantity = Polarize.polarize 1
1420 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1421 ["B":|[]]
1422 }
1423 ]
1424 }
1425 ]
1426 , "expanded" ~: TestList
1427 [ "mempty" ~:
1428 Balance.expanded TreeMap.empty
1429 ~?=
1430 (TreeMap.empty::Balance.Expanded (NonEmpty Text) Text Integer)
1431 , "A+$1 = A+$1" ~:
1432 Balance.expanded
1433 (TreeMap.from_List const $
1434 [ ( ("A":|[])
1435 , Balance.Account_Sum $
1436 Map.fromListWith const $
1437 [ amount_usd $ Polarize.polarize 1 ]
1438 )
1439 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1440 ~?=
1441 (TreeMap.from_List const $
1442 [ ("A":|[], Balance.Account_Sum_Expanded
1443 { Balance.inclusive =
1444 Balance.Account_Sum $
1445 Map.map Polarize.polarize $
1446 amounts [ amount_usd $ 1 ]
1447 , Balance.exclusive =
1448 Balance.Account_Sum $
1449 Map.map Polarize.polarize $
1450 amounts [ amount_usd $ 1 ]
1451 })
1452 ])
1453 , "A/A+$1 = A+$1 A/A+$1" ~:
1454 Balance.expanded
1455 (TreeMap.from_List const $
1456 [ ( ("A":|["A"])
1457 , Balance.Account_Sum $
1458 Map.fromListWith const $
1459 [ amount_usd $ Polarize.polarize 1 ]
1460 )
1461 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1462 ~?=
1463 (TreeMap.from_List const
1464 [ ("A":|[], Balance.Account_Sum_Expanded
1465 { Balance.inclusive =
1466 Balance.Account_Sum $
1467 Map.map Polarize.polarize $
1468 amounts [ amount_usd $ 1 ]
1469 , Balance.exclusive =
1470 Balance.Account_Sum $
1471 Map.map Polarize.polarize $
1472 amounts []
1473 })
1474 , ("A":|["A"], Balance.Account_Sum_Expanded
1475 { Balance.inclusive =
1476 Balance.Account_Sum $
1477 Map.map Polarize.polarize $
1478 amounts [ amount_usd $ 1 ]
1479 , Balance.exclusive =
1480 Balance.Account_Sum $
1481 Map.map Polarize.polarize $
1482 amounts [ amount_usd $ 1 ]
1483 })
1484 ])
1485 , "A/B+$1 = A+$1 A/B+$1" ~:
1486 Balance.expanded
1487 (TreeMap.from_List const $
1488 [ ( ("A":|["B"])
1489 , Balance.Account_Sum $
1490 Map.fromListWith const $
1491 [ amount_usd $ Polarize.polarize 1 ]
1492 )
1493 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1494 ~?=
1495 (TreeMap.from_List const
1496 [ ("A":|[], Balance.Account_Sum_Expanded
1497 { Balance.inclusive =
1498 Balance.Account_Sum $
1499 Map.map Polarize.polarize $
1500 amounts [ amount_usd $ 1 ]
1501 , Balance.exclusive =
1502 Balance.Account_Sum $
1503 Map.map Polarize.polarize $
1504 amounts []
1505 })
1506 , ("A":|["B"], Balance.Account_Sum_Expanded
1507 { Balance.inclusive =
1508 Balance.Account_Sum $
1509 Map.map Polarize.polarize $
1510 amounts [ amount_usd $ 1 ]
1511 , Balance.exclusive =
1512 Balance.Account_Sum $
1513 Map.map Polarize.polarize $
1514 amounts [ amount_usd $ 1 ]
1515 })
1516 ])
1517 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
1518 Balance.expanded
1519 (TreeMap.from_List const $
1520 [ ( ("A":|["B", "C"])
1521 , Balance.Account_Sum $
1522 Map.fromListWith const $
1523 [ amount_usd $ Polarize.polarize 1 ]
1524 )
1525 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1526 ~?=
1527 (TreeMap.from_List const $
1528 [ ("A":|[], Balance.Account_Sum_Expanded
1529 { Balance.inclusive =
1530 Balance.Account_Sum $
1531 Map.map Polarize.polarize $
1532 amounts [ amount_usd $ 1 ]
1533 , Balance.exclusive =
1534 Balance.Account_Sum $
1535 Map.map Polarize.polarize $
1536 amounts []
1537 })
1538 , ("A":|["B"], Balance.Account_Sum_Expanded
1539 { Balance.inclusive =
1540 Balance.Account_Sum $
1541 Map.map Polarize.polarize $
1542 amounts [ amount_usd $ 1 ]
1543 , Balance.exclusive =
1544 Balance.Account_Sum $
1545 Map.map Polarize.polarize $
1546 amounts []
1547 })
1548 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
1549 { Balance.inclusive =
1550 Balance.Account_Sum $
1551 Map.map Polarize.polarize $
1552 amounts [ amount_usd $ 1 ]
1553 , Balance.exclusive =
1554 Balance.Account_Sum $
1555 Map.map Polarize.polarize $
1556 amounts [ amount_usd $ 1 ]
1557 })
1558 ])
1559 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
1560 Balance.expanded
1561 (TreeMap.from_List const $
1562 [ ( ("A":|[])
1563 , Balance.Account_Sum $
1564 Map.fromListWith const $
1565 [ amount_usd $ Polarize.polarize 1 ]
1566 )
1567 , ( ("A":|["B"])
1568 , Balance.Account_Sum $
1569 Map.fromListWith const $
1570 [ amount_usd $ Polarize.polarize 1 ]
1571 )
1572 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1573 ~?=
1574 (TreeMap.from_List const
1575 [ ("A":|[], Balance.Account_Sum_Expanded
1576 { Balance.inclusive =
1577 Balance.Account_Sum $
1578 Map.map Polarize.polarize $
1579 amounts [ amount_usd $ 2 ]
1580 , Balance.exclusive =
1581 Balance.Account_Sum $
1582 Map.map Polarize.polarize $
1583 amounts [ amount_usd $ 1 ]
1584 })
1585 , ("A":|["B"], Balance.Account_Sum_Expanded
1586 { Balance.inclusive =
1587 Balance.Account_Sum $
1588 Map.map Polarize.polarize $
1589 amounts [ amount_usd $ 1 ]
1590 , Balance.exclusive =
1591 Balance.Account_Sum $
1592 Map.map Polarize.polarize $
1593 amounts [ amount_usd $ 1 ]
1594 })
1595 ])
1596 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
1597 Balance.expanded
1598 (TreeMap.from_List const $
1599 [ ( ("A":|[])
1600 , Balance.Account_Sum $
1601 Map.fromListWith const $
1602 [ amount_usd $ Polarize.polarize 1 ]
1603 )
1604 , ( ("A":|["B"])
1605 , Balance.Account_Sum $
1606 Map.fromListWith const $
1607 [ amount_usd $ Polarize.polarize 1 ]
1608 )
1609 , ( ("A":|["B", "C"])
1610 , Balance.Account_Sum $
1611 Map.fromListWith const $
1612 [ amount_usd $ Polarize.polarize 1 ]
1613 )
1614 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1615 ~?=
1616 (TreeMap.from_List const
1617 [ ("A":|[], Balance.Account_Sum_Expanded
1618 { Balance.inclusive =
1619 Balance.Account_Sum $
1620 Map.map Polarize.polarize $
1621 amounts [ amount_usd $ 3 ]
1622 , Balance.exclusive =
1623 Balance.Account_Sum $
1624 Map.map Polarize.polarize $
1625 amounts [ amount_usd $ 1 ]
1626 })
1627 , ("A":|["B"], Balance.Account_Sum_Expanded
1628 { Balance.inclusive =
1629 Balance.Account_Sum $
1630 Map.map Polarize.polarize $
1631 amounts [ amount_usd $ 2 ]
1632 , Balance.exclusive =
1633 Balance.Account_Sum $
1634 Map.map Polarize.polarize $
1635 amounts [ amount_usd $ 1 ]
1636 })
1637 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
1638 { Balance.inclusive =
1639 Balance.Account_Sum $
1640 Map.map Polarize.polarize $
1641 amounts [ amount_usd $ 1 ]
1642 , Balance.exclusive =
1643 Balance.Account_Sum $
1644 Map.map Polarize.polarize $
1645 amounts [ amount_usd $ 1 ]
1646 })
1647 ])
1648 , "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" ~:
1649 Balance.expanded
1650 (TreeMap.from_List const $
1651 [ ( ("A":|[])
1652 , Balance.Account_Sum $
1653 Map.fromListWith const $
1654 [ amount_usd $ Polarize.polarize 1 ]
1655 )
1656 , ( ("A":|["B"])
1657 , Balance.Account_Sum $
1658 Map.fromListWith const $
1659 [ amount_usd $ Polarize.polarize 1 ]
1660 )
1661 , ( ("A":|["B", "C"])
1662 , Balance.Account_Sum $
1663 Map.fromListWith const $
1664 [ amount_usd $ Polarize.polarize 1 ]
1665 )
1666 , ( ("A":|["B", "C", "D"])
1667 , Balance.Account_Sum $
1668 Map.fromListWith const $
1669 [ amount_usd $ Polarize.polarize 1 ]
1670 )
1671 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1672 ~?=
1673 (TreeMap.from_List const
1674 [ ("A":|[], Balance.Account_Sum_Expanded
1675 { Balance.inclusive =
1676 Balance.Account_Sum $
1677 Map.map Polarize.polarize $
1678 amounts [ amount_usd $ 4 ]
1679 , Balance.exclusive =
1680 Balance.Account_Sum $
1681 Map.map Polarize.polarize $
1682 amounts [ amount_usd $ 1 ]
1683 })
1684 , ("A":|["B"], Balance.Account_Sum_Expanded
1685 { Balance.inclusive =
1686 Balance.Account_Sum $
1687 Map.map Polarize.polarize $
1688 amounts [ amount_usd $ 3 ]
1689 , Balance.exclusive =
1690 Balance.Account_Sum $
1691 Map.map Polarize.polarize $
1692 amounts [ amount_usd $ 1 ]
1693 })
1694 , ("A":|["B", "C"], Balance.Account_Sum_Expanded
1695 { Balance.inclusive =
1696 Balance.Account_Sum $
1697 Map.map Polarize.polarize $
1698 amounts [ amount_usd $ 2 ]
1699 , Balance.exclusive =
1700 Balance.Account_Sum $
1701 Map.map Polarize.polarize $
1702 amounts [ amount_usd $ 1 ]
1703 })
1704 , ("A":|["B", "C", "D"], Balance.Account_Sum_Expanded
1705 { Balance.inclusive =
1706 Balance.Account_Sum $
1707 Map.map Polarize.polarize $
1708 amounts [ amount_usd $ 1 ]
1709 , Balance.exclusive =
1710 Balance.Account_Sum $
1711 Map.map Polarize.polarize $
1712 amounts [ amount_usd $ 1 ]
1713 })
1714 ])
1715 , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
1716 Balance.expanded
1717 (TreeMap.from_List const $
1718 [ ( ("A":|[])
1719 , Balance.Account_Sum $
1720 Map.fromListWith const $
1721 [ amount_usd $ Polarize.polarize 1 ]
1722 )
1723 , ( ("A":|["B"])
1724 , Balance.Account_Sum $
1725 Map.fromListWith const $
1726 [ amount_usd $ Polarize.polarize 1 ]
1727 )
1728 , ( ("A":|["BB"])
1729 , Balance.Account_Sum $
1730 Map.fromListWith const $
1731 [ amount_usd $ Polarize.polarize 1 ]
1732 )
1733 , ( ("AA":|["B"])
1734 , Balance.Account_Sum $
1735 Map.fromListWith const $
1736 [ amount_usd $ Polarize.polarize 1 ]
1737 )
1738 ]::Balance.Balance_by_Account Text Text (Polarize.Polarized Integer))
1739 ~?=
1740 (TreeMap.from_List const
1741 [ ("A":|[], Balance.Account_Sum_Expanded
1742 { Balance.inclusive =
1743 Balance.Account_Sum $
1744 Map.map Polarize.polarize $
1745 amounts [ amount_usd $ 3 ]
1746 , Balance.exclusive =
1747 Balance.Account_Sum $
1748 Map.map Polarize.polarize $
1749 amounts [ amount_usd $ 1 ]
1750 })
1751 , ("A":|["B"], Balance.Account_Sum_Expanded
1752 { Balance.inclusive =
1753 Balance.Account_Sum $
1754 Map.map Polarize.polarize $
1755 amounts [ amount_usd $ 1 ]
1756 , Balance.exclusive =
1757 Balance.Account_Sum $
1758 Map.map Polarize.polarize $
1759 amounts [ amount_usd $ 1 ]
1760 })
1761 , ("A":|["BB"], Balance.Account_Sum_Expanded
1762 { Balance.inclusive =
1763 Balance.Account_Sum $
1764 Map.map Polarize.polarize $
1765 amounts [ amount_usd $ 1 ]
1766 , Balance.exclusive =
1767 Balance.Account_Sum $
1768 Map.map Polarize.polarize $
1769 amounts [ amount_usd $ 1 ]
1770 })
1771 , ("AA":|[], Balance.Account_Sum_Expanded
1772 { Balance.inclusive =
1773 Balance.Account_Sum $
1774 Map.map Polarize.polarize $
1775 amounts [ amount_usd $ 1 ]
1776 , Balance.exclusive =
1777 Balance.Account_Sum $
1778 Map.map Polarize.polarize $
1779 amounts []
1780 })
1781 , ("AA":|["B"], Balance.Account_Sum_Expanded
1782 { Balance.inclusive =
1783 Balance.Account_Sum $
1784 Map.map Polarize.polarize $
1785 amounts [ amount_usd $ 1 ]
1786 , Balance.exclusive =
1787 Balance.Account_Sum $
1788 Map.map Polarize.polarize $
1789 amounts [ amount_usd $ 1 ]
1790 })
1791 ])
1792 ]
1793 , "deviation" ~: TestList
1794 [ "{A+$1, $1}" ~:
1795 (Balance.deviation $
1796 Balance.Balance
1797 { Balance.balance_by_account =
1798 TreeMap.from_List const $
1799 [ ( ("A":|[])
1800 , Balance.Account_Sum $
1801 Map.fromListWith const $
1802 [ amount_usd $ Polarize.polarize 1 ]
1803 )
1804 , ( ("B":|[])
1805 , Balance.Account_Sum $
1806 Map.fromListWith const $
1807 [ ]
1808 )
1809 ]
1810 , Balance.balance_by_unit =
1811 Balance.Balance_by_Unit $ Map.fromList $
1812 [ amount_usd $ Balance.Unit_Sum
1813 { Balance.unit_sum_quantity = Polarize.polarize 1
1814 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1815 ["A":|[]]
1816 }
1817 ]
1818 }::Balance.Deviation (NonEmpty Text) Text (Polarize.Polarized Integer))
1819 ~?=
1820 (Balance.Deviation $
1821 Balance.Balance_by_Unit $ Map.fromList $
1822 [ amount_usd $ Balance.Unit_Sum
1823 { Balance.unit_sum_quantity = Polarize.polarize 1
1824 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1825 ["B":|[]]
1826 }
1827 ])
1828 , "{A+$1 B+$1, $2}" ~:
1829 (Balance.deviation $
1830 Balance.Balance
1831 { Balance.balance_by_account =
1832 TreeMap.from_List const $
1833 [ ( ("A":|[])
1834 , Balance.Account_Sum $
1835 Map.fromListWith const $
1836 [ amount_usd $ Polarize.polarize 1 ]
1837 )
1838 , ( ("B":|[])
1839 , Balance.Account_Sum $
1840 Map.fromListWith const $
1841 [ amount_usd $ Polarize.polarize 1 ]
1842 )
1843 ]
1844 , Balance.balance_by_unit =
1845 Balance.Balance_by_Unit $ Map.fromList $
1846 [ amount_usd $ Balance.Unit_Sum
1847 { Balance.unit_sum_quantity = Polarize.polarize 2
1848 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1849 [ "A":|[]
1850 , "B":|[]
1851 ]
1852 }
1853 ]
1854 }::Balance.Deviation (NonEmpty Text) Text (Polarize.Polarized Integer))
1855 ~?=
1856 (Balance.Deviation $
1857 Balance.Balance_by_Unit $ Map.fromList $
1858 [ amount_usd $ Balance.Unit_Sum
1859 { Balance.unit_sum_quantity = Polarize.polarize 2
1860 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1861 [
1862 ]
1863 }
1864 ])
1865 ]
1866 , "is_equilibrium_inferrable" ~: TestList
1867 [ "empty" ~: TestCase $
1868 (@=?) True $
1869 Balance.is_equilibrium_inferrable $
1870 Balance.deviation $
1871 (Balance.empty::Balance.Balance (NonEmpty Text) Text Integer)
1872 , "{A+$0, $+0}" ~: TestCase $
1873 (@=?) True $
1874 Balance.is_equilibrium_inferrable $
1875 Balance.deviation $
1876 (Balance.Balance
1877 { Balance.balance_by_account =
1878 TreeMap.from_List const $
1879 [ ( ("A":|[])
1880 , Balance.Account_Sum $
1881 Map.fromListWith const $
1882 [ amount_usd $ Polarize.polarize 0 ]
1883 )
1884 ]
1885 , Balance.balance_by_unit =
1886 Balance.Balance_by_Unit $ Map.fromList $
1887 [ amount_usd $ Balance.Unit_Sum
1888 { Balance.unit_sum_quantity = Polarize.polarize 0
1889 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1890 ["A":|[]]
1891 }
1892 ]
1893 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1894 , "{A+$1, $+1}" ~: TestCase $
1895 (@=?) False $
1896 Balance.is_equilibrium_inferrable $
1897 Balance.deviation $
1898 (Balance.Balance
1899 { Balance.balance_by_account =
1900 TreeMap.from_List const $
1901 [ ( ("A":|[])
1902 , Balance.Account_Sum $
1903 Map.fromListWith const $
1904 [ amount_usd $ Polarize.polarize 1 ]
1905 )
1906 ]
1907 , Balance.balance_by_unit =
1908 Balance.Balance_by_Unit $ Map.fromList $
1909 [ amount_usd $ Balance.Unit_Sum
1910 { Balance.unit_sum_quantity = Polarize.polarize 1
1911 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1912 ["A":|[]]
1913 }
1914 ]
1915 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1916 , "{A+$0+€0, $0 €+0}" ~: TestCase $
1917 (@=?) True $
1918 Balance.is_equilibrium_inferrable $
1919 Balance.deviation $
1920 (Balance.Balance
1921 { Balance.balance_by_account =
1922 TreeMap.from_List const $
1923 [ ( ("A":|[])
1924 , Balance.Account_Sum $
1925 Map.fromListWith const $
1926 [ amount_usd $ Polarize.polarize 0
1927 , amount_eur $ Polarize.polarize 0
1928 ]
1929 )
1930 ]
1931 , Balance.balance_by_unit =
1932 Balance.Balance_by_Unit $ Map.fromList $
1933 [ amount_usd $ Balance.Unit_Sum
1934 { Balance.unit_sum_quantity = Polarize.polarize 0
1935 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1936 ["A":|[]]
1937 }
1938 , amount_eur $ Balance.Unit_Sum
1939 { Balance.unit_sum_quantity = Polarize.polarize 0
1940 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1941 ["A":|[]]
1942 }
1943 ]
1944 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1945 , "{A+$1, B-$1, $+0}" ~: TestCase $
1946 (@=?) True $
1947 Balance.is_equilibrium_inferrable $
1948 Balance.deviation $
1949 (Balance.Balance
1950 { Balance.balance_by_account =
1951 TreeMap.from_List const $
1952 [ ( ("A":|[])
1953 , Balance.Account_Sum $
1954 Map.fromListWith const $
1955 [ amount_usd $ Polarize.polarize 1 ]
1956 )
1957 , ( ("B":|[])
1958 , Balance.Account_Sum $
1959 Map.fromListWith const $
1960 [ amount_usd $ Polarize.polarize (-1) ]
1961 )
1962 ]
1963 , Balance.balance_by_unit =
1964 Balance.Balance_by_Unit $ Map.fromList $
1965 [ amount_usd $ Balance.Unit_Sum
1966 { Balance.unit_sum_quantity = Polarize.polarize 0
1967 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1968 ["A":|[], "B":|[]]
1969 }
1970 ]
1971 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1972 , "{A+$1 B, $+1}" ~: TestCase $
1973 (@=?) True $
1974 Balance.is_equilibrium_inferrable $
1975 Balance.deviation $
1976 (Balance.Balance
1977 { Balance.balance_by_account =
1978 TreeMap.from_List const $
1979 [ ( ("A":|[])
1980 , Balance.Account_Sum $
1981 Map.fromListWith const $
1982 [ amount_usd $ Polarize.polarize 1 ]
1983 )
1984 , ( ("B":|[])
1985 , Balance.Account_Sum $
1986 Map.fromListWith const $
1987 [ ]
1988 )
1989 ]
1990 , Balance.balance_by_unit =
1991 Balance.Balance_by_Unit $ Map.fromList $
1992 [ amount_usd $ Balance.Unit_Sum
1993 { Balance.unit_sum_quantity = Polarize.polarize 1
1994 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
1995 ["A":|[]]
1996 }
1997 ]
1998 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
1999 , "{A+$1 B+€1, $+1 €+1}" ~: TestCase $
2000 (@=?) True $
2001 Balance.is_equilibrium_inferrable $
2002 Balance.deviation $
2003 (Balance.Balance
2004 { Balance.balance_by_account =
2005 TreeMap.from_List const $
2006 [ ( ("A":|[])
2007 , Balance.Account_Sum $
2008 Map.fromListWith const $
2009 [ amount_usd $ Polarize.polarize 1 ]
2010 )
2011 , ( ("B":|[])
2012 , Balance.Account_Sum $
2013 Map.fromListWith const $
2014 [ amount_eur $ Polarize.polarize 1 ]
2015 )
2016 ]
2017 , Balance.balance_by_unit =
2018 Balance.Balance_by_Unit $ Map.fromList $
2019 [ amount_usd $ Balance.Unit_Sum
2020 { Balance.unit_sum_quantity = Polarize.polarize 1
2021 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2022 ["A":|[]]
2023 }
2024 , amount_eur $ Balance.Unit_Sum
2025 { Balance.unit_sum_quantity = Polarize.polarize 1
2026 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2027 ["B":|[]]
2028 }
2029 ]
2030 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
2031 , "{A+$1 B-$1+€1, $+0 €+1}" ~: TestCase $
2032 (@=?) True $
2033 Balance.is_equilibrium_inferrable $
2034 Balance.deviation $
2035 (Balance.Balance
2036 { Balance.balance_by_account =
2037 TreeMap.from_List const $
2038 [ ( ("A":|[])
2039 , Balance.Account_Sum $
2040 Map.fromListWith const $
2041 [ amount_usd $ Polarize.polarize 1 ]
2042 )
2043 , ( ("B":|[])
2044 , Balance.Account_Sum $
2045 Map.fromListWith const $
2046 [ amount_usd $ Polarize.polarize (-1)
2047 , amount_eur $ Polarize.polarize 1
2048 ]
2049 )
2050 ]
2051 , Balance.balance_by_unit =
2052 Balance.Balance_by_Unit $ Map.fromList $
2053 [ amount_usd $ Balance.Unit_Sum
2054 { Balance.unit_sum_quantity = Polarize.polarize 0
2055 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2056 ["A":|[], "B":|[]]
2057 }
2058 , amount_eur $ Balance.Unit_Sum
2059 { Balance.unit_sum_quantity = Polarize.polarize 1
2060 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2061 ["B":|[]]
2062 }
2063 ]
2064 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
2065 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0}" ~: TestCase $
2066 (@=?) True $
2067 Balance.is_equilibrium_inferrable $
2068 Balance.deviation $
2069 (Balance.Balance
2070 { Balance.balance_by_account =
2071 TreeMap.from_List const $
2072 [ ( ("A":|[])
2073 , Balance.Account_Sum $
2074 Map.fromListWith const $
2075 [ amount_usd $ Polarize.polarize 1
2076 , amount_eur $ Polarize.polarize 2
2077 , amount_gbp $ Polarize.polarize 3
2078 ]
2079 )
2080 , ( ("B":|[])
2081 , Balance.Account_Sum $
2082 Map.fromListWith const $
2083 [ amount_usd $ Polarize.polarize (-1)
2084 , amount_eur $ Polarize.polarize (-2)
2085 , amount_gbp $ Polarize.polarize (-3)
2086 ]
2087 )
2088 ]
2089 , Balance.balance_by_unit =
2090 Balance.Balance_by_Unit $ Map.fromList $
2091 [ amount_usd $ Balance.Unit_Sum
2092 { Balance.unit_sum_quantity = Polarize.polarize 0
2093 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2094 ["A":|[], "B":|[]]
2095 }
2096 , amount_eur $ Balance.Unit_Sum
2097 { Balance.unit_sum_quantity = Polarize.polarize 0
2098 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2099 ["A":|[], "B":|[]]
2100 }
2101 , amount_gbp $ Balance.Unit_Sum
2102 { Balance.unit_sum_quantity = Polarize.polarize 0
2103 , Balance.unit_sum_accounts = Map.fromList $ List.map (,())
2104 ["A":|[], "B":|[]]
2105 }
2106 ]
2107 }::Balance.Balance (NonEmpty Text) Text (Polarize.Polarized Integer))
2108 ]
2109 , "infer_equilibrium" ~: TestList
2110 [ "{A+$1 B}" ~:
2111 (snd $ Balance.infer_equilibrium $
2112 Map.fromList $
2113 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2114 [ ( ("A"::Text):|[]
2115 , amounts [ amount_usd $ (1::Integer) ] )
2116 , ( "B":|[]
2117 , amounts [] )
2118 ])
2119 ~?=
2120 (Right $
2121 Map.fromList $
2122 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2123 [ ( "A":|[]
2124 , amounts [ amount_usd $ 1 ] )
2125 , ( "B":|[]
2126 , amounts [ amount_usd $ -1 ] )
2127 ])
2128 , "{A+$1 B-1€}" ~:
2129 (snd $ Balance.infer_equilibrium $
2130 Map.fromList $
2131 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2132 [ ( ("A"::Text):|[]
2133 , amounts [ amount_usd $ (1::Integer) ] )
2134 , ( "B":|[]
2135 , amounts [ amount_eur $ -1 ] )
2136 ])
2137 ~?=
2138 (Right $
2139 Map.fromList $
2140 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2141 [ ( ("A"::Text):|[]
2142 , amounts [ amount_usd $ 1, amount_eur $ (1::Integer)] )
2143 , ( "B":|[]
2144 , amounts [ amount_eur $ -1, amount_usd $ -1 ] )
2145 ])
2146 , "{A+$1 B+$1}" ~:
2147 (snd $ Balance.infer_equilibrium $
2148 Map.fromList $
2149 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2150 [ ( ("A"::Text):|[]
2151 , amounts [ amount_usd $ (1::Integer) ] )
2152 , ( "B":|[]
2153 , amounts [ amount_usd $ 1 ] )
2154 ])
2155 ~?=
2156 (Left
2157 [ amount_usd $ Balance.Unit_Sum
2158 { Balance.unit_sum_quantity = 2
2159 , Balance.unit_sum_accounts = Map.fromList []}
2160 ])
2161 , "{A+$1 B-$1 B-1€}" ~:
2162 (snd $ Balance.infer_equilibrium $
2163 Map.fromList $
2164 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2165 [ ( ("A"::Text):|[]
2166 , amounts [ amount_usd $ (1::Integer) ] )
2167 , ( "B":|[]
2168 , amounts [ amount_usd $ -1, amount_eur $ -1 ] )
2169 ])
2170 ~?=
2171 (Right $
2172 Map.fromList $
2173 List.map (\(acct, amts) -> (acct, [(acct, amts)])) $
2174 [ ( "A":|[]
2175 , amounts [ amount_usd $ 1, amount_eur $ 1 ] )
2176 , ( "B":|[]
2177 , amounts [ amount_usd $ -1, amount_eur $ -1 ] )
2178 ])
2179 ]
2180 ]
2181 ]
2182 -}