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