1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
6 import Control.Applicative (Applicative(..), (<*))
7 import Control.Arrow (right)
8 import Control.Monad.IO.Class (MonadIO(..))
11 import Data.Decimal (DecimalRaw(..))
12 import Data.Either (either, rights)
13 import Data.Function (($), (.), id, const)
14 import Data.Functor ((<$>))
15 import Data.List.NonEmpty (NonEmpty(..))
16 import qualified Data.Map.Strict as Map
17 import Data.Maybe (Maybe(..))
18 import Data.Monoid (Monoid(..), (<>))
19 import Data.Text (Text)
20 import qualified Data.Text as Text
21 import qualified Data.Time.Calendar as Time
22 import qualified Data.Time.LocalTime as Time
23 import Prelude (error)
25 import Test.Tasty.HUnit
26 import qualified Text.Parsec as R hiding
39 import qualified Text.Parsec.Combinator.CorrectSourcePosWithTab as R
40 import qualified Text.Parsec.Error.Custom as R
41 import qualified Text.Parsec.Pos as R
42 import Text.Show (Show(..))
44 import qualified Hcompta as H
45 import qualified Hcompta.JCC as JCC
48 tests = testGroup "Read"
49 [ testGroup "read_date" $
50 (let (==>) (txt::Text) =
51 testCase (Text.unpack txt) .
52 (@?=) (rights [R.runParserWithError
53 (JCC.read_date id Nothing <* R.eof) () "" txt]) in
55 [ Time.zonedTimeToUTC $
58 (Time.fromGregorian 2000 01 01)
59 (Time.TimeOfDay 0 0 0))
62 , "2000-01-01_12:34" ==>
63 [ Time.zonedTimeToUTC $
66 (Time.fromGregorian 2000 01 01)
67 (Time.TimeOfDay 12 34 0))
69 , "2000-01-01_12:34:56" ==>
70 [ Time.zonedTimeToUTC $
73 (Time.fromGregorian 2000 01 01)
74 (Time.TimeOfDay 12 34 56))
76 , "2000-01-01_12:34_CET" ==>
77 [ Time.zonedTimeToUTC $
80 (Time.fromGregorian 2000 01 01)
81 (Time.TimeOfDay 12 34 0))
82 (Time.TimeZone 60 True "CET") ]
83 , "2000-01-01_12:34+01:30" ==>
84 [ Time.zonedTimeToUTC $
87 (Time.fromGregorian 2000 01 01)
88 (Time.TimeOfDay 12 34 0))
89 (Time.TimeZone 90 False "+01:30") ]
90 , "2000-01-01_12:34:56_CET" ==>
91 [ Time.zonedTimeToUTC $
94 (Time.fromGregorian 2000 01 01)
95 (Time.TimeOfDay 12 34 56))
96 (Time.TimeZone 60 True "CET") ]
99 (let (==>) (txt::Text, def) =
100 testCase (Text.unpack txt) .
101 (@?=) (rights [R.runParserWithError
102 (JCC.read_date id (Just def) <* R.eof) () "" txt]) in
103 [ ("01-01", 2000) ==>
104 [ Time.zonedTimeToUTC $
107 (Time.fromGregorian 2000 01 01)
108 (Time.TimeOfDay 0 0 0))
111 , testGroup "read_account_section" $
112 let (==>) (txt::Text) b =
113 testCase (Text.unpack txt) $
114 (@?=) (rights [R.runParser
115 (JCC.read_account_section <* R.eof) () "" txt])
140 , testCase "\"A \"" $
142 (JCC.read_account_section)
147 , testGroup "read_account" $
148 let (==>) (txt::Text) =
149 testCase (Text.unpack txt) .
150 (@?=) (rights [R.runParser
151 (JCC.read_account <* R.eof) () "" txt]) in
155 , "/A" ==> [ "A":|[] ]
158 , "/A/B" ==> [ "A":|["B"] ]
159 , "/A/B/C" ==> [ "A":|["B","C"] ]
160 , "/Aa/Bbb/Cccc" ==> [ "Aa":|["Bbb", "Cccc"] ]
161 , "/A a / B b b / C c c c" ==> []
166 , testGroup "read_amount" $
167 let (==>) (txt::Text) =
168 testCase (Text.unpack txt) .
169 (@?=) (rights [R.runParser
170 (JCC.read_amount <* R.eof) () "" txt]) in
174 , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )]
177 , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )]
179 [( mempty { JCC.amount_style_fractioning = Just '.' }
180 , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )]
182 [( mempty { JCC.amount_style_fractioning = Just '.' }
183 , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )]
185 [( mempty { JCC.amount_style_fractioning = Just ',' }
186 , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )]
188 [( mempty { JCC.amount_style_fractioning = Just ',' }
189 , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )]
193 [( mempty { JCC.amount_style_fractioning = Just '.' }
194 , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )]
196 [( mempty { JCC.amount_style_fractioning = Just '.' }
197 , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )]
199 [( mempty { JCC.amount_style_fractioning = Just ',' }
200 , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )]
202 [( mempty { JCC.amount_style_fractioning = Just ',' }
203 , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )]
205 [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [1] }
206 , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )]
208 [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [2] }
209 , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )]
212 { JCC.amount_style_fractioning = Just '.'
213 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping ',' [3] }
214 , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )]
217 { JCC.amount_style_fractioning = Just ','
218 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3] }
219 , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )]
222 { JCC.amount_style_fractioning = Just '.'
223 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping ',' [3] }
224 , JCC.amount { JCC.amount_quantity = Decimal 2 100000 } )]
227 { JCC.amount_style_fractioning = Just ','
228 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3] }
229 , JCC.amount { JCC.amount_quantity = Decimal 2 100000 } )]
235 , JCC.amount { JCC.amount_quantity = Decimal 0 123 } )]
237 [( mempty { JCC.amount_style_fractioning = Just '.' }
238 , JCC.amount { JCC.amount_quantity = Decimal 1 12 } )]
240 [( mempty { JCC.amount_style_fractioning = Just ',' }
241 , JCC.amount { JCC.amount_quantity = Decimal 1 12 } )]
243 [( mempty { JCC.amount_style_fractioning = Just '.' }
244 , JCC.amount { JCC.amount_quantity = Decimal 2 1234 } )]
246 [( mempty { JCC.amount_style_fractioning = Just ',' }
247 , JCC.amount { JCC.amount_quantity = Decimal 2 1234 } )]
249 [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [1] }
250 , JCC.amount { JCC.amount_quantity = Decimal 0 12 } )]
252 [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [2] }
253 , JCC.amount { JCC.amount_quantity = Decimal 0 123 } )]
255 [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [3, 2] }
256 , JCC.amount { JCC.amount_quantity = Decimal 0 123456 } )]
257 , "1_23_456,7890_12345_678901" ==>
259 { JCC.amount_style_fractioning = Just ','
260 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [3, 2]
261 , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] }
262 , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )]
263 , "1_23_456.7890_12345_678901" ==>
265 { JCC.amount_style_fractioning = Just '.'
266 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [3, 2]
267 , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] }
268 , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )]
269 , "1,23,456.7890_12345_678901" ==>
271 { JCC.amount_style_fractioning = Just '.'
272 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping ',' [3, 2]
273 , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] }
274 , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )]
275 , "1.23.456,7890_12345_678901" ==>
277 { JCC.amount_style_fractioning = Just ','
278 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3, 2]
279 , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] }
280 , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )]
281 , "123456_78901_2345.678_90_1" ==>
283 { JCC.amount_style_fractioning = Just '.'
284 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6]
285 , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [3, 2] }
286 , JCC.amount { JCC.amount_quantity = Decimal 6 123456789012345678901 } )]
289 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left
290 , JCC.amount_style_unit_spaced = Just False }
292 { JCC.amount_quantity = Decimal 0 1
293 , JCC.amount_unit = "$" } )]
296 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right
297 , JCC.amount_style_unit_spaced = Just False }
299 { JCC.amount_quantity = Decimal 0 1
300 , JCC.amount_unit = "$" } )]
303 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left
304 , JCC.amount_style_unit_spaced = Just True }
306 { JCC.amount_quantity = Decimal 0 1
307 , JCC.amount_unit = "$" } )]
310 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right
311 , JCC.amount_style_unit_spaced = Just True }
313 { JCC.amount_quantity = Decimal 0 1
314 , JCC.amount_unit = "$" } )]
317 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left
318 , JCC.amount_style_unit_spaced = Just False }
320 { JCC.amount_quantity = Decimal 0 (-1)
321 , JCC.amount_unit = "$" } )]
324 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left
325 , JCC.amount_style_unit_spaced = Just False }
327 { JCC.amount_quantity = Decimal 0 1
328 , JCC.amount_unit = "4 2" } )]
331 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right
332 , JCC.amount_style_unit_spaced = Just False }
334 { JCC.amount_quantity = Decimal 0 1
335 , JCC.amount_unit = "4 2" } )]
338 { JCC.amount_style_fractioning = Just ','
339 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3]
340 , JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left
341 , JCC.amount_style_unit_spaced = Just False }
343 { JCC.amount_quantity = Decimal 2 100000
344 , JCC.amount_unit = "$" } )]
347 { JCC.amount_style_fractioning = Just ','
348 , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3]
349 , JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right
350 , JCC.amount_style_unit_spaced = Just False }
352 { JCC.amount_quantity = Decimal 2 100000
353 , JCC.amount_unit = "$" } )]
355 , testGroup "read_comment" $
356 let (==>) (txt::Text, end) =
357 testCase (Text.unpack txt) .
358 (@?=) (rights [R.runParser
359 (JCC.read_comment <* end) () "" txt]) in
360 [ ("; some comment", R.eof) ==> [" some comment"]
361 , ("; some comment \n", R.newline <* R.eof) ==> [ " some comment " ]
362 , ("; some comment \r\n", R.string "\r\n" <* R.eof) ==> [ " some comment " ]
364 , testGroup "read_comments" $
365 let (==>) (txt::Text, end) =
366 testCase (Text.unpack txt) .
367 (@?=) (rights [R.runParser
368 (JCC.read_comments <* end) () "" txt]) in
369 [ ("; some comment\n ; some other comment", R.eof) ==> [ [" some comment", " some other comment"] ]
370 , ("; some comment \n", R.string "\n" <* R.eof) ==> [ [" some comment "] ]
372 , testGroup "read_transaction_tag" $
373 let (==>) (txt::Text, end) =
374 testCase (Text.unpack txt) .
375 (@?=) ((\(H.Transaction_Tag t) -> t) <$>
377 (JCC.read_transaction_tag <* end) () "" txt]) in
378 [ ("#Name" , R.eof) ==> [ ("Name":|[], "") ]
379 , ("#Name:" , R.eof) ==> []
380 , ("#Name:name" , R.eof) ==> [ ("Name":|["name"], "") ]
381 , ("#Name=Value" , R.eof) ==> [ ("Name":|[], "Value") ]
382 , ("#Name = Value" , R.eof) ==> [ ("Name":|[], "Value") ]
383 , ("#Name=Value\n" , R.string "\n" <* R.eof) ==> [ ("Name":|[], "Value") ]
384 , ("#Name=Val ue" , R.eof) ==> [ ("Name":|[], "Val ue") ]
385 , ("#Name=," , R.eof) ==> [ ("Name":|[], ",") ]
386 , ("#Name=Val,ue" , R.eof) ==> [ ("Name":|[], "Val,ue") ]
387 , ("#Name=Val,ue:" , R.eof) ==> [ ("Name":|[], "Val,ue:") ]
388 , ("#Name=Val,ue :", R.eof) ==> [ ("Name":|[], "Val,ue :") ]
390 , testGroup "read_posting" $
391 let (==>) (txt::Text) =
393 ( JCC.context_read (const ()) JCC.journal
394 ::JCC.Context_Read () ()) in
395 testCase (Text.unpack txt) .
398 (const []) -- (error . show)
401 (JCC.read_posting <* R.eof) context_read "" txt) .
402 ((\p -> p { JCC.posting_sourcepos = R.newPos "" 1 1 }) <$>) in
403 [ "/A/B/C" ==> [JCC.posting ("A":|["B", "C"])]
404 , "/A/B/C $1" ==> [(JCC.posting ("A":|["B", "C"]))
405 { JCC.posting_amounts = Map.fromList [("$", 1)] }]
406 , "/A/B/C $1" ==> [(JCC.posting ("A":|["B", "C"]))
407 { JCC.posting_amounts = Map.fromList [("$", 1)] }]
408 , "/A/B/C 1€" ==> [(JCC.posting ("A":|["B", "C"]))
409 { JCC.posting_amounts = Map.fromList [("€", 1)] }]
410 , "/A/B/C $1; some comment" ==> [(JCC.posting ("A":|["B", "C"]))
411 { JCC.posting_amounts = Map.fromList [("$", 1)]
412 , JCC.posting_comments = [" some comment"] }]
413 , "/A/B/C; some comment" ==> [(JCC.posting ("A":|["B", "C"]))
414 { JCC.posting_amounts = Map.fromList []
415 , JCC.posting_comments = [" some comment"] }]
416 , "/A/B/C ; some comment" ==> [(JCC.posting ("A":|["B", "C"]))
417 { JCC.posting_amounts = Map.fromList []
418 , JCC.posting_comments = [" some comment"] }]
419 , "/A/B/C ; some comment\n ; some other comment" ==>
420 [(JCC.posting ("A":|["B", "C"]))
421 { JCC.posting_amounts = Map.fromList []
422 , JCC.posting_comments = [" some comment", " some other comment"] }]
423 , "/A/B/C $1 ; some comment" ==>
424 [(JCC.posting ("A":|["B", "C"]))
425 { JCC.posting_amounts = Map.fromList [("$", 1)]
426 , JCC.posting_comments = [" some comment"] }]
428 [(JCC.posting ("A":|["B", "C"]))
429 { JCC.posting_tags = H.Posting_Tags $
430 H.tag_from_List [ ("N":|[], "V") ] }]
431 , "/A/B/C #N:O=V" ==>
432 [(JCC.posting ("A":|["B", "C"]))
433 { JCC.posting_tags = H.Posting_Tags $
434 H.tag_from_List [ ("N":|["O"], "V") ] }]
435 , "/A/B/C #N=Val;ue" ==>
436 [(JCC.posting ("A":|["B", "C"]))
437 { JCC.posting_tags = H.Posting_Tags $
438 H.tag_from_List [ ("N":|[], "Val;ue") ] }]
439 , "/A/B/C #N=Val#ue" ==>
440 [(JCC.posting ("A":|["B", "C"]))
441 { JCC.posting_tags = H.Posting_Tags $
442 H.tag_from_List [ ("N":|[], "Val#ue") ] }]
443 , "/A/B/C #N=V ; some comment" ==>
444 [(JCC.posting ("A":|["B", "C"]))
445 { JCC.posting_tags = H.Posting_Tags $
446 H.tag_from_List [ ("N":|[], "V") ]
447 , JCC.posting_comments = [" some comment"] }]
448 , "/A/B/C #N=V #O" ==>
449 [(JCC.posting ("A":|["B", "C"]))
450 { JCC.posting_tags = H.Posting_Tags $
451 H.tag_from_List [ ("N":|[], "V"), ("O":|[], "") ] }]
452 , "/A/B/C #N#O" ==> []
453 , "/A/B/C #N; #O" ==>
454 [(JCC.posting ("A":|["B", "C"]))
455 { JCC.posting_tags = H.Posting_Tags $
456 H.tag_from_List [ ("N":|[], "") ]
457 , JCC.posting_comments = [" #O"] }]
459 [(JCC.posting ("A":|["B", "C"]))
460 { JCC.posting_tags = H.Posting_Tags $
461 H.tag_from_List [ ("N":|[], ""), ("O":|[], "") ] }]
462 , "/A/B/C \n #N=V" ==>
463 [(JCC.posting ("A":|["B", "C"]))
464 { JCC.posting_tags = H.Posting_Tags $
465 H.tag_from_List [ ("N":|[], "V") ] }]
466 , "/A/B/C ; some comment\n #N=V" ==>
467 [(JCC.posting ("A":|["B", "C"]))
468 { JCC.posting_comments = [" some comment"]
469 , JCC.posting_tags = H.Posting_Tags $
470 H.tag_from_List [ ("N":|[], "V") ] }]
471 , "/A/B/C ; some comment\n #N=V v\n #N2=V2 v2" ==>
472 [(JCC.posting ("A":|["B", "C"]))
473 { JCC.posting_comments = [" some comment"]
474 , JCC.posting_tags = H.Posting_Tags $
477 , ("N2":|[], "V2 v2") ] }]
478 , "/A/B/C\n #N=V\n #N=V2" ==>
479 [(JCC.posting ("A":|["B", "C"]))
480 { JCC.posting_tags = H.Posting_Tags $
485 , "/A/B/C\n #N=V\n #N2=V" ==>
486 [(JCC.posting ("A":|["B", "C"]))
487 { JCC.posting_tags = H.Posting_Tags $
493 , testGroup "read_transaction" $
494 let (==>) (txt::Text) =
496 ( JCC.context_read (const ()) JCC.journal
497 ::JCC.Context_Read () ()) in
498 testCase (Text.unpack txt) .
500 either (error . show) pure $
502 (JCC.read_transaction <* R.newline <* R.eof) context_read "" txt) .
503 ((\t -> t { JCC.transaction_sourcepos = R.newPos "" 1 1 }) <$>) in
505 [ "2000-01-01 some wording"
510 { JCC.transaction_dates=
511 ( Time.zonedTimeToUTC $
514 (Time.fromGregorian 2000 01 01)
515 (Time.TimeOfDay 0 0 0))
518 , JCC.transaction_wording="some wording"
519 , JCC.transaction_postings = JCC.postings_by_account
520 [ (JCC.posting ("A":|["B", "C"]))
521 { JCC.posting_amounts = Map.fromList [ ("$", 1) ]
522 , JCC.posting_sourcepos = R.newPos "" 2 2 }
523 , (JCC.posting ("a":|["b", "c"]))
524 { JCC.posting_amounts = Map.fromList [ ("$", -1) ]
525 , JCC.posting_sourcepos = R.newPos "" 3 2 }
529 [ "2000-01-01 some wording ; some comment"
530 , "; some other;comment"
531 , " ; some last comment"
536 { JCC.transaction_comments =
538 , " some other;comment"
539 , " some last comment"
541 , JCC.transaction_dates=
542 ( Time.zonedTimeToUTC $
545 (Time.fromGregorian 2000 01 01)
546 (Time.TimeOfDay 0 0 0))
549 , JCC.transaction_wording="some wording"
550 , JCC.transaction_postings = JCC.postings_by_account
551 [ (JCC.posting ("A":|["B", "C"]))
552 { JCC.posting_amounts = Map.fromList [ ("$", 1) ]
553 , JCC.posting_sourcepos = R.newPos "" 4 2 }
554 , (JCC.posting ("a":|["b", "c"]))
555 { JCC.posting_amounts = Map.fromList [ ("$", -1) ]
556 , JCC.posting_sourcepos = R.newPos "" 5 2 } ] }]
558 , testGroup "read_journal" $
559 let (==>) (txt::Text) e =
560 testCase (Text.unpack txt) $ do
563 right (\j -> j{JCC.journal_last_read_time=H.date_epoch}) <$>
564 R.runParserTWithError
565 (JCC.read_journal "" {-<* R.eof-})
566 ( JCC.context_read id JCC.journal
567 ::JCC.Context_Read (JCC.Charted JCC.Transaction)
568 [JCC.Charted JCC.Transaction])
570 (@?=) (rights [jnl]) e in
572 [ "2000-01-01 1° wording"
575 , "2000-01-02 2° wording"
580 { JCC.journal_content =
581 (JCC.Charted mempty <$>) $
583 { JCC.transaction_dates =
584 ( Time.zonedTimeToUTC $
587 (Time.fromGregorian 2000 01 02)
588 (Time.TimeOfDay 0 0 0))
591 , JCC.transaction_wording = "2° wording"
592 , JCC.transaction_postings = JCC.postings_by_account
593 [ (JCC.posting ("A":|["B", "C"]))
594 { JCC.posting_amounts = Map.fromList [ ("$", 1) ]
595 , JCC.posting_sourcepos = R.newPos "" 5 2
597 , (JCC.posting ("x":|["y", "z"]))
598 { JCC.posting_amounts = Map.fromList [ ("$", -1) ]
599 , JCC.posting_sourcepos = R.newPos "" 6 2
602 , JCC.transaction_sourcepos = R.newPos "" 4 1
605 { JCC.transaction_dates =
606 ( Time.zonedTimeToUTC $
609 (Time.fromGregorian 2000 01 01)
610 (Time.TimeOfDay 0 0 0))
613 , JCC.transaction_wording="1° wording"
614 , JCC.transaction_postings = JCC.postings_by_account
615 [ (JCC.posting ("A":|["B", "C"]))
616 { JCC.posting_amounts = Map.fromList [ ("$", 1) ]
617 , JCC.posting_sourcepos = R.newPos "" 2 2
619 , (JCC.posting ("a":|["b", "c"]))
620 { JCC.posting_amounts = Map.fromList [ ("$", -1) ]
621 , JCC.posting_sourcepos = R.newPos "" 3 2
624 , JCC.transaction_sourcepos = R.newPos "" 1 1
627 , JCC.journal_files = [""]
628 , JCC.journal_amount_styles = JCC.Amount_Styles $ Map.fromList
631 { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left
632 , JCC.amount_style_unit_spaced = Just False }