]> Git — Sourcephile - comptalang.git/blob - lib/Test/Main.hs
Ajout : Format.Ledger.Write.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 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_by_amount_unit $
141 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
169 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
197 [ Calc.Balance.Sum_by_Unit
198 { Calc.Balance.amount = Amount.usd $ 1
199 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
200 [["A"]]
201 }
202 , Calc.Balance.Sum_by_Unit
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_by_amount_unit $
232 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
261 [ Calc.Balance.Sum_by_Unit
262 { Calc.Balance.amount = Amount.usd $ 0
263 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
264 [["A"]]
265 }
266 , Calc.Balance.Sum_by_Unit
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_by_amount_unit $
296 [ Calc.Balance.Sum_by_Unit
297 { Calc.Balance.amount = Amount.usd $ 0
298 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
299 [["A"], ["B"]]
300 }
301 , Calc.Balance.Sum_by_Unit
302 { Calc.Balance.amount = Amount.eur $ 0
303 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
304 [["A"], ["B"]]
305 }
306 , Calc.Balance.Sum_by_Unit
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_by_amount_unit $
330 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
344 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
359 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
375 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
389 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
405 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
421 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
435 [ Calc.Balance.Sum_by_Unit
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_by_amount_unit $
451 [ Calc.Balance.Sum_by_Unit
452 { Calc.Balance.amount = Amount.usd $ 1
453 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
454 [["A"]]
455 }
456 , Calc.Balance.Sum_by_Unit
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_equilibrated" ~: TestList
575 [ "nil = True" ~: TestCase $
576 (@=?) True $
577 Calc.Balance.is_equilibrated $
578 Calc.Balance.nil
579 , "{A+$0, $+0} = True" ~: TestCase $
580 (@=?) True $
581 Calc.Balance.is_equilibrated $
582 Calc.Balance.Balance
583 { Calc.Balance.by_account =
584 Data.Map.fromList
585 [ (["A"], Amount.from_List [ Amount.usd $ 0 ])
586 ]
587 , Calc.Balance.by_unit =
588 Data.Map.fromList $
589 Data.List.map Calc.Balance.assoc_by_amount_unit $
590 [ Calc.Balance.Sum_by_Unit
591 { Calc.Balance.amount = Amount.usd $ 0
592 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
593 [["A"]]
594 }
595 ]
596 }
597 , "{A+$1, $+1} = False" ~: TestCase $
598 (@=?) False $
599 Calc.Balance.is_equilibrated $
600 Calc.Balance.Balance
601 { Calc.Balance.by_account =
602 Data.Map.fromList
603 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
604 ]
605 , Calc.Balance.by_unit =
606 Data.Map.fromList $
607 Data.List.map Calc.Balance.assoc_by_amount_unit $
608 [ Calc.Balance.Sum_by_Unit
609 { Calc.Balance.amount = Amount.usd $ 1
610 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
611 [["A"]]
612 }
613 ]
614 }
615 , "{A+$0+€0, $0 €+0} = True" ~: TestCase $
616 (@=?) True $
617 Calc.Balance.is_equilibrated $
618 Calc.Balance.Balance
619 { Calc.Balance.by_account =
620 Data.Map.fromList
621 [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
622 ]
623 , Calc.Balance.by_unit =
624 Data.Map.fromList $
625 Data.List.map Calc.Balance.assoc_by_amount_unit $
626 [ Calc.Balance.Sum_by_Unit
627 { Calc.Balance.amount = Amount.usd $ 0
628 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
629 [["A"]]
630 }
631 , Calc.Balance.Sum_by_Unit
632 { Calc.Balance.amount = Amount.eur $ 0
633 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
634 [["A"]]
635 }
636 ]
637 }
638 , "{A+$1, B-$1, $+0} = True" ~: TestCase $
639 (@=?) True $
640 Calc.Balance.is_equilibrated $
641 Calc.Balance.Balance
642 { Calc.Balance.by_account =
643 Data.Map.fromList
644 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
645 , (["B"], Amount.from_List [ Amount.usd $ -1 ])
646 ]
647 , Calc.Balance.by_unit =
648 Data.Map.fromList $
649 Data.List.map Calc.Balance.assoc_by_amount_unit $
650 [ Calc.Balance.Sum_by_Unit
651 { Calc.Balance.amount = Amount.usd $ 0
652 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
653 [["A"], ["B"]]
654 }
655 ]
656 }
657 , "{A+$1 B, $+1} = True" ~: TestCase $
658 (@=?) True $
659 Calc.Balance.is_equilibrated $
660 Calc.Balance.Balance
661 { Calc.Balance.by_account =
662 Data.Map.fromList
663 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
664 , (["B"], Amount.from_List [])
665 ]
666 , Calc.Balance.by_unit =
667 Data.Map.fromList $
668 Data.List.map Calc.Balance.assoc_by_amount_unit $
669 [ Calc.Balance.Sum_by_Unit
670 { Calc.Balance.amount = Amount.usd $ 1
671 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
672 [["A"]]
673 }
674 ]
675 }
676 , "{A+$1 B+€1, $+1 €+1} = True" ~: TestCase $
677 (@=?) True $
678 Calc.Balance.is_equilibrated $
679 Calc.Balance.Balance
680 { Calc.Balance.by_account =
681 Data.Map.fromList
682 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
683 , (["B"], Amount.from_List [ Amount.eur $ 1 ])
684 ]
685 , Calc.Balance.by_unit =
686 Data.Map.fromList $
687 Data.List.map Calc.Balance.assoc_by_amount_unit $
688 [ Calc.Balance.Sum_by_Unit
689 { Calc.Balance.amount = Amount.usd $ 1
690 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
691 [["A"]]
692 }
693 , Calc.Balance.Sum_by_Unit
694 { Calc.Balance.amount = Amount.eur $ 1
695 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
696 [["B"]]
697 }
698 ]
699 }
700 , "{A+$1 B-$1+€1, $+0 €+1} = True" ~: TestCase $
701 (@=?) True $
702 Calc.Balance.is_equilibrated $
703 Calc.Balance.Balance
704 { Calc.Balance.by_account =
705 Data.Map.fromList
706 [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
707 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
708 ]
709 , Calc.Balance.by_unit =
710 Data.Map.fromList $
711 Data.List.map Calc.Balance.assoc_by_amount_unit $
712 [ Calc.Balance.Sum_by_Unit
713 { Calc.Balance.amount = Amount.usd $ 0
714 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
715 [["A"], ["B"]]
716 }
717 , Calc.Balance.Sum_by_Unit
718 { Calc.Balance.amount = Amount.eur $ 1
719 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
720 [["B"]]
721 }
722 ]
723 }
724 , "{A+$1+€2+£3 B-$1-€2-£3, $+0 €+0 £+0} = True" ~: TestCase $
725 (@=?) True $
726 Calc.Balance.is_equilibrated $
727 Calc.Balance.Balance
728 { Calc.Balance.by_account =
729 Data.Map.fromList
730 [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ])
731 , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
732 ]
733 , Calc.Balance.by_unit =
734 Data.Map.fromList $
735 Data.List.map Calc.Balance.assoc_by_amount_unit $
736 [ Calc.Balance.Sum_by_Unit
737 { Calc.Balance.amount = Amount.usd $ 0
738 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
739 [["A"], ["B"]]
740 }
741 , Calc.Balance.Sum_by_Unit
742 { Calc.Balance.amount = Amount.eur $ 0
743 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
744 [["A"], ["B"]]
745 }
746 , Calc.Balance.Sum_by_Unit
747 { Calc.Balance.amount = Amount.gbp $ 0
748 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
749 [["A"], ["B"]]
750 }
751 ]
752 }
753 ]
754 ]
755 ]
756 , "Format" ~: TestList
757 [ "Ledger" ~: TestList
758 [ "Read" ~: TestList
759 [ "account_name" ~: TestList
760 [ "\"\" = Left" ~:
761 (Data.Either.rights $
762 [P.runParser
763 (Format.Ledger.Read.account_name <* P.eof)
764 () "" (""::Text)])
765 ~?=
766 []
767 , "\"A\" = Right \"A\"" ~:
768 (Data.Either.rights $
769 [P.runParser
770 (Format.Ledger.Read.account_name <* P.eof)
771 () "" ("A"::Text)])
772 ~?=
773 ["A"]
774 , "\"AA\" = Right \"AA\"" ~:
775 (Data.Either.rights $
776 [P.runParser
777 (Format.Ledger.Read.account_name <* P.eof)
778 () "" ("AA"::Text)])
779 ~?=
780 ["AA"]
781 , "\" \" = Left" ~:
782 (Data.Either.rights $
783 [P.runParser
784 (Format.Ledger.Read.account_name <* P.eof)
785 () "" (" "::Text)])
786 ~?=
787 []
788 , "\":\" = Left" ~:
789 (Data.Either.rights $
790 [P.runParser
791 (Format.Ledger.Read.account_name <* P.eof)
792 () "" (":"::Text)])
793 ~?=
794 []
795 , "\"A:\" = Left" ~:
796 (Data.Either.rights $
797 [P.runParser
798 (Format.Ledger.Read.account_name <* P.eof)
799 () "" ("A:"::Text)])
800 ~?=
801 []
802 , "\":A\" = Left" ~:
803 (Data.Either.rights $
804 [P.runParser
805 (Format.Ledger.Read.account_name <* P.eof)
806 () "" (":A"::Text)])
807 ~?=
808 []
809 , "\"A \" = Left" ~:
810 (Data.Either.rights $
811 [P.runParser
812 (Format.Ledger.Read.account_name <* P.eof)
813 () "" ("A "::Text)])
814 ~?=
815 []
816 , "\"A \" ^= Right" ~:
817 (Data.Either.rights $
818 [P.runParser
819 (Format.Ledger.Read.account_name)
820 () "" ("A "::Text)])
821 ~?=
822 ["A"]
823 , "\"A A\" = Right \"A A\"" ~:
824 (Data.Either.rights $
825 [P.runParser
826 (Format.Ledger.Read.account_name <* P.eof)
827 () "" ("A A"::Text)])
828 ~?=
829 ["A A"]
830 , "\"A \" = Left" ~:
831 (Data.Either.rights $
832 [P.runParser
833 (Format.Ledger.Read.account_name <* P.eof)
834 () "" ("A "::Text)])
835 ~?=
836 []
837 , "\"A \\n\" = Left" ~:
838 (Data.Either.rights $
839 [P.runParser
840 (Format.Ledger.Read.account_name <* P.eof)
841 () "" ("A \n"::Text)])
842 ~?=
843 []
844 , "\"(A)A\" = Right \"(A)A\"" ~:
845 (Data.Either.rights $
846 [P.runParser
847 (Format.Ledger.Read.account_name <* P.eof)
848 () "" ("(A)A"::Text)])
849 ~?=
850 ["(A)A"]
851 , "\"( )A\" = Right \"( )A\"" ~:
852 (Data.Either.rights $
853 [P.runParser
854 (Format.Ledger.Read.account_name <* P.eof)
855 () "" ("( )A"::Text)])
856 ~?=
857 ["( )A"]
858 , "\"(A) A\" = Right \"(A) A\"" ~:
859 (Data.Either.rights $
860 [P.runParser
861 (Format.Ledger.Read.account_name <* P.eof)
862 () "" ("(A) A"::Text)])
863 ~?=
864 ["(A) A"]
865 , "\"[ ]A\" = Right \"[ ]A\"" ~:
866 (Data.Either.rights $
867 [P.runParser
868 (Format.Ledger.Read.account_name <* P.eof)
869 () "" ("[ ]A"::Text)])
870 ~?=
871 ["[ ]A"]
872 , "\"(A) \" = Left" ~:
873 (Data.Either.rights $
874 [P.runParser
875 (Format.Ledger.Read.account_name <* P.eof)
876 () "" ("(A) "::Text)])
877 ~?=
878 []
879 , "\"(A)\" = Left" ~:
880 (Data.Either.rights $
881 [P.runParser
882 (Format.Ledger.Read.account_name <* P.eof)
883 () "" ("(A)"::Text)])
884 ~?=
885 []
886 , "\"[A]A\" = Right \"(A)A\"" ~:
887 (Data.Either.rights $
888 [P.runParser
889 (Format.Ledger.Read.account_name <* P.eof)
890 () "" ("[A]A"::Text)])
891 ~?=
892 ["[A]A"]
893 , "\"[A] A\" = Right \"[A] A\"" ~:
894 (Data.Either.rights $
895 [P.runParser
896 (Format.Ledger.Read.account_name <* P.eof)
897 () "" ("[A] A"::Text)])
898 ~?=
899 ["[A] A"]
900 , "\"[A] \" = Left" ~:
901 (Data.Either.rights $
902 [P.runParser
903 (Format.Ledger.Read.account_name <* P.eof)
904 () "" ("[A] "::Text)])
905 ~?=
906 []
907 , "\"[A]\" = Left" ~:
908 (Data.Either.rights $
909 [P.runParser
910 (Format.Ledger.Read.account_name <* P.eof)
911 () "" ("[A]"::Text)])
912 ~?=
913 []
914 ]
915 , "account" ~: TestList
916 [ "\"\" = Left" ~:
917 (Data.Either.rights $
918 [P.runParser
919 (Format.Ledger.Read.account <* P.eof)
920 () "" (""::Text)])
921 ~?=
922 []
923 , "\"A\" = Right [\"A\"]" ~:
924 (Data.Either.rights $
925 [P.runParser
926 (Format.Ledger.Read.account <* P.eof)
927 () "" ("A"::Text)])
928 ~?=
929 [["A"]]
930 , "\"A:\" = Left" ~:
931 (Data.Either.rights $
932 [P.runParser
933 (Format.Ledger.Read.account <* P.eof)
934 () "" ("A:"::Text)])
935 ~?=
936 []
937 , "\":A\" = Left" ~:
938 (Data.Either.rights $
939 [P.runParser
940 (Format.Ledger.Read.account <* P.eof)
941 () "" (":A"::Text)])
942 ~?=
943 []
944 , "\"A \" = Left" ~:
945 (Data.Either.rights $
946 [P.runParser
947 (Format.Ledger.Read.account <* P.eof)
948 () "" ("A "::Text)])
949 ~?=
950 []
951 , "\" A\" = Left" ~:
952 (Data.Either.rights $
953 [P.runParser
954 (Format.Ledger.Read.account <* P.eof)
955 () "" (" A"::Text)])
956 ~?=
957 []
958 , "\"A:B\" = Right [\"A\", \"B\"]" ~:
959 (Data.Either.rights $
960 [P.runParser
961 (Format.Ledger.Read.account <* P.eof)
962 () "" ("A:B"::Text)])
963 ~?=
964 [["A", "B"]]
965 , "\"A:B:C\" = Right [\"A\", \"B\", \"C\"]" ~:
966 (Data.Either.rights $
967 [P.runParser
968 (Format.Ledger.Read.account <* P.eof)
969 () "" ("A:B:C"::Text)])
970 ~?=
971 [["A", "B", "C"]]
972 , "\"Aa:Bbb:Cccc\" = Right [\"Aa\", \"Bbb\", \":Cccc\"]" ~:
973 (Data.Either.rights $
974 [P.runParser
975 (Format.Ledger.Read.account <* P.eof)
976 () "" ("Aa:Bbb:Cccc"::Text)])
977 ~?=
978 [["Aa", "Bbb", "Cccc"]]
979 , "\"A a : B b b : C c c c\" = Right [\"A a \", \" B b b \", \": C c c c\"]" ~:
980 (Data.Either.rights $
981 [P.runParser
982 (Format.Ledger.Read.account <* P.eof)
983 () "" ("A a : B b b : C c c c"::Text)])
984 ~?=
985 [["A a ", " B b b ", " C c c c"]]
986 , "\"A: :C\" = Right [\"A\", \" \", \"C\"]" ~:
987 (Data.Either.rights $
988 [P.runParser
989 (Format.Ledger.Read.account <* P.eof)
990 () "" ("A: :C"::Text)])
991 ~?=
992 [["A", " ", "C"]]
993 , "\"A::C\" = Left" ~:
994 (Data.Either.rights $
995 [P.runParser
996 (Format.Ledger.Read.account <* P.eof)
997 () "" ("A::C"::Text)])
998 ~?=
999 []
1000 ]
1001 , "amount" ~: TestList
1002 [ "\"\" = Left" ~:
1003 (Data.Either.rights $
1004 [P.runParser
1005 (Format.Ledger.Read.amount <* P.eof)
1006 () "" (""::Text)])
1007 ~?=
1008 []
1009 , "\"0\" = Right 0" ~:
1010 (Data.Either.rights $
1011 [P.runParser
1012 (Format.Ledger.Read.amount <* P.eof)
1013 () "" ("0"::Text)])
1014 ~?=
1015 [Amount.nil
1016 { Amount.quantity = Decimal 0 0
1017 }]
1018 , "\"00\" = Right 0" ~:
1019 (Data.Either.rights $
1020 [P.runParser
1021 (Format.Ledger.Read.amount <* P.eof)
1022 () "" ("00"::Text)])
1023 ~?=
1024 [Amount.nil
1025 { Amount.quantity = Decimal 0 0
1026 }]
1027 , "\"0.\" = Right 0." ~:
1028 (Data.Either.rights $
1029 [P.runParser
1030 (Format.Ledger.Read.amount <* P.eof)
1031 () "" ("0."::Text)])
1032 ~?=
1033 [Amount.nil
1034 { Amount.quantity = Decimal 0 0
1035 , Amount.style =
1036 Amount.Style.nil
1037 { Amount.Style.fractioning = Just '.'
1038 }
1039 }]
1040 , "\".0\" = Right 0.0" ~:
1041 (Data.Either.rights $
1042 [P.runParser
1043 (Format.Ledger.Read.amount <* P.eof)
1044 () "" (".0"::Text)])
1045 ~?=
1046 [Amount.nil
1047 { Amount.quantity = Decimal 0 0
1048 , Amount.style =
1049 Amount.Style.nil
1050 { Amount.Style.fractioning = Just '.'
1051 , Amount.Style.precision = 1
1052 }
1053 }]
1054 , "\"0,\" = Right 0," ~:
1055 (Data.Either.rights $
1056 [P.runParser
1057 (Format.Ledger.Read.amount <* P.eof)
1058 () "" ("0,"::Text)])
1059 ~?=
1060 [Amount.nil
1061 { Amount.quantity = Decimal 0 0
1062 , Amount.style =
1063 Amount.Style.nil
1064 { Amount.Style.fractioning = Just ','
1065 }
1066 }]
1067 , "\",0\" = Right 0,0" ~:
1068 (Data.Either.rights $
1069 [P.runParser
1070 (Format.Ledger.Read.amount <* P.eof)
1071 () "" (",0"::Text)])
1072 ~?=
1073 [Amount.nil
1074 { Amount.quantity = Decimal 0 0
1075 , Amount.style =
1076 Amount.Style.nil
1077 { Amount.Style.fractioning = Just ','
1078 , Amount.Style.precision = 1
1079 }
1080 }]
1081 , "\"0_\" = Left" ~:
1082 (Data.Either.rights $
1083 [P.runParser
1084 (Format.Ledger.Read.amount <* P.eof)
1085 () "" ("0_"::Text)])
1086 ~?=
1087 []
1088 , "\"_0\" = Left" ~:
1089 (Data.Either.rights $
1090 [P.runParser
1091 (Format.Ledger.Read.amount <* P.eof)
1092 () "" ("_0"::Text)])
1093 ~?=
1094 []
1095 , "\"0.0\" = Right 0.0" ~:
1096 (Data.Either.rights $
1097 [P.runParser
1098 (Format.Ledger.Read.amount <* P.eof)
1099 () "" ("0.0"::Text)])
1100 ~?=
1101 [Amount.nil
1102 { Amount.quantity = Decimal 0 0
1103 , Amount.style =
1104 Amount.Style.nil
1105 { Amount.Style.fractioning = Just '.'
1106 , Amount.Style.precision = 1
1107 }
1108 }]
1109 , "\"00.00\" = Right 0.00" ~:
1110 (Data.Either.rights $
1111 [P.runParser
1112 (Format.Ledger.Read.amount <* P.eof)
1113 () "" ("00.00"::Text)])
1114 ~?=
1115 [Amount.nil
1116 { Amount.quantity = Decimal 0 0
1117 , Amount.style =
1118 Amount.Style.nil
1119 { Amount.Style.fractioning = Just '.'
1120 , Amount.Style.precision = 2
1121 }
1122 }]
1123 , "\"0,0\" = Right 0,0" ~:
1124 (Data.Either.rights $
1125 [P.runParser
1126 (Format.Ledger.Read.amount <* P.eof)
1127 () "" ("0,0"::Text)])
1128 ~?=
1129 [Amount.nil
1130 { Amount.quantity = Decimal 0 0
1131 , Amount.style =
1132 Amount.Style.nil
1133 { Amount.Style.fractioning = Just ','
1134 , Amount.Style.precision = 1
1135 }
1136 }]
1137 , "\"00,00\" = Right 0,00" ~:
1138 (Data.Either.rights $
1139 [P.runParser
1140 (Format.Ledger.Read.amount <* P.eof)
1141 () "" ("00,00"::Text)])
1142 ~?=
1143 [Amount.nil
1144 { Amount.quantity = Decimal 0 0
1145 , Amount.style =
1146 Amount.Style.nil
1147 { Amount.Style.fractioning = Just ','
1148 , Amount.Style.precision = 2
1149 }
1150 }]
1151 , "\"0_0\" = Right 0" ~:
1152 (Data.Either.rights $
1153 [P.runParser
1154 (Format.Ledger.Read.amount <* P.eof)
1155 () "" ("0_0"::Text)])
1156 ~?=
1157 [Amount.nil
1158 { Amount.quantity = Decimal 0 0
1159 , Amount.style =
1160 Amount.Style.nil
1161 { Amount.Style.fractioning = Nothing
1162 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1163 , Amount.Style.precision = 0
1164 }
1165 }]
1166 , "\"00_00\" = Right 0" ~:
1167 (Data.Either.rights $
1168 [P.runParser
1169 (Format.Ledger.Read.amount <* P.eof)
1170 () "" ("00_00"::Text)])
1171 ~?=
1172 [Amount.nil
1173 { Amount.quantity = Decimal 0 0
1174 , Amount.style =
1175 Amount.Style.nil
1176 { Amount.Style.fractioning = Nothing
1177 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1178 , Amount.Style.precision = 0
1179 }
1180 }]
1181 , "\"0,000.00\" = Right 0,000.00" ~:
1182 (Data.Either.rights $
1183 [P.runParser
1184 (Format.Ledger.Read.amount <* P.eof)
1185 () "" ("0,000.00"::Text)])
1186 ~?=
1187 [Amount.nil
1188 { Amount.quantity = Decimal 0 0
1189 , Amount.style =
1190 Amount.Style.nil
1191 { Amount.Style.fractioning = Just '.'
1192 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1193 , Amount.Style.precision = 2
1194 }
1195 }]
1196 , "\"0.000,00\" = Right 0.000,00" ~:
1197 (Data.Either.rights $
1198 [P.runParser
1199 (Format.Ledger.Read.amount)
1200 () "" ("0.000,00"::Text)])
1201 ~?=
1202 [Amount.nil
1203 { Amount.quantity = Decimal 0 0
1204 , Amount.style =
1205 Amount.Style.nil
1206 { Amount.Style.fractioning = Just ','
1207 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1208 , Amount.Style.precision = 2
1209 }
1210 }]
1211 , "\"1,000.00\" = Right 1,000.00" ~:
1212 (Data.Either.rights $
1213 [P.runParser
1214 (Format.Ledger.Read.amount <* P.eof)
1215 () "" ("1,000.00"::Text)])
1216 ~?=
1217 [Amount.nil
1218 { Amount.quantity = Decimal 0 1000
1219 , Amount.style =
1220 Amount.Style.nil
1221 { Amount.Style.fractioning = Just '.'
1222 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
1223 , Amount.Style.precision = 2
1224 }
1225 }]
1226 , "\"1.000,00\" = Right 1.000,00" ~:
1227 (Data.Either.rights $
1228 [P.runParser
1229 (Format.Ledger.Read.amount)
1230 () "" ("1.000,00"::Text)])
1231 ~?=
1232 [Amount.nil
1233 { Amount.quantity = Decimal 0 1000
1234 , Amount.style =
1235 Amount.Style.nil
1236 { Amount.Style.fractioning = Just ','
1237 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1238 , Amount.Style.precision = 2
1239 }
1240 }]
1241 , "\"1,000.00.\" = Left" ~:
1242 (Data.Either.rights $
1243 [P.runParser
1244 (Format.Ledger.Read.amount)
1245 () "" ("1,000.00."::Text)])
1246 ~?=
1247 []
1248 , "\"1.000,00,\" = Left" ~:
1249 (Data.Either.rights $
1250 [P.runParser
1251 (Format.Ledger.Read.amount)
1252 () "" ("1.000,00,"::Text)])
1253 ~?=
1254 []
1255 , "\"1,000.00_\" = Left" ~:
1256 (Data.Either.rights $
1257 [P.runParser
1258 (Format.Ledger.Read.amount)
1259 () "" ("1,000.00_"::Text)])
1260 ~?=
1261 []
1262 , "\"12\" = Right 12" ~:
1263 (Data.Either.rights $
1264 [P.runParser
1265 (Format.Ledger.Read.amount <* P.eof)
1266 () "" ("123"::Text)])
1267 ~?=
1268 [Amount.nil
1269 { Amount.quantity = Decimal 0 123
1270 }]
1271 , "\"1.2\" = Right 1.2" ~:
1272 (Data.Either.rights $
1273 [P.runParser
1274 (Format.Ledger.Read.amount <* P.eof)
1275 () "" ("1.2"::Text)])
1276 ~?=
1277 [Amount.nil
1278 { Amount.quantity = Decimal 1 12
1279 , Amount.style =
1280 Amount.Style.nil
1281 { Amount.Style.fractioning = Just '.'
1282 , Amount.Style.precision = 1
1283 }
1284 }]
1285 , "\"1,2\" = Right 1,2" ~:
1286 (Data.Either.rights $
1287 [P.runParser
1288 (Format.Ledger.Read.amount <* P.eof)
1289 () "" ("1,2"::Text)])
1290 ~?=
1291 [Amount.nil
1292 { Amount.quantity = Decimal 1 12
1293 , Amount.style =
1294 Amount.Style.nil
1295 { Amount.Style.fractioning = Just ','
1296 , Amount.Style.precision = 1
1297 }
1298 }]
1299 , "\"12.23\" = Right 12.23" ~:
1300 (Data.Either.rights $
1301 [P.runParser
1302 (Format.Ledger.Read.amount <* P.eof)
1303 () "" ("12.34"::Text)])
1304 ~?=
1305 [Amount.nil
1306 { Amount.quantity = Decimal 2 1234
1307 , Amount.style =
1308 Amount.Style.nil
1309 { Amount.Style.fractioning = Just '.'
1310 , Amount.Style.precision = 2
1311 }
1312 }]
1313 , "\"12,23\" = Right 12,23" ~:
1314 (Data.Either.rights $
1315 [P.runParser
1316 (Format.Ledger.Read.amount <* P.eof)
1317 () "" ("12,34"::Text)])
1318 ~?=
1319 [Amount.nil
1320 { Amount.quantity = Decimal 2 1234
1321 , Amount.style =
1322 Amount.Style.nil
1323 { Amount.Style.fractioning = Just ','
1324 , Amount.Style.precision = 2
1325 }
1326 }]
1327 , "\"1_2\" = Right 1_2" ~:
1328 (Data.Either.rights $
1329 [P.runParser
1330 (Format.Ledger.Read.amount <* P.eof)
1331 () "" ("1_2"::Text)])
1332 ~?=
1333 [Amount.nil
1334 { Amount.quantity = Decimal 0 12
1335 , Amount.style =
1336 Amount.Style.nil
1337 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
1338 , Amount.Style.precision = 0
1339 }
1340 }]
1341 , "\"1_23\" = Right 1_23" ~:
1342 (Data.Either.rights $
1343 [P.runParser
1344 (Format.Ledger.Read.amount <* P.eof)
1345 () "" ("1_23"::Text)])
1346 ~?=
1347 [Amount.nil
1348 { Amount.quantity = Decimal 0 123
1349 , Amount.style =
1350 Amount.Style.nil
1351 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
1352 , Amount.Style.precision = 0
1353 }
1354 }]
1355 , "\"1_23_456\" = Right 1_23_456" ~:
1356 (Data.Either.rights $
1357 [P.runParser
1358 (Format.Ledger.Read.amount <* P.eof)
1359 () "" ("1_23_456"::Text)])
1360 ~?=
1361 [Amount.nil
1362 { Amount.quantity = Decimal 0 123456
1363 , Amount.style =
1364 Amount.Style.nil
1365 { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1366 , Amount.Style.precision = 0
1367 }
1368 }]
1369 , "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
1370 (Data.Either.rights $
1371 [P.runParser
1372 (Format.Ledger.Read.amount <* P.eof)
1373 () "" ("1_23_456.7890_12345_678901"::Text)])
1374 ~?=
1375 [Amount.nil
1376 { Amount.quantity = Decimal 15 123456789012345678901
1377 , Amount.style =
1378 Amount.Style.nil
1379 { Amount.Style.fractioning = Just '.'
1380 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
1381 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1382 , Amount.Style.precision = 15
1383 }
1384 }]
1385 , "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
1386 (Data.Either.rights $
1387 [P.runParser
1388 (Format.Ledger.Read.amount <* P.eof)
1389 () "" ("123456_78901_2345.678_90_1"::Text)])
1390 ~?=
1391 [Amount.nil
1392 { Amount.quantity = Decimal 6 123456789012345678901
1393 , Amount.style =
1394 Amount.Style.nil
1395 { Amount.Style.fractioning = Just '.'
1396 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
1397 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
1398 , Amount.Style.precision = 6
1399 }
1400 }]
1401 , "\"$1\" = Right $1" ~:
1402 (Data.Either.rights $
1403 [P.runParser
1404 (Format.Ledger.Read.amount <* P.eof)
1405 () "" ("$1"::Text)])
1406 ~?=
1407 [Amount.nil
1408 { Amount.quantity = Decimal 0 1
1409 , Amount.style =
1410 Amount.Style.nil
1411 { Amount.Style.fractioning = Nothing
1412 , Amount.Style.grouping_integral = Nothing
1413 , Amount.Style.grouping_fractional = Nothing
1414 , Amount.Style.precision = 0
1415 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1416 , Amount.Style.unit_spaced = Just False
1417 }
1418 , Amount.unit = "$"
1419 }]
1420 , "\"1$\" = Right 1$" ~:
1421 (Data.Either.rights $
1422 [P.runParser
1423 (Format.Ledger.Read.amount <* P.eof)
1424 () "" ("1$"::Text)])
1425 ~?=
1426 [Amount.nil
1427 { Amount.quantity = Decimal 0 1
1428 , Amount.style =
1429 Amount.Style.nil
1430 { Amount.Style.fractioning = Nothing
1431 , Amount.Style.grouping_integral = Nothing
1432 , Amount.Style.grouping_fractional = Nothing
1433 , Amount.Style.precision = 0
1434 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1435 , Amount.Style.unit_spaced = Just False
1436 }
1437 , Amount.unit = "$"
1438 }]
1439 , "\"$ 1\" = Right $ 1" ~:
1440 (Data.Either.rights $
1441 [P.runParser
1442 (Format.Ledger.Read.amount <* P.eof)
1443 () "" ("$ 1"::Text)])
1444 ~?=
1445 [Amount.nil
1446 { Amount.quantity = Decimal 0 1
1447 , Amount.style =
1448 Amount.Style.nil
1449 { Amount.Style.fractioning = Nothing
1450 , Amount.Style.grouping_integral = Nothing
1451 , Amount.Style.grouping_fractional = Nothing
1452 , Amount.Style.precision = 0
1453 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1454 , Amount.Style.unit_spaced = Just True
1455 }
1456 , Amount.unit = "$"
1457 }]
1458 , "\"1 $\" = Right 1 $" ~:
1459 (Data.Either.rights $
1460 [P.runParser
1461 (Format.Ledger.Read.amount <* P.eof)
1462 () "" ("1 $"::Text)])
1463 ~?=
1464 [Amount.nil
1465 { Amount.quantity = Decimal 0 1
1466 , Amount.style =
1467 Amount.Style.nil
1468 { Amount.Style.fractioning = Nothing
1469 , Amount.Style.grouping_integral = Nothing
1470 , Amount.Style.grouping_fractional = Nothing
1471 , Amount.Style.precision = 0
1472 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1473 , Amount.Style.unit_spaced = Just True
1474 }
1475 , Amount.unit = "$"
1476 }]
1477 , "\"-$1\" = Right $-1" ~:
1478 (Data.Either.rights $
1479 [P.runParser
1480 (Format.Ledger.Read.amount <* P.eof)
1481 () "" ("-$1"::Text)])
1482 ~?=
1483 [Amount.nil
1484 { Amount.quantity = Decimal 0 (-1)
1485 , Amount.style =
1486 Amount.Style.nil
1487 { Amount.Style.fractioning = Nothing
1488 , Amount.Style.grouping_integral = Nothing
1489 , Amount.Style.grouping_fractional = Nothing
1490 , Amount.Style.precision = 0
1491 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1492 , Amount.Style.unit_spaced = Just False
1493 }
1494 , Amount.unit = "$"
1495 }]
1496 , "\"\\\"4 2\\\"1\" = Right \\\"4 2\\\"1" ~:
1497 (Data.Either.rights $
1498 [P.runParser
1499 (Format.Ledger.Read.amount <* P.eof)
1500 () "" ("\"4 2\"1"::Text)])
1501 ~?=
1502 [Amount.nil
1503 { Amount.quantity = Decimal 0 1
1504 , Amount.style =
1505 Amount.Style.nil
1506 { Amount.Style.fractioning = Nothing
1507 , Amount.Style.grouping_integral = Nothing
1508 , Amount.Style.grouping_fractional = Nothing
1509 , Amount.Style.precision = 0
1510 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1511 , Amount.Style.unit_spaced = Just False
1512 }
1513 , Amount.unit = "4 2"
1514 }]
1515 , "\"1\\\"4 2\\\"\" = Right 1\\\"4 2\\\"" ~:
1516 (Data.Either.rights $
1517 [P.runParser
1518 (Format.Ledger.Read.amount <* P.eof)
1519 () "" ("1\"4 2\""::Text)])
1520 ~?=
1521 [Amount.nil
1522 { Amount.quantity = Decimal 0 1
1523 , Amount.style =
1524 Amount.Style.nil
1525 { Amount.Style.fractioning = Nothing
1526 , Amount.Style.grouping_integral = Nothing
1527 , Amount.Style.grouping_fractional = Nothing
1528 , Amount.Style.precision = 0
1529 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1530 , Amount.Style.unit_spaced = Just False
1531 }
1532 , Amount.unit = "4 2"
1533 }]
1534 , "\"$1.000,00\" = Right $1.000,00" ~:
1535 (Data.Either.rights $
1536 [P.runParser
1537 (Format.Ledger.Read.amount <* P.eof)
1538 () "" ("$1.000,00"::Text)])
1539 ~?=
1540 [Amount.nil
1541 { Amount.quantity = Decimal 0 1000
1542 , Amount.style =
1543 Amount.Style.nil
1544 { Amount.Style.fractioning = Just ','
1545 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1546 , Amount.Style.grouping_fractional = Nothing
1547 , Amount.Style.precision = 2
1548 , Amount.Style.unit_side = Just Amount.Style.Side_Left
1549 , Amount.Style.unit_spaced = Just False
1550 }
1551 , Amount.unit = "$"
1552 }]
1553 , "\"1.000,00$\" = Right 1.000,00$" ~:
1554 (Data.Either.rights $
1555 [P.runParser
1556 (Format.Ledger.Read.amount <* P.eof)
1557 () "" ("1.000,00$"::Text)])
1558 ~?=
1559 [Amount.nil
1560 { Amount.quantity = Decimal 0 1000
1561 , Amount.style =
1562 Amount.Style.nil
1563 { Amount.Style.fractioning = Just ','
1564 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
1565 , Amount.Style.grouping_fractional = Nothing
1566 , Amount.Style.precision = 2
1567 , Amount.Style.unit_side = Just Amount.Style.Side_Right
1568 , Amount.Style.unit_spaced = Just False
1569 }
1570 , Amount.unit = "$"
1571 }]
1572 ]
1573 , "comment" ~: TestList
1574 [ "; some comment = Right \" some comment\"" ~:
1575 (Data.Either.rights $
1576 [P.runParser
1577 (Format.Ledger.Read.comment <* P.eof)
1578 () "" ("; some comment"::Text)])
1579 ~?=
1580 [ " some comment" ]
1581 , "; some comment \\n = Right \" some comment \"" ~:
1582 (Data.Either.rights $
1583 [P.runParser
1584 (Format.Ledger.Read.comment <* P.newline <* P.eof)
1585 () "" ("; some comment \n"::Text)])
1586 ~?=
1587 [ " some comment " ]
1588 , "; some comment \\r\\n = Right \" some comment \"" ~:
1589 (Data.Either.rights $
1590 [P.runParser
1591 (Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
1592 () "" ("; some comment \r\n"::Text)])
1593 ~?=
1594 [ " some comment " ]
1595 ]
1596 , "comments" ~: TestList
1597 [ "; some comment\\n ; some other comment = Right [\" some comment\", \" some other comment\"]" ~:
1598 (Data.Either.rights $
1599 [P.runParser
1600 (Format.Ledger.Read.comments <* P.eof)
1601 () "" ("; some comment\n ; some other comment"::Text)])
1602 ~?=
1603 [ [" some comment", " some other comment"] ]
1604 , "; some comment \\n = Right \" some comment \"" ~:
1605 (Data.Either.rights $
1606 [P.runParser
1607 (Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
1608 () "" ("; some comment \n"::Text)])
1609 ~?=
1610 [ [" some comment "] ]
1611 ]
1612 , "date" ~: TestList
1613 [ "2000/01/01 = Right 2000/01/01" ~:
1614 (Data.Either.rights $
1615 [P.runParser
1616 (Format.Ledger.Read.date Nothing <* P.eof)
1617 () "" ("2000/01/01"::Text)])
1618 ~?=
1619 [ Time.ZonedTime
1620 (Time.LocalTime
1621 (Time.fromGregorian 2000 01 01)
1622 (Time.TimeOfDay 0 0 0))
1623 (Time.utc)]
1624 , "2000/01/01 some text = Right 2000/01/01" ~:
1625 (Data.Either.rights $
1626 [P.runParser
1627 (Format.Ledger.Read.date Nothing)
1628 () "" ("2000/01/01 some text"::Text)])
1629 ~?=
1630 [ Time.ZonedTime
1631 (Time.LocalTime
1632 (Time.fromGregorian 2000 01 01)
1633 (Time.TimeOfDay 0 0 0))
1634 (Time.utc)]
1635 , "2000/01/01 12:34 = Right 2000/01/01 12:34" ~:
1636 (Data.Either.rights $
1637 [P.runParser
1638 (Format.Ledger.Read.date Nothing <* P.eof)
1639 () "" ("2000/01/01 12:34"::Text)])
1640 ~?=
1641 [ Time.ZonedTime
1642 (Time.LocalTime
1643 (Time.fromGregorian 2000 01 01)
1644 (Time.TimeOfDay 12 34 0))
1645 (Time.utc)]
1646 , "2000/01/01 12:34:56 = Right 2000/01/01 12:34:56" ~:
1647 (Data.Either.rights $
1648 [P.runParser
1649 (Format.Ledger.Read.date Nothing <* P.eof)
1650 () "" ("2000/01/01 12:34:56"::Text)])
1651 ~?=
1652 [ Time.ZonedTime
1653 (Time.LocalTime
1654 (Time.fromGregorian 2000 01 01)
1655 (Time.TimeOfDay 12 34 56))
1656 (Time.utc)]
1657 , "2000/01/01 12:34 CET = Right 2000/01/01 12:34 CET" ~:
1658 (Data.Either.rights $
1659 [P.runParser
1660 (Format.Ledger.Read.date Nothing <* P.eof)
1661 () "" ("2000/01/01 12:34 CET"::Text)])
1662 ~?=
1663 [ Time.ZonedTime
1664 (Time.LocalTime
1665 (Time.fromGregorian 2000 01 01)
1666 (Time.TimeOfDay 12 34 0))
1667 (Time.TimeZone 60 True "CET")]
1668 , "2000/01/01 12:34 +0130 = Right 2000/01/01 12:34 +0130" ~:
1669 (Data.Either.rights $
1670 [P.runParser
1671 (Format.Ledger.Read.date Nothing <* P.eof)
1672 () "" ("2000/01/01 12:34 +0130"::Text)])
1673 ~?=
1674 [ Time.ZonedTime
1675 (Time.LocalTime
1676 (Time.fromGregorian 2000 01 01)
1677 (Time.TimeOfDay 12 34 0))
1678 (Time.TimeZone 90 False "+0130")]
1679 , "2000/01/01 12:34:56 CET = Right 2000/01/01 12:34:56 CET" ~:
1680 (Data.Either.rights $
1681 [P.runParser
1682 (Format.Ledger.Read.date Nothing <* P.eof)
1683 () "" ("2000/01/01 12:34:56 CET"::Text)])
1684 ~?=
1685 [ Time.ZonedTime
1686 (Time.LocalTime
1687 (Time.fromGregorian 2000 01 01)
1688 (Time.TimeOfDay 12 34 56))
1689 (Time.TimeZone 60 True "CET")]
1690 , "2001/02/29 = Left" ~:
1691 (Data.Either.rights $
1692 [P.runParser
1693 (Format.Ledger.Read.date Nothing <* P.eof)
1694 () "" ("2001/02/29"::Text)])
1695 ~?=
1696 []
1697 , "01/01 = Right default_year/01/01" ~:
1698 (Data.Either.rights $
1699 [P.runParser
1700 (Format.Ledger.Read.date (Just 2000) <* P.eof)
1701 () "" ("01/01"::Text)])
1702 ~?=
1703 [ Time.ZonedTime
1704 (Time.LocalTime
1705 (Time.fromGregorian 2000 01 01)
1706 (Time.TimeOfDay 0 0 0))
1707 (Time.utc)]
1708 ]
1709 , "tag" ~: TestList
1710 [ "Name: = Right Name:" ~:
1711 (Data.Either.rights $
1712 [P.runParser
1713 (Format.Ledger.Read.tag <* P.eof)
1714 () "" ("Name:"::Text)])
1715 ~?=
1716 [("Name", "")]
1717 , "Name:Value = Right Name:Value" ~:
1718 (Data.Either.rights $
1719 [P.runParser
1720 (Format.Ledger.Read.tag <* P.eof)
1721 () "" ("Name:Value"::Text)])
1722 ~?=
1723 [("Name", "Value")]
1724 , "Name:Val ue = Right Name:Val ue" ~:
1725 (Data.Either.rights $
1726 [P.runParser
1727 (Format.Ledger.Read.tag <* P.eof)
1728 () "" ("Name:Val ue"::Text)])
1729 ~?=
1730 [("Name", "Val ue")]
1731 ]
1732 , "tags" ~: TestList
1733 [ "Name: = Right Name:" ~:
1734 (Data.Either.rights $
1735 [P.runParser
1736 (Format.Ledger.Read.tags <* P.eof)
1737 () "" ("Name:"::Text)])
1738 ~?=
1739 [Data.Map.fromList
1740 [ ("Name", [""])
1741 ]
1742 ]
1743 , "Name:, = Right Name:" ~:
1744 (Data.Either.rights $
1745 [P.runParser
1746 (Format.Ledger.Read.tags <* P.char ',' <* P.eof)
1747 () "" ("Name:,"::Text)])
1748 ~?=
1749 [Data.Map.fromList
1750 [ ("Name", [""])
1751 ]
1752 ]
1753 , "Name:,Name: = Right Name:,Name:" ~:
1754 (Data.Either.rights $
1755 [P.runParser
1756 (Format.Ledger.Read.tags <* P.eof)
1757 () "" ("Name:,Name:"::Text)])
1758 ~?=
1759 [Data.Map.fromList
1760 [ ("Name", ["", ""])
1761 ]
1762 ]
1763 , "Name:,Name2: = Right Name:,Name2:" ~:
1764 (Data.Either.rights $
1765 [P.runParser
1766 (Format.Ledger.Read.tags <* P.eof)
1767 () "" ("Name:,Name2:"::Text)])
1768 ~?=
1769 [Data.Map.fromList
1770 [ ("Name", [""])
1771 , ("Name2", [""])
1772 ]
1773 ]
1774 , "Name: , Name2: = Right Name: ,Name2:" ~:
1775 (Data.Either.rights $
1776 [P.runParser
1777 (Format.Ledger.Read.tags <* P.eof)
1778 () "" ("Name: , Name2:"::Text)])
1779 ~?=
1780 [Data.Map.fromList
1781 [ ("Name", [" "])
1782 , ("Name2", [""])
1783 ]
1784 ]
1785 , "Name:,Name2:,Name3: = Right Name:,Name2:,Name3:" ~:
1786 (Data.Either.rights $
1787 [P.runParser
1788 (Format.Ledger.Read.tags <* P.eof)
1789 () "" ("Name:,Name2:,Name3:"::Text)])
1790 ~?=
1791 [Data.Map.fromList
1792 [ ("Name", [""])
1793 , ("Name2", [""])
1794 , ("Name3", [""])
1795 ]
1796 ]
1797 , "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" ~:
1798 (Data.Either.rights $
1799 [P.runParser
1800 (Format.Ledger.Read.tags <* P.eof)
1801 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
1802 ~?=
1803 [Data.Map.fromList
1804 [ ("Name", ["Val ue"])
1805 , ("Name2", ["V a l u e"])
1806 , ("Name3", ["V al ue"])
1807 ]
1808 ]
1809 ]
1810 , "posting" ~: TestList
1811 [ " A:B:C = Right A:B:C" ~:
1812 (Data.Either.rights $
1813 [P.runParser
1814 (Format.Ledger.Read.posting <* P.eof)
1815 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
1816 ~?=
1817 [ ( Posting.nil
1818 { Posting.account = ["A","B","C"]
1819 , Posting.sourcepos = P.newPos "" 1 1
1820 }
1821 , Posting.Type_Regular
1822 )
1823 ]
1824 , " !A:B:C = Right !A:B:C" ~:
1825 (Data.List.map fst $
1826 Data.Either.rights $
1827 [P.runParser
1828 (Format.Ledger.Read.posting <* P.eof)
1829 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
1830 ~?=
1831 [ Posting.nil
1832 { Posting.account = ["A","B","C"]
1833 , Posting.sourcepos = P.newPos "" 1 1
1834 , Posting.status = True
1835 }
1836 ]
1837 , " *A:B:C = Right *A:B:C" ~:
1838 (Data.List.map fst $
1839 Data.Either.rights $
1840 [P.runParser
1841 (Format.Ledger.Read.posting <* P.eof)
1842 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
1843 ~?=
1844 [ Posting.nil
1845 { Posting.account = ["A","B","C"]
1846 , Posting.amounts = Data.Map.fromList []
1847 , Posting.comments = []
1848 , Posting.dates = []
1849 , Posting.status = True
1850 , Posting.sourcepos = P.newPos "" 1 1
1851 , Posting.tags = Data.Map.fromList []
1852 }
1853 ]
1854 , " A:B:C $1 = Right A:B:C $1" ~:
1855 (Data.List.map fst $
1856 Data.Either.rights $
1857 [P.runParser
1858 (Format.Ledger.Read.posting <* P.eof)
1859 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1860 ~?=
1861 [ Posting.nil
1862 { Posting.account = ["A","B","C $1"]
1863 , Posting.sourcepos = P.newPos "" 1 1
1864 }
1865 ]
1866 , " A:B:C $1 = Right A:B:C $1" ~:
1867 (Data.List.map fst $
1868 Data.Either.rights $
1869 [P.runParser
1870 (Format.Ledger.Read.posting <* P.eof)
1871 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1872 ~?=
1873 [ Posting.nil
1874 { Posting.account = ["A","B","C"]
1875 , Posting.amounts = Data.Map.fromList
1876 [ ("$", Amount.nil
1877 { Amount.quantity = 1
1878 , Amount.style = Amount.Style.nil
1879 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1880 , Amount.Style.unit_spaced = Just False
1881 }
1882 , Amount.unit = "$"
1883 })
1884 ]
1885 , Posting.sourcepos = P.newPos "" 1 1
1886 }
1887 ]
1888 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
1889 (Data.List.map fst $
1890 Data.Either.rights $
1891 [P.runParser
1892 (Format.Ledger.Read.posting <* P.eof)
1893 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
1894 ~?=
1895 [ Posting.nil
1896 { Posting.account = ["A","B","C"]
1897 , Posting.amounts = Data.Map.fromList
1898 [ ("$", Amount.nil
1899 { Amount.quantity = 1
1900 , Amount.style = Amount.Style.nil
1901 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1902 , Amount.Style.unit_spaced = Just False
1903 }
1904 , Amount.unit = "$"
1905 })
1906 , ("€", Amount.nil
1907 { Amount.quantity = 1
1908 , Amount.style = Amount.Style.nil
1909 { Amount.Style.unit_side = Just Amount.Style.Side_Right
1910 , Amount.Style.unit_spaced = Just False
1911 }
1912 , Amount.unit = "€"
1913 })
1914 ]
1915 , Posting.sourcepos = P.newPos "" 1 1
1916 }
1917 ]
1918 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
1919 (Data.List.map fst $
1920 Data.Either.rights $
1921 [P.runParser
1922 (Format.Ledger.Read.posting <* P.eof)
1923 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
1924 ~?=
1925 [ Posting.nil
1926 { Posting.account = ["A","B","C"]
1927 , Posting.amounts = Data.Map.fromList
1928 [ ("$", Amount.nil
1929 { Amount.quantity = 2
1930 , Amount.style = Amount.Style.nil
1931 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1932 , Amount.Style.unit_spaced = Just False
1933 }
1934 , Amount.unit = "$"
1935 })
1936 ]
1937 , Posting.sourcepos = P.newPos "" 1 1
1938 }
1939 ]
1940 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
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 + 1$ + 1$"::Text)])
1946 ~?=
1947 [ Posting.nil
1948 { Posting.account = ["A","B","C"]
1949 , Posting.amounts = Data.Map.fromList
1950 [ ("$", Amount.nil
1951 { Amount.quantity = 3
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 ; some comment = Right A:B:C ; some comment" ~:
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 ; some comment"::Text)])
1968 ~?=
1969 [ Posting.nil
1970 { Posting.account = ["A","B","C"]
1971 , Posting.amounts = Data.Map.fromList []
1972 , Posting.comments = [" some comment"]
1973 , Posting.sourcepos = P.newPos "" 1 1
1974 }
1975 ]
1976 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
1977 (Data.List.map fst $
1978 Data.Either.rights $
1979 [P.runParser
1980 (Format.Ledger.Read.posting <* P.eof)
1981 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
1982 ~?=
1983 [ Posting.nil
1984 { Posting.account = ["A","B","C"]
1985 , Posting.amounts = Data.Map.fromList []
1986 , Posting.comments = [" some comment", " some other comment"]
1987 , Posting.sourcepos = P.newPos "" 1 1
1988 }
1989 ]
1990 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
1991 (Data.List.map fst $
1992 Data.Either.rights $
1993 [P.runParser
1994 (Format.Ledger.Read.posting)
1995 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
1996 ~?=
1997 [ Posting.nil
1998 { Posting.account = ["A","B","C"]
1999 , Posting.amounts = Data.Map.fromList
2000 [ ("$", Amount.nil
2001 { Amount.quantity = 1
2002 , Amount.style = Amount.Style.nil
2003 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2004 , Amount.Style.unit_spaced = Just False
2005 }
2006 , Amount.unit = "$"
2007 })
2008 ]
2009 , Posting.comments = [" some comment"]
2010 , Posting.sourcepos = P.newPos "" 1 1
2011 }
2012 ]
2013 , " A:B:C ; N:V = Right A:B:C ; N:V" ~:
2014 (Data.List.map fst $
2015 Data.Either.rights $
2016 [P.runParser
2017 (Format.Ledger.Read.posting <* P.eof)
2018 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
2019 ~?=
2020 [ Posting.nil
2021 { Posting.account = ["A","B","C"]
2022 , Posting.comments = [" N:V"]
2023 , Posting.sourcepos = P.newPos "" 1 1
2024 , Posting.tags = Data.Map.fromList
2025 [ ("N", ["V"])
2026 ]
2027 }
2028 ]
2029 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2030 (Data.List.map fst $
2031 Data.Either.rights $
2032 [P.runParser
2033 (Format.Ledger.Read.posting <* P.eof)
2034 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2035 ~?=
2036 [ Posting.nil
2037 { Posting.account = ["A","B","C"]
2038 , Posting.comments = [" some comment N:V"]
2039 , Posting.sourcepos = P.newPos "" 1 1
2040 , Posting.tags = Data.Map.fromList
2041 [ ("N", ["V"])
2042 ]
2043 }
2044 ]
2045 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2046 (Data.List.map fst $
2047 Data.Either.rights $
2048 [P.runParser
2049 (Format.Ledger.Read.posting )
2050 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2051 ~?=
2052 [ Posting.nil
2053 { Posting.account = ["A","B","C"]
2054 , Posting.comments = [" some comment N:V v, N2:V2 v2"]
2055 , Posting.sourcepos = P.newPos "" 1 1
2056 , Posting.tags = Data.Map.fromList
2057 [ ("N", ["V v"])
2058 , ("N2", ["V2 v2"])
2059 ]
2060 }
2061 ]
2062 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2063 (Data.List.map fst $
2064 Data.Either.rights $
2065 [P.runParser
2066 (Format.Ledger.Read.posting <* P.eof)
2067 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2068 ~?=
2069 [ Posting.nil
2070 { Posting.account = ["A","B","C"]
2071 , Posting.comments = [" N:V", " N:V2"]
2072 , Posting.sourcepos = P.newPos "" 1 1
2073 , Posting.tags = Data.Map.fromList
2074 [ ("N", ["V", "V2"])
2075 ]
2076 }
2077 ]
2078 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2079 (Data.List.map fst $
2080 Data.Either.rights $
2081 [P.runParser
2082 (Format.Ledger.Read.posting <* P.eof)
2083 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2084 ~?=
2085 [ Posting.nil
2086 { Posting.account = ["A","B","C"]
2087 , Posting.comments = [" N:V", " N2:V"]
2088 , Posting.sourcepos = P.newPos "" 1 1
2089 , Posting.tags = Data.Map.fromList
2090 [ ("N", ["V"])
2091 , ("N2", ["V"])
2092 ]
2093 }
2094 ]
2095 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2096 (Data.List.map fst $
2097 Data.Either.rights $
2098 [P.runParser
2099 (Format.Ledger.Read.posting <* P.eof)
2100 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2101 ~?=
2102 [ Posting.nil
2103 { Posting.account = ["A","B","C"]
2104 , Posting.comments = [" date:2001/01/01"]
2105 , Posting.dates =
2106 [ Time.ZonedTime
2107 (Time.LocalTime
2108 (Time.fromGregorian 2001 01 01)
2109 (Time.TimeOfDay 0 0 0))
2110 Time.utc
2111 ]
2112 , Posting.sourcepos = P.newPos "" 1 1
2113 , Posting.tags = Data.Map.fromList
2114 [ ("date", ["2001/01/01"])
2115 ]
2116 }
2117 ]
2118 , " (A:B:C) = Right (A:B:C)" ~:
2119 (Data.Either.rights $
2120 [P.runParser
2121 (Format.Ledger.Read.posting <* P.eof)
2122 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
2123 ~?=
2124 [ ( Posting.nil
2125 { Posting.account = ["A","B","C"]
2126 , Posting.sourcepos = P.newPos "" 1 1
2127 }
2128 , Posting.Type_Virtual
2129 )
2130 ]
2131 , " [A:B:C] = Right [A:B:C]" ~:
2132 (Data.Either.rights $
2133 [P.runParser
2134 (Format.Ledger.Read.posting <* P.eof)
2135 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
2136 ~?=
2137 [ ( Posting.nil
2138 { Posting.account = ["A","B","C"]
2139 , Posting.sourcepos = P.newPos "" 1 1
2140 }
2141 , Posting.Type_Virtual_Balanced
2142 )
2143 ]
2144 ]
2145 , "transaction" ~: TestList
2146 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
2147 (Data.Either.rights $
2148 [P.runParser
2149 (Format.Ledger.Read.transaction <* P.eof)
2150 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
2151 ~?=
2152 [ Transaction.nil
2153 { Transaction.dates=
2154 ( Time.ZonedTime
2155 (Time.LocalTime
2156 (Time.fromGregorian 2000 01 01)
2157 (Time.TimeOfDay 0 0 0))
2158 (Time.utc)
2159 , [] )
2160 , Transaction.description="some description"
2161 , Transaction.postings = Posting.from_List
2162 [ Posting.nil
2163 { Posting.account = ["A","B","C"]
2164 , Posting.amounts = Data.Map.fromList
2165 [ ("$", Amount.nil
2166 { Amount.quantity = 1
2167 , Amount.style = Amount.Style.nil
2168 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2169 , Amount.Style.unit_spaced = Just False
2170 }
2171 , Amount.unit = "$"
2172 })
2173 ]
2174 , Posting.sourcepos = P.newPos "" 2 1
2175 }
2176 , Posting.nil
2177 { Posting.account = ["a","b","c"]
2178 , Posting.sourcepos = P.newPos "" 3 1
2179 }
2180 ]
2181 , Transaction.sourcepos = P.newPos "" 1 1
2182 }
2183 ]
2184 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
2185 (Data.Either.rights $
2186 [P.runParser
2187 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
2188 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
2189 ~?=
2190 [ Transaction.nil
2191 { Transaction.dates=
2192 ( Time.ZonedTime
2193 (Time.LocalTime
2194 (Time.fromGregorian 2000 01 01)
2195 (Time.TimeOfDay 0 0 0))
2196 (Time.utc)
2197 , [] )
2198 , Transaction.description="some description"
2199 , Transaction.postings = Posting.from_List
2200 [ Posting.nil
2201 { Posting.account = ["A","B","C"]
2202 , Posting.amounts = Data.Map.fromList
2203 [ ("$", Amount.nil
2204 { Amount.quantity = 1
2205 , Amount.style = Amount.Style.nil
2206 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2207 , Amount.Style.unit_spaced = Just False
2208 }
2209 , Amount.unit = "$"
2210 })
2211 ]
2212 , Posting.sourcepos = P.newPos "" 2 1
2213 }
2214 , Posting.nil
2215 { Posting.account = ["a","b","c"]
2216 , Posting.sourcepos = P.newPos "" 3 1
2217 }
2218 ]
2219 , Transaction.sourcepos = P.newPos "" 1 1
2220 }
2221 ]
2222 , "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" ~:
2223 (Data.Either.rights $
2224 [P.runParser
2225 (Format.Ledger.Read.transaction <* P.eof)
2226 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)])
2227 ~?=
2228 [ Transaction.nil
2229 { Transaction.comments_after =
2230 [ " some comment"
2231 , " some other;comment"
2232 , " some Tag:"
2233 , " some last comment"
2234 ]
2235 , Transaction.dates=
2236 ( Time.ZonedTime
2237 (Time.LocalTime
2238 (Time.fromGregorian 2000 01 01)
2239 (Time.TimeOfDay 0 0 0))
2240 (Time.utc)
2241 , [] )
2242 , Transaction.description="some description"
2243 , Transaction.postings = Posting.from_List
2244 [ Posting.nil
2245 { Posting.account = ["A","B","C"]
2246 , Posting.amounts = Data.Map.fromList
2247 [ ("$", Amount.nil
2248 { Amount.quantity = 1
2249 , Amount.style = Amount.Style.nil
2250 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2251 , Amount.Style.unit_spaced = Just False
2252 }
2253 , Amount.unit = "$"
2254 })
2255 ]
2256 , Posting.sourcepos = P.newPos "" 5 1
2257 }
2258 , Posting.nil
2259 { Posting.account = ["a","b","c"]
2260 , Posting.sourcepos = P.newPos "" 6 1
2261 , Posting.tags = Data.Map.fromList []
2262 }
2263 ]
2264 , Transaction.sourcepos = P.newPos "" 1 1
2265 , Transaction.tags = Data.Map.fromList
2266 [ ("Tag", [""])
2267 ]
2268 }
2269 ]
2270 ]
2271 , "journal" ~: TestList
2272 [ "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
2273 jnl <- liftIO $
2274 P.runParserT
2275 (Format.Ledger.Read.journal "" {-<* P.eof-})
2276 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)
2277 (Data.List.map
2278 (\j -> j{Format.Ledger.Journal.last_read_time=
2279 Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $
2280 Data.Either.rights [jnl])
2281 @?=
2282 [ Format.Ledger.Journal.nil
2283 { Format.Ledger.Journal.transactions = Transaction.from_List
2284 [ Transaction.nil
2285 { Transaction.dates=
2286 ( Time.ZonedTime
2287 (Time.LocalTime
2288 (Time.fromGregorian 2000 01 01)
2289 (Time.TimeOfDay 0 0 0))
2290 (Time.utc)
2291 , [] )
2292 , Transaction.description="1° description"
2293 , Transaction.postings = Posting.from_List
2294 [ Posting.nil
2295 { Posting.account = ["A","B","C"]
2296 , Posting.amounts = Data.Map.fromList
2297 [ ("$", Amount.nil
2298 { Amount.quantity = 1
2299 , Amount.style = Amount.Style.nil
2300 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2301 , Amount.Style.unit_spaced = Just False
2302 }
2303 , Amount.unit = "$"
2304 })
2305 ]
2306 , Posting.sourcepos = P.newPos "" 2 1
2307 }
2308 , Posting.nil
2309 { Posting.account = ["a","b","c"]
2310 , Posting.sourcepos = P.newPos "" 3 1
2311 }
2312 ]
2313 , Transaction.sourcepos = P.newPos "" 1 1
2314 }
2315 , Transaction.nil
2316 { Transaction.dates=
2317 ( Time.ZonedTime
2318 (Time.LocalTime
2319 (Time.fromGregorian 2000 01 02)
2320 (Time.TimeOfDay 0 0 0))
2321 (Time.utc)
2322 , [] )
2323 , Transaction.description="2° description"
2324 , Transaction.postings = Posting.from_List
2325 [ Posting.nil
2326 { Posting.account = ["A","B","C"]
2327 , Posting.amounts = Data.Map.fromList
2328 [ ("$", Amount.nil
2329 { Amount.quantity = 1
2330 , Amount.style = Amount.Style.nil
2331 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2332 , Amount.Style.unit_spaced = Just False
2333 }
2334 , Amount.unit = "$"
2335 })
2336 ]
2337 , Posting.sourcepos = P.newPos "" 5 1
2338 }
2339 , Posting.nil
2340 { Posting.account = ["x","y","z"]
2341 , Posting.sourcepos = P.newPos "" 6 1
2342 }
2343 ]
2344 , Transaction.sourcepos = P.newPos "" 4 1
2345 }
2346 ]
2347 }
2348 ]
2349 ]
2350 ]
2351 , "Write" ~: TestList
2352 [ "account" ~: TestList
2353 [ "nil" ~:
2354 ((Format.Ledger.Write.show $
2355 Format.Ledger.Write.account Posting.Type_Regular
2356 Account.nil)
2357 ~?=
2358 "")
2359 , "A" ~:
2360 ((Format.Ledger.Write.show $
2361 Format.Ledger.Write.account Posting.Type_Regular
2362 ["A"])
2363 ~?=
2364 "A")
2365 , "A:B:C" ~:
2366 ((Format.Ledger.Write.show $
2367 Format.Ledger.Write.account Posting.Type_Regular
2368 ["A", "B", "C"])
2369 ~?=
2370 "A:B:C")
2371 , "(A:B:C)" ~:
2372 ((Format.Ledger.Write.show $
2373 Format.Ledger.Write.account Posting.Type_Virtual
2374 ["A", "B", "C"])
2375 ~?=
2376 "(A:B:C)")
2377 , "[A:B:C]" ~:
2378 ((Format.Ledger.Write.show $
2379 Format.Ledger.Write.account Posting.Type_Virtual_Balanced
2380 ["A", "B", "C"])
2381 ~?=
2382 "[A:B:C]")
2383 ]
2384 , "amount" ~: TestList
2385 [ "nil" ~:
2386 ((Format.Ledger.Write.show $
2387 Format.Ledger.Write.amount
2388 Amount.nil)
2389 ~?=
2390 "0")
2391 , "nil @ prec=2" ~:
2392 ((Format.Ledger.Write.show $
2393 Format.Ledger.Write.amount
2394 Amount.nil
2395 { Amount.style = Amount.Style.nil
2396 { Amount.Style.precision = 2 }
2397 })
2398 ~?=
2399 "0.00")
2400 , "123" ~:
2401 ((Format.Ledger.Write.show $
2402 Format.Ledger.Write.amount
2403 Amount.nil
2404 { Amount.quantity = Decimal 0 123
2405 })
2406 ~?=
2407 "123")
2408 , "-123" ~:
2409 ((Format.Ledger.Write.show $
2410 Format.Ledger.Write.amount
2411 Amount.nil
2412 { Amount.quantity = Decimal 0 (- 123)
2413 })
2414 ~?=
2415 "-123")
2416 , "12.3 @ prec=0" ~:
2417 ((Format.Ledger.Write.show $
2418 Format.Ledger.Write.amount
2419 Amount.nil
2420 { Amount.quantity = Decimal 1 123
2421 , Amount.style = Amount.Style.nil
2422 { Amount.Style.fractioning = Just '.'
2423 }
2424 })
2425 ~?=
2426 "12")
2427 , "12.5 @ prec=0" ~:
2428 ((Format.Ledger.Write.show $
2429 Format.Ledger.Write.amount
2430 Amount.nil
2431 { Amount.quantity = Decimal 1 125
2432 , Amount.style = Amount.Style.nil
2433 { Amount.Style.fractioning = Just '.'
2434 }
2435 })
2436 ~?=
2437 "13")
2438 , "12.3 @ prec=1" ~:
2439 ((Format.Ledger.Write.show $
2440 Format.Ledger.Write.amount
2441 Amount.nil
2442 { Amount.quantity = Decimal 1 123
2443 , Amount.style = Amount.Style.nil
2444 { Amount.Style.fractioning = Just '.'
2445 , Amount.Style.precision = 1
2446 }
2447 })
2448 ~?=
2449 "12.3")
2450 , "1,234.56 @ prec=2" ~:
2451 ((Format.Ledger.Write.show $
2452 Format.Ledger.Write.amount
2453 Amount.nil
2454 { Amount.quantity = Decimal 2 123456
2455 , Amount.style = Amount.Style.nil
2456 { Amount.Style.fractioning = Just '.'
2457 , Amount.Style.precision = 2
2458 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2459 }
2460 })
2461 ~?=
2462 "1,234.56")
2463 , "123,456,789,01,2.3456789 @ prec=7" ~:
2464 ((Format.Ledger.Write.show $
2465 Format.Ledger.Write.amount
2466 Amount.nil
2467 { Amount.quantity = Decimal 7 1234567890123456789
2468 , Amount.style = Amount.Style.nil
2469 { Amount.Style.fractioning = Just '.'
2470 , Amount.Style.precision = 7
2471 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2472 }
2473 })
2474 ~?=
2475 "123,456,789,01,2.3456789")
2476 , "1234567.8,90,123,456,789 @ prec=12" ~:
2477 ((Format.Ledger.Write.show $
2478 Format.Ledger.Write.amount
2479 Amount.nil
2480 { Amount.quantity = Decimal 12 1234567890123456789
2481 , Amount.style = Amount.Style.nil
2482 { Amount.Style.fractioning = Just '.'
2483 , Amount.Style.precision = 12
2484 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2485 }
2486 })
2487 ~?=
2488 "1234567.8,90,123,456,789")
2489 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2490 ((Format.Ledger.Write.show $
2491 Format.Ledger.Write.amount
2492 Amount.nil
2493 { Amount.quantity = Decimal 7 1234567890123456789
2494 , Amount.style = Amount.Style.nil
2495 { Amount.Style.fractioning = Just '.'
2496 , Amount.Style.precision = 7
2497 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2498 }
2499 })
2500 ~?=
2501 "1,2,3,4,5,6,7,89,012.3456789")
2502 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2503 ((Format.Ledger.Write.show $
2504 Format.Ledger.Write.amount
2505 Amount.nil
2506 { Amount.quantity = Decimal 12 1234567890123456789
2507 , Amount.style = Amount.Style.nil
2508 { Amount.Style.fractioning = Just '.'
2509 , Amount.Style.precision = 12
2510 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2511 }
2512 })
2513 ~?=
2514 "1234567.890,12,3,4,5,6,7,8,9")
2515 ]
2516 , "amount_length" ~: TestList
2517 [ "nil" ~:
2518 ((Format.Ledger.Write.amount_length
2519 Amount.nil)
2520 ~?=
2521 1)
2522 , "nil @ prec=2" ~:
2523 ((Format.Ledger.Write.amount_length
2524 Amount.nil
2525 { Amount.style = Amount.Style.nil
2526 { Amount.Style.precision = 2 }
2527 })
2528 ~?=
2529 4)
2530 , "123" ~:
2531 ((Format.Ledger.Write.amount_length
2532 Amount.nil
2533 { Amount.quantity = Decimal 0 123
2534 })
2535 ~?=
2536 3)
2537 , "-123" ~:
2538 ((Format.Ledger.Write.amount_length
2539 Amount.nil
2540 { Amount.quantity = Decimal 0 (- 123)
2541 })
2542 ~?=
2543 4)
2544 , "12.3 @ prec=0" ~:
2545 ((Format.Ledger.Write.amount_length
2546 Amount.nil
2547 { Amount.quantity = Decimal 1 123
2548 , Amount.style = Amount.Style.nil
2549 { Amount.Style.fractioning = Just '.'
2550 }
2551 })
2552 ~?=
2553 2)
2554 , "12.5 @ prec=0" ~:
2555 ((Format.Ledger.Write.amount_length
2556 Amount.nil
2557 { Amount.quantity = Decimal 1 125
2558 , Amount.style = Amount.Style.nil
2559 { Amount.Style.fractioning = Just '.'
2560 }
2561 })
2562 ~?=
2563 2)
2564 , "12.3 @ prec=1" ~:
2565 ((Format.Ledger.Write.amount_length
2566 Amount.nil
2567 { Amount.quantity = Decimal 1 123
2568 , Amount.style = Amount.Style.nil
2569 { Amount.Style.fractioning = Just '.'
2570 , Amount.Style.precision = 1
2571 }
2572 })
2573 ~?=
2574 4)
2575 , "1,234.56 @ prec=2" ~:
2576 ((Format.Ledger.Write.amount_length
2577 Amount.nil
2578 { Amount.quantity = Decimal 2 123456
2579 , Amount.style = Amount.Style.nil
2580 { Amount.Style.fractioning = Just '.'
2581 , Amount.Style.precision = 2
2582 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2583 }
2584 })
2585 ~?=
2586 8)
2587 , "123,456,789,01,2.3456789 @ prec=7" ~:
2588 ((Format.Ledger.Write.amount_length
2589 Amount.nil
2590 { Amount.quantity = Decimal 7 1234567890123456789
2591 , Amount.style = Amount.Style.nil
2592 { Amount.Style.fractioning = Just '.'
2593 , Amount.Style.precision = 7
2594 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2595 }
2596 })
2597 ~?=
2598 24)
2599 , "1234567.8,90,123,456,789 @ prec=12" ~:
2600 ((Format.Ledger.Write.amount_length
2601 Amount.nil
2602 { Amount.quantity = Decimal 12 1234567890123456789
2603 , Amount.style = Amount.Style.nil
2604 { Amount.Style.fractioning = Just '.'
2605 , Amount.Style.precision = 12
2606 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2607 }
2608 })
2609 ~?=
2610 24)
2611 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2612 ((Format.Ledger.Write.amount_length
2613 Amount.nil
2614 { Amount.quantity = Decimal 7 1234567890123456789
2615 , Amount.style = Amount.Style.nil
2616 { Amount.Style.fractioning = Just '.'
2617 , Amount.Style.precision = 7
2618 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2619 }
2620 })
2621 ~?=
2622 28)
2623 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2624 ((Format.Ledger.Write.amount_length
2625 Amount.nil
2626 { Amount.quantity = Decimal 12 1234567890123456789
2627 , Amount.style = Amount.Style.nil
2628 { Amount.Style.fractioning = Just '.'
2629 , Amount.Style.precision = 12
2630 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2631 }
2632 })
2633 ~?=
2634 28)
2635 ]
2636 , "date" ~: TestList
2637 [ "nil" ~:
2638 ((Format.Ledger.Write.show $
2639 Format.Ledger.Write.date
2640 Date.nil)
2641 ~?=
2642 "1970/01/01")
2643 , "2000/01/01 12:34:51 CET" ~:
2644 (Format.Ledger.Write.show $
2645 Format.Ledger.Write.date $
2646 Time.ZonedTime
2647 (Time.LocalTime
2648 (Time.fromGregorian 2000 01 01)
2649 (Time.TimeOfDay 12 34 51))
2650 (Time.TimeZone 60 False "CET"))
2651 ~?=
2652 "2000/01/01 12:34:51 CET"
2653 , "2000/01/01 12:34:51 +0100" ~:
2654 (Format.Ledger.Write.show $
2655 Format.Ledger.Write.date $
2656 Time.ZonedTime
2657 (Time.LocalTime
2658 (Time.fromGregorian 2000 01 01)
2659 (Time.TimeOfDay 12 34 51))
2660 (Time.TimeZone 60 False ""))
2661 ~?=
2662 "2000/01/01 12:34:51 +0100"
2663 , "2000/01/01 01:02:03" ~:
2664 (Format.Ledger.Write.show $
2665 Format.Ledger.Write.date $
2666 Time.ZonedTime
2667 (Time.LocalTime
2668 (Time.fromGregorian 2000 01 01)
2669 (Time.TimeOfDay 1 2 3))
2670 (Time.utc))
2671 ~?=
2672 "2000/01/01 01:02:03"
2673 , "01/01 01:02" ~:
2674 (Format.Ledger.Write.show $
2675 Format.Ledger.Write.date $
2676 Time.ZonedTime
2677 (Time.LocalTime
2678 (Time.fromGregorian 0 01 01)
2679 (Time.TimeOfDay 1 2 0))
2680 (Time.utc))
2681 ~?=
2682 "01/01 01:02"
2683 , "01/01 01:00" ~:
2684 (Format.Ledger.Write.show $
2685 Format.Ledger.Write.date $
2686 Time.ZonedTime
2687 (Time.LocalTime
2688 (Time.fromGregorian 0 01 01)
2689 (Time.TimeOfDay 1 0 0))
2690 (Time.utc))
2691 ~?=
2692 "01/01 01:00"
2693 , "01/01 00:01" ~:
2694 (Format.Ledger.Write.show $
2695 Format.Ledger.Write.date $
2696 Time.ZonedTime
2697 (Time.LocalTime
2698 (Time.fromGregorian 0 01 01)
2699 (Time.TimeOfDay 0 1 0))
2700 (Time.utc))
2701 ~?=
2702 "01/01 00:01"
2703 , "01/01" ~:
2704 (Format.Ledger.Write.show $
2705 Format.Ledger.Write.date $
2706 Time.ZonedTime
2707 (Time.LocalTime
2708 (Time.fromGregorian 0 01 01)
2709 (Time.TimeOfDay 0 0 0))
2710 (Time.utc))
2711 ~?=
2712 "01/01"
2713 ]
2714 , "transaction" ~: TestList
2715 [ "nil" ~:
2716 ((Format.Ledger.Write.show $
2717 Format.Ledger.Write.transaction
2718 Transaction.nil)
2719 ~?=
2720 "1970/01/01\n")
2721 , "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" ~:
2722 ((Format.Ledger.Write.show $
2723 Format.Ledger.Write.transaction $
2724 Transaction.nil
2725 { Transaction.dates=
2726 ( Time.ZonedTime
2727 (Time.LocalTime
2728 (Time.fromGregorian 2000 01 01)
2729 (Time.TimeOfDay 0 0 0))
2730 (Time.utc)
2731 , [] )
2732 , Transaction.description="some description"
2733 , Transaction.postings = Posting.from_List
2734 [ Posting.nil
2735 { Posting.account = ["A","B","C"]
2736 , Posting.amounts = Data.Map.fromList
2737 [ ("$", Amount.nil
2738 { Amount.quantity = 1
2739 , Amount.style = Amount.Style.nil
2740 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2741 , Amount.Style.unit_spaced = Just False
2742 }
2743 , Amount.unit = "$"
2744 })
2745 ]
2746 }
2747 , Posting.nil
2748 { Posting.account = ["a","b","c"]
2749 , Posting.comments = ["first comment","second comment","third comment"]
2750 }
2751 ]
2752 })
2753 ~?=
2754 "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")
2755 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
2756 ((Format.Ledger.Write.show $
2757 Format.Ledger.Write.transaction $
2758 Transaction.nil
2759 { Transaction.dates=
2760 ( Time.ZonedTime
2761 (Time.LocalTime
2762 (Time.fromGregorian 2000 01 01)
2763 (Time.TimeOfDay 0 0 0))
2764 (Time.utc)
2765 , [] )
2766 , Transaction.description="some description"
2767 , Transaction.postings = Posting.from_List
2768 [ Posting.nil
2769 { Posting.account = ["A","B","C"]
2770 , Posting.amounts = Data.Map.fromList
2771 [ ("$", Amount.nil
2772 { Amount.quantity = 1
2773 , Amount.style = Amount.Style.nil
2774 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2775 , Amount.Style.unit_spaced = Just False
2776 }
2777 , Amount.unit = "$"
2778 })
2779 ]
2780 }
2781 , Posting.nil
2782 { Posting.account = ["AA","BB","CC"]
2783 , Posting.amounts = Data.Map.fromList
2784 [ ("$", Amount.nil
2785 { Amount.quantity = 123
2786 , Amount.style = Amount.Style.nil
2787 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2788 , Amount.Style.unit_spaced = Just False
2789 }
2790 , Amount.unit = "$"
2791 })
2792 ]
2793 }
2794 ]
2795 })
2796 ~?=
2797 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")
2798 ]
2799 ]
2800 ]
2801 ]
2802 ]