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