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