]> Git — Sourcephile - comptalang.git/blob - lib/Test/Main.hs
Ajout : Hcompta.Format.Text : couleurs ANSI.
[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" ~:
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" ~:
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" ~:
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" ~:
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" ~:
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" ~:
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" ~:
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" ~:
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" ~:
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_value" ~: TestList
1710 [ "," ~:
1711 (Data.Either.rights $
1712 [P.runParser
1713 (Format.Ledger.Read.tag_value <* P.eof)
1714 () "" (","::Text)])
1715 ~?=
1716 [","]
1717 , ",\\n" ~:
1718 (Data.Either.rights $
1719 [P.runParser
1720 (Format.Ledger.Read.tag_value <* P.char '\n' <* P.eof)
1721 () "" (",\n"::Text)])
1722 ~?=
1723 [","]
1724 , ",x" ~:
1725 (Data.Either.rights $
1726 [P.runParser
1727 (Format.Ledger.Read.tag_value <* P.eof)
1728 () "" (",x"::Text)])
1729 ~?=
1730 [",x"]
1731 , ",x:" ~:
1732 (Data.Either.rights $
1733 [P.runParser
1734 (Format.Ledger.Read.tag_value <* P.string ",x:" <* P.eof)
1735 () "" (",x:"::Text)])
1736 ~?=
1737 [""]
1738 , "v, v, n:" ~:
1739 (Data.Either.rights $
1740 [P.runParser
1741 (Format.Ledger.Read.tag_value <* P.string ", n:" <* P.eof)
1742 () "" ("v, v, n:"::Text)])
1743 ~?=
1744 ["v, v"]
1745 ]
1746 , "tag" ~: TestList
1747 [ "Name:" ~:
1748 (Data.Either.rights $
1749 [P.runParser
1750 (Format.Ledger.Read.tag <* P.eof)
1751 () "" ("Name:"::Text)])
1752 ~?=
1753 [("Name", "")]
1754 , "Name:Value" ~:
1755 (Data.Either.rights $
1756 [P.runParser
1757 (Format.Ledger.Read.tag <* P.eof)
1758 () "" ("Name:Value"::Text)])
1759 ~?=
1760 [("Name", "Value")]
1761 , "Name:Value\\n" ~:
1762 (Data.Either.rights $
1763 [P.runParser
1764 (Format.Ledger.Read.tag <* P.string "\n" <* P.eof)
1765 () "" ("Name:Value\n"::Text)])
1766 ~?=
1767 [("Name", "Value")]
1768 , "Name:Val ue" ~:
1769 (Data.Either.rights $
1770 [P.runParser
1771 (Format.Ledger.Read.tag <* P.eof)
1772 () "" ("Name:Val ue"::Text)])
1773 ~?=
1774 [("Name", "Val ue")]
1775 , "Name:," ~:
1776 (Data.Either.rights $
1777 [P.runParser
1778 (Format.Ledger.Read.tag <* P.eof)
1779 () "" ("Name:,"::Text)])
1780 ~?=
1781 [("Name", ",")]
1782 , "Name:Val,ue" ~:
1783 (Data.Either.rights $
1784 [P.runParser
1785 (Format.Ledger.Read.tag <* P.eof)
1786 () "" ("Name:Val,ue"::Text)])
1787 ~?=
1788 [("Name", "Val,ue")]
1789 , "Name:Val,ue:" ~:
1790 (Data.Either.rights $
1791 [P.runParser
1792 (Format.Ledger.Read.tag <* P.string ",ue:" <* P.eof)
1793 () "" ("Name:Val,ue:"::Text)])
1794 ~?=
1795 [("Name", "Val")]
1796 ]
1797 , "tags" ~: TestList
1798 [ "Name:" ~:
1799 (Data.Either.rights $
1800 [P.runParser
1801 (Format.Ledger.Read.tags <* P.eof)
1802 () "" ("Name:"::Text)])
1803 ~?=
1804 [Data.Map.fromList
1805 [ ("Name", [""])
1806 ]
1807 ]
1808 , "Name:," ~:
1809 (Data.Either.rights $
1810 [P.runParser
1811 (Format.Ledger.Read.tags <* P.eof)
1812 () "" ("Name:,"::Text)])
1813 ~?=
1814 [Data.Map.fromList
1815 [ ("Name", [","])
1816 ]
1817 ]
1818 , "Name:,Name:" ~:
1819 (Data.Either.rights $
1820 [P.runParser
1821 (Format.Ledger.Read.tags <* P.eof)
1822 () "" ("Name:,Name:"::Text)])
1823 ~?=
1824 [Data.Map.fromList
1825 [ ("Name", ["", ""])
1826 ]
1827 ]
1828 , "Name:,Name2:" ~:
1829 (Data.Either.rights $
1830 [P.runParser
1831 (Format.Ledger.Read.tags <* P.eof)
1832 () "" ("Name:,Name2:"::Text)])
1833 ~?=
1834 [Data.Map.fromList
1835 [ ("Name", [""])
1836 , ("Name2", [""])
1837 ]
1838 ]
1839 , "Name: , Name2:" ~:
1840 (Data.Either.rights $
1841 [P.runParser
1842 (Format.Ledger.Read.tags <* P.eof)
1843 () "" ("Name: , Name2:"::Text)])
1844 ~?=
1845 [Data.Map.fromList
1846 [ ("Name", [" "])
1847 , ("Name2", [""])
1848 ]
1849 ]
1850 , "Name:,Name2:,Name3:" ~:
1851 (Data.Either.rights $
1852 [P.runParser
1853 (Format.Ledger.Read.tags <* P.eof)
1854 () "" ("Name:,Name2:,Name3:"::Text)])
1855 ~?=
1856 [Data.Map.fromList
1857 [ ("Name", [""])
1858 , ("Name2", [""])
1859 , ("Name3", [""])
1860 ]
1861 ]
1862 , "Name:Val ue,Name2:V a l u e,Name3:V al ue" ~:
1863 (Data.Either.rights $
1864 [P.runParser
1865 (Format.Ledger.Read.tags <* P.eof)
1866 () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
1867 ~?=
1868 [Data.Map.fromList
1869 [ ("Name", ["Val ue"])
1870 , ("Name2", ["V a l u e"])
1871 , ("Name3", ["V al ue"])
1872 ]
1873 ]
1874 ]
1875 , "posting" ~: TestList
1876 [ " A:B:C = Right A:B:C" ~:
1877 (Data.Either.rights $
1878 [P.runParser
1879 (Format.Ledger.Read.posting <* P.eof)
1880 Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
1881 ~?=
1882 [ ( Posting.nil
1883 { Posting.account = ["A","B","C"]
1884 , Posting.sourcepos = P.newPos "" 1 1
1885 }
1886 , Posting.Type_Regular
1887 )
1888 ]
1889 , " !A:B:C = Right !A:B:C" ~:
1890 (Data.List.map fst $
1891 Data.Either.rights $
1892 [P.runParser
1893 (Format.Ledger.Read.posting <* P.eof)
1894 Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
1895 ~?=
1896 [ Posting.nil
1897 { Posting.account = ["A","B","C"]
1898 , Posting.sourcepos = P.newPos "" 1 1
1899 , Posting.status = True
1900 }
1901 ]
1902 , " *A:B:C = Right *A:B:C" ~:
1903 (Data.List.map fst $
1904 Data.Either.rights $
1905 [P.runParser
1906 (Format.Ledger.Read.posting <* P.eof)
1907 Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
1908 ~?=
1909 [ Posting.nil
1910 { Posting.account = ["A","B","C"]
1911 , Posting.amounts = Data.Map.fromList []
1912 , Posting.comments = []
1913 , Posting.dates = []
1914 , Posting.status = True
1915 , Posting.sourcepos = P.newPos "" 1 1
1916 , Posting.tags = Data.Map.fromList []
1917 }
1918 ]
1919 , " A:B:C $1 = Right A:B:C $1" ~:
1920 (Data.List.map fst $
1921 Data.Either.rights $
1922 [P.runParser
1923 (Format.Ledger.Read.posting <* P.eof)
1924 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1925 ~?=
1926 [ Posting.nil
1927 { Posting.account = ["A","B","C $1"]
1928 , Posting.sourcepos = P.newPos "" 1 1
1929 }
1930 ]
1931 , " A:B:C $1 = Right A:B:C $1" ~:
1932 (Data.List.map fst $
1933 Data.Either.rights $
1934 [P.runParser
1935 (Format.Ledger.Read.posting <* P.eof)
1936 Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
1937 ~?=
1938 [ Posting.nil
1939 { Posting.account = ["A","B","C"]
1940 , Posting.amounts = Data.Map.fromList
1941 [ ("$", Amount.nil
1942 { Amount.quantity = 1
1943 , Amount.style = Amount.Style.nil
1944 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1945 , Amount.Style.unit_spaced = Just False
1946 }
1947 , Amount.unit = "$"
1948 })
1949 ]
1950 , Posting.sourcepos = P.newPos "" 1 1
1951 }
1952 ]
1953 , " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
1954 (Data.List.map fst $
1955 Data.Either.rights $
1956 [P.runParser
1957 (Format.Ledger.Read.posting <* P.eof)
1958 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
1959 ~?=
1960 [ Posting.nil
1961 { Posting.account = ["A","B","C"]
1962 , Posting.amounts = Data.Map.fromList
1963 [ ("$", Amount.nil
1964 { Amount.quantity = 1
1965 , Amount.style = Amount.Style.nil
1966 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1967 , Amount.Style.unit_spaced = Just False
1968 }
1969 , Amount.unit = "$"
1970 })
1971 , ("€", Amount.nil
1972 { Amount.quantity = 1
1973 , Amount.style = Amount.Style.nil
1974 { Amount.Style.unit_side = Just Amount.Style.Side_Right
1975 , Amount.Style.unit_spaced = Just False
1976 }
1977 , Amount.unit = "€"
1978 })
1979 ]
1980 , Posting.sourcepos = P.newPos "" 1 1
1981 }
1982 ]
1983 , " A:B:C $1 + 1$ = Right A:B:C $2" ~:
1984 (Data.List.map fst $
1985 Data.Either.rights $
1986 [P.runParser
1987 (Format.Ledger.Read.posting <* P.eof)
1988 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
1989 ~?=
1990 [ Posting.nil
1991 { Posting.account = ["A","B","C"]
1992 , Posting.amounts = Data.Map.fromList
1993 [ ("$", Amount.nil
1994 { Amount.quantity = 2
1995 , Amount.style = Amount.Style.nil
1996 { Amount.Style.unit_side = Just Amount.Style.Side_Left
1997 , Amount.Style.unit_spaced = Just False
1998 }
1999 , Amount.unit = "$"
2000 })
2001 ]
2002 , Posting.sourcepos = P.newPos "" 1 1
2003 }
2004 ]
2005 , " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
2006 (Data.List.map fst $
2007 Data.Either.rights $
2008 [P.runParser
2009 (Format.Ledger.Read.posting <* P.eof)
2010 Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
2011 ~?=
2012 [ Posting.nil
2013 { Posting.account = ["A","B","C"]
2014 , Posting.amounts = Data.Map.fromList
2015 [ ("$", Amount.nil
2016 { Amount.quantity = 3
2017 , Amount.style = Amount.Style.nil
2018 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2019 , Amount.Style.unit_spaced = Just False
2020 }
2021 , Amount.unit = "$"
2022 })
2023 ]
2024 , Posting.sourcepos = P.newPos "" 1 1
2025 }
2026 ]
2027 , " A:B:C ; some comment = Right A:B:C ; some comment" ~:
2028 (Data.List.map fst $
2029 Data.Either.rights $
2030 [P.runParser
2031 (Format.Ledger.Read.posting <* P.eof)
2032 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
2033 ~?=
2034 [ Posting.nil
2035 { Posting.account = ["A","B","C"]
2036 , Posting.amounts = Data.Map.fromList []
2037 , Posting.comments = [" some comment"]
2038 , Posting.sourcepos = P.newPos "" 1 1
2039 }
2040 ]
2041 , " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
2042 (Data.List.map fst $
2043 Data.Either.rights $
2044 [P.runParser
2045 (Format.Ledger.Read.posting <* P.eof)
2046 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
2047 ~?=
2048 [ Posting.nil
2049 { Posting.account = ["A","B","C"]
2050 , Posting.amounts = Data.Map.fromList []
2051 , Posting.comments = [" some comment", " some other comment"]
2052 , Posting.sourcepos = P.newPos "" 1 1
2053 }
2054 ]
2055 , " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
2056 (Data.List.map fst $
2057 Data.Either.rights $
2058 [P.runParser
2059 (Format.Ledger.Read.posting)
2060 Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
2061 ~?=
2062 [ Posting.nil
2063 { Posting.account = ["A","B","C"]
2064 , Posting.amounts = Data.Map.fromList
2065 [ ("$", Amount.nil
2066 { Amount.quantity = 1
2067 , Amount.style = Amount.Style.nil
2068 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2069 , Amount.Style.unit_spaced = Just False
2070 }
2071 , Amount.unit = "$"
2072 })
2073 ]
2074 , Posting.comments = [" some comment"]
2075 , Posting.sourcepos = P.newPos "" 1 1
2076 }
2077 ]
2078 , " A:B:C ; N:V = Right A:B:C ; N: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"::Text)])
2084 ~?=
2085 [ Posting.nil
2086 { Posting.account = ["A","B","C"]
2087 , Posting.comments = [" N:V"]
2088 , Posting.sourcepos = P.newPos "" 1 1
2089 , Posting.tags = Data.Map.fromList
2090 [ ("N", ["V"])
2091 ]
2092 }
2093 ]
2094 , " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
2095 (Data.List.map fst $
2096 Data.Either.rights $
2097 [P.runParser
2098 (Format.Ledger.Read.posting <* P.eof)
2099 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
2100 ~?=
2101 [ Posting.nil
2102 { Posting.account = ["A","B","C"]
2103 , Posting.comments = [" some comment N:V"]
2104 , Posting.sourcepos = P.newPos "" 1 1
2105 , Posting.tags = Data.Map.fromList
2106 [ ("N", ["V"])
2107 ]
2108 }
2109 ]
2110 , " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
2111 (Data.List.map fst $
2112 Data.Either.rights $
2113 [P.runParser
2114 (Format.Ledger.Read.posting )
2115 Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
2116 ~?=
2117 [ Posting.nil
2118 { Posting.account = ["A","B","C"]
2119 , Posting.comments = [" some comment N:V v, N2:V2 v2"]
2120 , Posting.sourcepos = P.newPos "" 1 1
2121 , Posting.tags = Data.Map.fromList
2122 [ ("N", ["V v"])
2123 , ("N2", ["V2 v2"])
2124 ]
2125 }
2126 ]
2127 , " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
2128 (Data.List.map fst $
2129 Data.Either.rights $
2130 [P.runParser
2131 (Format.Ledger.Read.posting <* P.eof)
2132 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
2133 ~?=
2134 [ Posting.nil
2135 { Posting.account = ["A","B","C"]
2136 , Posting.comments = [" N:V", " N:V2"]
2137 , Posting.sourcepos = P.newPos "" 1 1
2138 , Posting.tags = Data.Map.fromList
2139 [ ("N", ["V", "V2"])
2140 ]
2141 }
2142 ]
2143 , " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
2144 (Data.List.map fst $
2145 Data.Either.rights $
2146 [P.runParser
2147 (Format.Ledger.Read.posting <* P.eof)
2148 Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
2149 ~?=
2150 [ Posting.nil
2151 { Posting.account = ["A","B","C"]
2152 , Posting.comments = [" N:V", " N2:V"]
2153 , Posting.sourcepos = P.newPos "" 1 1
2154 , Posting.tags = Data.Map.fromList
2155 [ ("N", ["V"])
2156 , ("N2", ["V"])
2157 ]
2158 }
2159 ]
2160 , " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
2161 (Data.List.map fst $
2162 Data.Either.rights $
2163 [P.runParser
2164 (Format.Ledger.Read.posting <* P.eof)
2165 Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
2166 ~?=
2167 [ Posting.nil
2168 { Posting.account = ["A","B","C"]
2169 , Posting.comments = [" date:2001/01/01"]
2170 , Posting.dates =
2171 [ Time.ZonedTime
2172 (Time.LocalTime
2173 (Time.fromGregorian 2001 01 01)
2174 (Time.TimeOfDay 0 0 0))
2175 Time.utc
2176 ]
2177 , Posting.sourcepos = P.newPos "" 1 1
2178 , Posting.tags = Data.Map.fromList
2179 [ ("date", ["2001/01/01"])
2180 ]
2181 }
2182 ]
2183 , " (A:B:C) = Right (A:B:C)" ~:
2184 (Data.Either.rights $
2185 [P.runParser
2186 (Format.Ledger.Read.posting <* P.eof)
2187 Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
2188 ~?=
2189 [ ( Posting.nil
2190 { Posting.account = ["A","B","C"]
2191 , Posting.sourcepos = P.newPos "" 1 1
2192 }
2193 , Posting.Type_Virtual
2194 )
2195 ]
2196 , " [A:B:C] = Right [A:B:C]" ~:
2197 (Data.Either.rights $
2198 [P.runParser
2199 (Format.Ledger.Read.posting <* P.eof)
2200 Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
2201 ~?=
2202 [ ( Posting.nil
2203 { Posting.account = ["A","B","C"]
2204 , Posting.sourcepos = P.newPos "" 1 1
2205 }
2206 , Posting.Type_Virtual_Balanced
2207 )
2208 ]
2209 ]
2210 , "transaction" ~: TestList
2211 [ "2000/01/01 some description\\n A:B:C $1\\n a:b:c" ~:
2212 (Data.Either.rights $
2213 [P.runParser
2214 (Format.Ledger.Read.transaction <* P.eof)
2215 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
2216 ~?=
2217 [ Transaction.nil
2218 { Transaction.dates=
2219 ( Time.ZonedTime
2220 (Time.LocalTime
2221 (Time.fromGregorian 2000 01 01)
2222 (Time.TimeOfDay 0 0 0))
2223 (Time.utc)
2224 , [] )
2225 , Transaction.description="some description"
2226 , Transaction.postings = Posting.from_List
2227 [ Posting.nil
2228 { Posting.account = ["A","B","C"]
2229 , Posting.amounts = Data.Map.fromList
2230 [ ("$", Amount.nil
2231 { Amount.quantity = 1
2232 , Amount.style = Amount.Style.nil
2233 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2234 , Amount.Style.unit_spaced = Just False
2235 }
2236 , Amount.unit = "$"
2237 })
2238 ]
2239 , Posting.sourcepos = P.newPos "" 2 1
2240 }
2241 , Posting.nil
2242 { Posting.account = ["a","b","c"]
2243 , Posting.sourcepos = P.newPos "" 3 1
2244 }
2245 ]
2246 , Transaction.sourcepos = P.newPos "" 1 1
2247 }
2248 ]
2249 , "2000/01/01 some description\\n A:B:C $1\\n a:b:c\\n" ~:
2250 (Data.Either.rights $
2251 [P.runParser
2252 (Format.Ledger.Read.transaction <* P.newline <* P.eof)
2253 Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
2254 ~?=
2255 [ Transaction.nil
2256 { Transaction.dates=
2257 ( Time.ZonedTime
2258 (Time.LocalTime
2259 (Time.fromGregorian 2000 01 01)
2260 (Time.TimeOfDay 0 0 0))
2261 (Time.utc)
2262 , [] )
2263 , Transaction.description="some description"
2264 , Transaction.postings = Posting.from_List
2265 [ Posting.nil
2266 { Posting.account = ["A","B","C"]
2267 , Posting.amounts = Data.Map.fromList
2268 [ ("$", Amount.nil
2269 { Amount.quantity = 1
2270 , Amount.style = Amount.Style.nil
2271 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2272 , Amount.Style.unit_spaced = Just False
2273 }
2274 , Amount.unit = "$"
2275 })
2276 ]
2277 , Posting.sourcepos = P.newPos "" 2 1
2278 }
2279 , Posting.nil
2280 { Posting.account = ["a","b","c"]
2281 , Posting.sourcepos = P.newPos "" 3 1
2282 }
2283 ]
2284 , Transaction.sourcepos = P.newPos "" 1 1
2285 }
2286 ]
2287 , "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" ~:
2288 (Data.Either.rights $
2289 [P.runParser
2290 (Format.Ledger.Read.transaction <* P.eof)
2291 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)])
2292 ~?=
2293 [ Transaction.nil
2294 { Transaction.comments_after =
2295 [ " some comment"
2296 , " some other;comment"
2297 , " some Tag:"
2298 , " some last comment"
2299 ]
2300 , Transaction.dates=
2301 ( Time.ZonedTime
2302 (Time.LocalTime
2303 (Time.fromGregorian 2000 01 01)
2304 (Time.TimeOfDay 0 0 0))
2305 (Time.utc)
2306 , [] )
2307 , Transaction.description="some description"
2308 , Transaction.postings = Posting.from_List
2309 [ Posting.nil
2310 { Posting.account = ["A","B","C"]
2311 , Posting.amounts = Data.Map.fromList
2312 [ ("$", Amount.nil
2313 { Amount.quantity = 1
2314 , Amount.style = Amount.Style.nil
2315 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2316 , Amount.Style.unit_spaced = Just False
2317 }
2318 , Amount.unit = "$"
2319 })
2320 ]
2321 , Posting.sourcepos = P.newPos "" 5 1
2322 }
2323 , Posting.nil
2324 { Posting.account = ["a","b","c"]
2325 , Posting.sourcepos = P.newPos "" 6 1
2326 , Posting.tags = Data.Map.fromList []
2327 }
2328 ]
2329 , Transaction.sourcepos = P.newPos "" 1 1
2330 , Transaction.tags = Data.Map.fromList
2331 [ ("Tag", [""])
2332 ]
2333 }
2334 ]
2335 ]
2336 , "journal" ~: TestList
2337 [ "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
2338 jnl <- liftIO $
2339 P.runParserT
2340 (Format.Ledger.Read.journal "" {-<* P.eof-})
2341 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)
2342 (Data.List.map
2343 (\j -> j{Format.Ledger.Journal.last_read_time=
2344 Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $
2345 Data.Either.rights [jnl])
2346 @?=
2347 [ Format.Ledger.Journal.nil
2348 { Format.Ledger.Journal.transactions = Transaction.from_List
2349 [ Transaction.nil
2350 { Transaction.dates=
2351 ( Time.ZonedTime
2352 (Time.LocalTime
2353 (Time.fromGregorian 2000 01 01)
2354 (Time.TimeOfDay 0 0 0))
2355 (Time.utc)
2356 , [] )
2357 , Transaction.description="1° description"
2358 , Transaction.postings = Posting.from_List
2359 [ Posting.nil
2360 { Posting.account = ["A","B","C"]
2361 , Posting.amounts = Data.Map.fromList
2362 [ ("$", Amount.nil
2363 { Amount.quantity = 1
2364 , Amount.style = Amount.Style.nil
2365 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2366 , Amount.Style.unit_spaced = Just False
2367 }
2368 , Amount.unit = "$"
2369 })
2370 ]
2371 , Posting.sourcepos = P.newPos "" 2 1
2372 }
2373 , Posting.nil
2374 { Posting.account = ["a","b","c"]
2375 , Posting.sourcepos = P.newPos "" 3 1
2376 }
2377 ]
2378 , Transaction.sourcepos = P.newPos "" 1 1
2379 }
2380 , Transaction.nil
2381 { Transaction.dates=
2382 ( Time.ZonedTime
2383 (Time.LocalTime
2384 (Time.fromGregorian 2000 01 02)
2385 (Time.TimeOfDay 0 0 0))
2386 (Time.utc)
2387 , [] )
2388 , Transaction.description="2° description"
2389 , Transaction.postings = Posting.from_List
2390 [ Posting.nil
2391 { Posting.account = ["A","B","C"]
2392 , Posting.amounts = Data.Map.fromList
2393 [ ("$", Amount.nil
2394 { Amount.quantity = 1
2395 , Amount.style = Amount.Style.nil
2396 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2397 , Amount.Style.unit_spaced = Just False
2398 }
2399 , Amount.unit = "$"
2400 })
2401 ]
2402 , Posting.sourcepos = P.newPos "" 5 1
2403 }
2404 , Posting.nil
2405 { Posting.account = ["x","y","z"]
2406 , Posting.sourcepos = P.newPos "" 6 1
2407 }
2408 ]
2409 , Transaction.sourcepos = P.newPos "" 4 1
2410 }
2411 ]
2412 }
2413 ]
2414 ]
2415 ]
2416 , "Write" ~: TestList
2417 [ "account" ~: TestList
2418 [ "nil" ~:
2419 ((Format.Ledger.Write.show False $
2420 Format.Ledger.Write.account Posting.Type_Regular
2421 Account.nil)
2422 ~?=
2423 "")
2424 , "A" ~:
2425 ((Format.Ledger.Write.show False $
2426 Format.Ledger.Write.account Posting.Type_Regular
2427 ["A"])
2428 ~?=
2429 "A")
2430 , "A:B:C" ~:
2431 ((Format.Ledger.Write.show False $
2432 Format.Ledger.Write.account Posting.Type_Regular
2433 ["A", "B", "C"])
2434 ~?=
2435 "A:B:C")
2436 , "(A:B:C)" ~:
2437 ((Format.Ledger.Write.show False $
2438 Format.Ledger.Write.account Posting.Type_Virtual
2439 ["A", "B", "C"])
2440 ~?=
2441 "(A:B:C)")
2442 , "[A:B:C]" ~:
2443 ((Format.Ledger.Write.show False $
2444 Format.Ledger.Write.account Posting.Type_Virtual_Balanced
2445 ["A", "B", "C"])
2446 ~?=
2447 "[A:B:C]")
2448 ]
2449 , "amount" ~: TestList
2450 [ "nil" ~:
2451 ((Format.Ledger.Write.show False $
2452 Format.Ledger.Write.amount
2453 Amount.nil)
2454 ~?=
2455 "0")
2456 , "nil @ prec=2" ~:
2457 ((Format.Ledger.Write.show False $
2458 Format.Ledger.Write.amount
2459 Amount.nil
2460 { Amount.style = Amount.Style.nil
2461 { Amount.Style.precision = 2 }
2462 })
2463 ~?=
2464 "0.00")
2465 , "123" ~:
2466 ((Format.Ledger.Write.show False $
2467 Format.Ledger.Write.amount
2468 Amount.nil
2469 { Amount.quantity = Decimal 0 123
2470 })
2471 ~?=
2472 "123")
2473 , "-123" ~:
2474 ((Format.Ledger.Write.show False $
2475 Format.Ledger.Write.amount
2476 Amount.nil
2477 { Amount.quantity = Decimal 0 (- 123)
2478 })
2479 ~?=
2480 "-123")
2481 , "12.3 @ prec=0" ~:
2482 ((Format.Ledger.Write.show False $
2483 Format.Ledger.Write.amount
2484 Amount.nil
2485 { Amount.quantity = Decimal 1 123
2486 , Amount.style = Amount.Style.nil
2487 { Amount.Style.fractioning = Just '.'
2488 }
2489 })
2490 ~?=
2491 "12")
2492 , "12.5 @ prec=0" ~:
2493 ((Format.Ledger.Write.show False $
2494 Format.Ledger.Write.amount
2495 Amount.nil
2496 { Amount.quantity = Decimal 1 125
2497 , Amount.style = Amount.Style.nil
2498 { Amount.Style.fractioning = Just '.'
2499 }
2500 })
2501 ~?=
2502 "13")
2503 , "12.3 @ prec=1" ~:
2504 ((Format.Ledger.Write.show False $
2505 Format.Ledger.Write.amount
2506 Amount.nil
2507 { Amount.quantity = Decimal 1 123
2508 , Amount.style = Amount.Style.nil
2509 { Amount.Style.fractioning = Just '.'
2510 , Amount.Style.precision = 1
2511 }
2512 })
2513 ~?=
2514 "12.3")
2515 , "1,234.56 @ prec=2" ~:
2516 ((Format.Ledger.Write.show False $
2517 Format.Ledger.Write.amount
2518 Amount.nil
2519 { Amount.quantity = Decimal 2 123456
2520 , Amount.style = Amount.Style.nil
2521 { Amount.Style.fractioning = Just '.'
2522 , Amount.Style.precision = 2
2523 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2524 }
2525 })
2526 ~?=
2527 "1,234.56")
2528 , "123,456,789,01,2.3456789 @ prec=7" ~:
2529 ((Format.Ledger.Write.show False $
2530 Format.Ledger.Write.amount
2531 Amount.nil
2532 { Amount.quantity = Decimal 7 1234567890123456789
2533 , Amount.style = Amount.Style.nil
2534 { Amount.Style.fractioning = Just '.'
2535 , Amount.Style.precision = 7
2536 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2537 }
2538 })
2539 ~?=
2540 "123,456,789,01,2.3456789")
2541 , "1234567.8,90,123,456,789 @ prec=12" ~:
2542 ((Format.Ledger.Write.show False $
2543 Format.Ledger.Write.amount
2544 Amount.nil
2545 { Amount.quantity = Decimal 12 1234567890123456789
2546 , Amount.style = Amount.Style.nil
2547 { Amount.Style.fractioning = Just '.'
2548 , Amount.Style.precision = 12
2549 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2550 }
2551 })
2552 ~?=
2553 "1234567.8,90,123,456,789")
2554 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2555 ((Format.Ledger.Write.show False $
2556 Format.Ledger.Write.amount
2557 Amount.nil
2558 { Amount.quantity = Decimal 7 1234567890123456789
2559 , Amount.style = Amount.Style.nil
2560 { Amount.Style.fractioning = Just '.'
2561 , Amount.Style.precision = 7
2562 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2563 }
2564 })
2565 ~?=
2566 "1,2,3,4,5,6,7,89,012.3456789")
2567 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2568 ((Format.Ledger.Write.show False $
2569 Format.Ledger.Write.amount
2570 Amount.nil
2571 { Amount.quantity = Decimal 12 1234567890123456789
2572 , Amount.style = Amount.Style.nil
2573 { Amount.Style.fractioning = Just '.'
2574 , Amount.Style.precision = 12
2575 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2576 }
2577 })
2578 ~?=
2579 "1234567.890,12,3,4,5,6,7,8,9")
2580 ]
2581 , "amount_length" ~: TestList
2582 [ "nil" ~:
2583 ((Format.Ledger.Write.amount_length
2584 Amount.nil)
2585 ~?=
2586 1)
2587 , "nil @ prec=2" ~:
2588 ((Format.Ledger.Write.amount_length
2589 Amount.nil
2590 { Amount.style = Amount.Style.nil
2591 { Amount.Style.precision = 2 }
2592 })
2593 ~?=
2594 4)
2595 , "123" ~:
2596 ((Format.Ledger.Write.amount_length
2597 Amount.nil
2598 { Amount.quantity = Decimal 0 123
2599 })
2600 ~?=
2601 3)
2602 , "-123" ~:
2603 ((Format.Ledger.Write.amount_length
2604 Amount.nil
2605 { Amount.quantity = Decimal 0 (- 123)
2606 })
2607 ~?=
2608 4)
2609 , "12.3 @ prec=0" ~:
2610 ((Format.Ledger.Write.amount_length
2611 Amount.nil
2612 { Amount.quantity = Decimal 1 123
2613 , Amount.style = Amount.Style.nil
2614 { Amount.Style.fractioning = Just '.'
2615 }
2616 })
2617 ~?=
2618 2)
2619 , "12.5 @ prec=0" ~:
2620 ((Format.Ledger.Write.amount_length
2621 Amount.nil
2622 { Amount.quantity = Decimal 1 125
2623 , Amount.style = Amount.Style.nil
2624 { Amount.Style.fractioning = Just '.'
2625 }
2626 })
2627 ~?=
2628 2)
2629 , "12.3 @ prec=1" ~:
2630 ((Format.Ledger.Write.amount_length
2631 Amount.nil
2632 { Amount.quantity = Decimal 1 123
2633 , Amount.style = Amount.Style.nil
2634 { Amount.Style.fractioning = Just '.'
2635 , Amount.Style.precision = 1
2636 }
2637 })
2638 ~?=
2639 4)
2640 , "1,234.56 @ prec=2" ~:
2641 ((Format.Ledger.Write.amount_length
2642 Amount.nil
2643 { Amount.quantity = Decimal 2 123456
2644 , Amount.style = Amount.Style.nil
2645 { Amount.Style.fractioning = Just '.'
2646 , Amount.Style.precision = 2
2647 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
2648 }
2649 })
2650 ~?=
2651 8)
2652 , "123,456,789,01,2.3456789 @ prec=7" ~:
2653 ((Format.Ledger.Write.amount_length
2654 Amount.nil
2655 { Amount.quantity = Decimal 7 1234567890123456789
2656 , Amount.style = Amount.Style.nil
2657 { Amount.Style.fractioning = Just '.'
2658 , Amount.Style.precision = 7
2659 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2660 }
2661 })
2662 ~?=
2663 24)
2664 , "1234567.8,90,123,456,789 @ prec=12" ~:
2665 ((Format.Ledger.Write.amount_length
2666 Amount.nil
2667 { Amount.quantity = Decimal 12 1234567890123456789
2668 , Amount.style = Amount.Style.nil
2669 { Amount.Style.fractioning = Just '.'
2670 , Amount.Style.precision = 12
2671 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
2672 }
2673 })
2674 ~?=
2675 24)
2676 , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
2677 ((Format.Ledger.Write.amount_length
2678 Amount.nil
2679 { Amount.quantity = Decimal 7 1234567890123456789
2680 , Amount.style = Amount.Style.nil
2681 { Amount.Style.fractioning = Just '.'
2682 , Amount.Style.precision = 7
2683 , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2684 }
2685 })
2686 ~?=
2687 28)
2688 , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
2689 ((Format.Ledger.Write.amount_length
2690 Amount.nil
2691 { Amount.quantity = Decimal 12 1234567890123456789
2692 , Amount.style = Amount.Style.nil
2693 { Amount.Style.fractioning = Just '.'
2694 , Amount.Style.precision = 12
2695 , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
2696 }
2697 })
2698 ~?=
2699 28)
2700 ]
2701 , "date" ~: TestList
2702 [ "nil" ~:
2703 ((Format.Ledger.Write.show False $
2704 Format.Ledger.Write.date
2705 Date.nil)
2706 ~?=
2707 "1970/01/01")
2708 , "2000/01/01 12:34:51 CET" ~:
2709 (Format.Ledger.Write.show False $
2710 Format.Ledger.Write.date $
2711 Time.ZonedTime
2712 (Time.LocalTime
2713 (Time.fromGregorian 2000 01 01)
2714 (Time.TimeOfDay 12 34 51))
2715 (Time.TimeZone 60 False "CET"))
2716 ~?=
2717 "2000/01/01 12:34:51 CET"
2718 , "2000/01/01 12:34:51 +0100" ~:
2719 (Format.Ledger.Write.show False $
2720 Format.Ledger.Write.date $
2721 Time.ZonedTime
2722 (Time.LocalTime
2723 (Time.fromGregorian 2000 01 01)
2724 (Time.TimeOfDay 12 34 51))
2725 (Time.TimeZone 60 False ""))
2726 ~?=
2727 "2000/01/01 12:34:51 +0100"
2728 , "2000/01/01 01:02:03" ~:
2729 (Format.Ledger.Write.show False $
2730 Format.Ledger.Write.date $
2731 Time.ZonedTime
2732 (Time.LocalTime
2733 (Time.fromGregorian 2000 01 01)
2734 (Time.TimeOfDay 1 2 3))
2735 (Time.utc))
2736 ~?=
2737 "2000/01/01 01:02:03"
2738 , "01/01 01:02" ~:
2739 (Format.Ledger.Write.show False $
2740 Format.Ledger.Write.date $
2741 Time.ZonedTime
2742 (Time.LocalTime
2743 (Time.fromGregorian 0 01 01)
2744 (Time.TimeOfDay 1 2 0))
2745 (Time.utc))
2746 ~?=
2747 "01/01 01:02"
2748 , "01/01 01:00" ~:
2749 (Format.Ledger.Write.show False $
2750 Format.Ledger.Write.date $
2751 Time.ZonedTime
2752 (Time.LocalTime
2753 (Time.fromGregorian 0 01 01)
2754 (Time.TimeOfDay 1 0 0))
2755 (Time.utc))
2756 ~?=
2757 "01/01 01:00"
2758 , "01/01 00:01" ~:
2759 (Format.Ledger.Write.show False $
2760 Format.Ledger.Write.date $
2761 Time.ZonedTime
2762 (Time.LocalTime
2763 (Time.fromGregorian 0 01 01)
2764 (Time.TimeOfDay 0 1 0))
2765 (Time.utc))
2766 ~?=
2767 "01/01 00:01"
2768 , "01/01" ~:
2769 (Format.Ledger.Write.show False $
2770 Format.Ledger.Write.date $
2771 Time.ZonedTime
2772 (Time.LocalTime
2773 (Time.fromGregorian 0 01 01)
2774 (Time.TimeOfDay 0 0 0))
2775 (Time.utc))
2776 ~?=
2777 "01/01"
2778 ]
2779 , "transaction" ~: TestList
2780 [ "nil" ~:
2781 ((Format.Ledger.Write.show False $
2782 Format.Ledger.Write.transaction
2783 Transaction.nil)
2784 ~?=
2785 "1970/01/01\n")
2786 , "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" ~:
2787 ((Format.Ledger.Write.show False $
2788 Format.Ledger.Write.transaction $
2789 Transaction.nil
2790 { Transaction.dates=
2791 ( Time.ZonedTime
2792 (Time.LocalTime
2793 (Time.fromGregorian 2000 01 01)
2794 (Time.TimeOfDay 0 0 0))
2795 (Time.utc)
2796 , [] )
2797 , Transaction.description="some description"
2798 , Transaction.postings = Posting.from_List
2799 [ Posting.nil
2800 { Posting.account = ["A","B","C"]
2801 , Posting.amounts = Data.Map.fromList
2802 [ ("$", Amount.nil
2803 { Amount.quantity = 1
2804 , Amount.style = Amount.Style.nil
2805 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2806 , Amount.Style.unit_spaced = Just False
2807 }
2808 , Amount.unit = "$"
2809 })
2810 ]
2811 }
2812 , Posting.nil
2813 { Posting.account = ["a","b","c"]
2814 , Posting.comments = ["first comment","second comment","third comment"]
2815 }
2816 ]
2817 })
2818 ~?=
2819 "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")
2820 , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
2821 ((Format.Ledger.Write.show False $
2822 Format.Ledger.Write.transaction $
2823 Transaction.nil
2824 { Transaction.dates=
2825 ( Time.ZonedTime
2826 (Time.LocalTime
2827 (Time.fromGregorian 2000 01 01)
2828 (Time.TimeOfDay 0 0 0))
2829 (Time.utc)
2830 , [] )
2831 , Transaction.description="some description"
2832 , Transaction.postings = Posting.from_List
2833 [ Posting.nil
2834 { Posting.account = ["A","B","C"]
2835 , Posting.amounts = Data.Map.fromList
2836 [ ("$", Amount.nil
2837 { Amount.quantity = 1
2838 , Amount.style = Amount.Style.nil
2839 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2840 , Amount.Style.unit_spaced = Just False
2841 }
2842 , Amount.unit = "$"
2843 })
2844 ]
2845 }
2846 , Posting.nil
2847 { Posting.account = ["AA","BB","CC"]
2848 , Posting.amounts = Data.Map.fromList
2849 [ ("$", Amount.nil
2850 { Amount.quantity = 123
2851 , Amount.style = Amount.Style.nil
2852 { Amount.Style.unit_side = Just Amount.Style.Side_Left
2853 , Amount.Style.unit_spaced = Just False
2854 }
2855 , Amount.unit = "$"
2856 })
2857 ]
2858 }
2859 ]
2860 })
2861 ~?=
2862 "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")
2863 ]
2864 ]
2865 ]
2866 ]
2867 ]