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