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