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