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