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