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