{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module Read.Test where import Control.Applicative (Applicative(..), (<*)) import Control.Arrow (right) import Control.Monad.IO.Class (MonadIO(..)) import Data.Bool import Data.Data () import Data.Decimal (DecimalRaw(..)) import Data.Either (either, rights) import Data.Function (($), (.), id, const) import Data.Functor ((<$>)) import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.Map.Strict as Map import Data.Maybe (Maybe(..)) import Data.Monoid (Monoid(..), (<>)) import Data.Text (Text) import qualified Data.Text as Text import qualified Data.Time.Calendar as Time import qualified Data.Time.LocalTime as Time import Prelude (error) import Test.Tasty import Test.Tasty.HUnit import qualified Text.Parsec as R hiding ( char , anyChar , crlf , newline , noneOf , oneOf , satisfy , space , spaces , string , tab ) import qualified Text.Parsec.Combinator.CorrectSourcePosWithTab as R import qualified Text.Parsec.Error.Custom as R import qualified Text.Parsec.Pos as R import Text.Show (Show(..)) import qualified Hcompta as H import qualified Hcompta.JCC as JCC tests :: TestTree tests = testGroup "Read" [ testGroup "read_date" $ (let (==>) (txt::Text) = testCase (Text.unpack txt) . (@?=) (rights [R.runParserWithError (JCC.read_date id Nothing <* R.eof) () "" txt]) in [ "2000-01-01" ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) ] , "2000/01/01" ==> [] , "2000-01-01_12:34" ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.utc) ] , "2000-01-01_12:34:56" ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 56)) (Time.utc) ] , "2000-01-01_12:34_CET" ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.TimeZone 60 True "CET") ] , "2000-01-01_12:34+01:30" ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 0)) (Time.TimeZone 90 False "+01:30") ] , "2000-01-01_12:34:56_CET" ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 12 34 56)) (Time.TimeZone 60 True "CET") ] , "2001-02-29" ==> [] ]) <> (let (==>) (txt::Text, def) = testCase (Text.unpack txt) . (@?=) (rights [R.runParserWithError (JCC.read_date id (Just def) <* R.eof) () "" txt]) in [ ("01-01", 2000) ==> [ Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc)] ]) , testGroup "read_account_section" $ let (==>) (txt::Text) b = testCase (Text.unpack txt) $ (@?=) (rights [R.runParser (JCC.read_account_section <* R.eof) () "" txt]) [txt | b] in [ "" ==> False , "A" ==> True , "AA" ==> True , " " ==> False , "/" ==> False , "A/" ==> False , "/A" ==> False , "A " ==> False , "A A" ==> False , "A " ==> False , "A\t" ==> False , "A \n" ==> False , "(A)A" ==> False , "( )A" ==> False , "(A) A" ==> False , "[ ] A" ==> False , "(A) " ==> False , "(A)" ==> False , "A(A)" ==> False , "[A]A" ==> False , "[A] A" ==> False , "[A] " ==> False , "[A]" ==> False , testCase "\"A \"" $ (rights [R.runParser (JCC.read_account_section) () "" ("A "::Text)]) @?= ["A"] ] , testGroup "read_account" $ let (==>) (txt::Text) = testCase (Text.unpack txt) . (@?=) (rights [R.runParser (JCC.read_account <* R.eof) () "" txt]) in [ "" ==> [] , "A" ==> [] , "A/" ==> [] , "/A" ==> [ "A":|[] ] , "A " ==> [] , " A" ==> [] , "/A/B" ==> [ "A":|["B"] ] , "/A/B/C" ==> [ "A":|["B","C"] ] , "/Aa/Bbb/Cccc" ==> [ "Aa":|["Bbb", "Cccc"] ] , "/A a / B b b / C c c c" ==> [] , "/A/ /C" ==> [] , "/A//C" ==> [] , "/A/B/(C)" ==> [] ] , testGroup "read_amount" $ let (==>) (txt::Text) = testCase (Text.unpack txt) . (@?=) (rights [R.runParser (JCC.read_amount <* R.eof) () "" txt]) in [ "" ==> [] , "0" ==> [( mempty , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )] , "00" ==> [( mempty , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )] , "0." ==> [( mempty { JCC.amount_style_fractioning = Just '.' } , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )] , ".0" ==> [( mempty { JCC.amount_style_fractioning = Just '.' } , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )] , "0," ==> [( mempty { JCC.amount_style_fractioning = Just ',' } , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )] , ",0" ==> [( mempty { JCC.amount_style_fractioning = Just ',' } , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )] , "0_" ==> [] , "_0" ==> [] , "0.0" ==> [( mempty { JCC.amount_style_fractioning = Just '.' } , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )] , "00.00" ==> [( mempty { JCC.amount_style_fractioning = Just '.' } , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )] , "0,0" ==> [( mempty { JCC.amount_style_fractioning = Just ',' } , JCC.amount { JCC.amount_quantity = Decimal 1 0 } )] , "00,00" ==> [( mempty { JCC.amount_style_fractioning = Just ',' } , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )] , "0_0" ==> [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [1] } , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )] , "00_00" ==> [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [2] } , JCC.amount { JCC.amount_quantity = Decimal 0 0 } )] , "0,000.00" ==> [( mempty { JCC.amount_style_fractioning = Just '.' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping ',' [3] } , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )] , "0.000,00" ==> [( mempty { JCC.amount_style_fractioning = Just ',' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3] } , JCC.amount { JCC.amount_quantity = Decimal 2 0 } )] , "1,000.00" ==> [( mempty { JCC.amount_style_fractioning = Just '.' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping ',' [3] } , JCC.amount { JCC.amount_quantity = Decimal 2 100000 } )] , "1.000,00" ==> [( mempty { JCC.amount_style_fractioning = Just ',' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3] } , JCC.amount { JCC.amount_quantity = Decimal 2 100000 } )] , "1,000.00." ==> [] , "1.000,00," ==> [] , "1,000.00_" ==> [] , "123" ==> [( mempty , JCC.amount { JCC.amount_quantity = Decimal 0 123 } )] , "1.2" ==> [( mempty { JCC.amount_style_fractioning = Just '.' } , JCC.amount { JCC.amount_quantity = Decimal 1 12 } )] , "1,2" ==> [( mempty { JCC.amount_style_fractioning = Just ',' } , JCC.amount { JCC.amount_quantity = Decimal 1 12 } )] , "12.34" ==> [( mempty { JCC.amount_style_fractioning = Just '.' } , JCC.amount { JCC.amount_quantity = Decimal 2 1234 } )] , "12,34" ==> [( mempty { JCC.amount_style_fractioning = Just ',' } , JCC.amount { JCC.amount_quantity = Decimal 2 1234 } )] , "1_2" ==> [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [1] } , JCC.amount { JCC.amount_quantity = Decimal 0 12 } )] , "1_23" ==> [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [2] } , JCC.amount { JCC.amount_quantity = Decimal 0 123 } )] , "1_23_456" ==> [( mempty { JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [3, 2] } , JCC.amount { JCC.amount_quantity = Decimal 0 123456 } )] , "1_23_456,7890_12345_678901" ==> [( mempty { JCC.amount_style_fractioning = Just ',' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [3, 2] , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] } , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )] , "1_23_456.7890_12345_678901" ==> [( mempty { JCC.amount_style_fractioning = Just '.' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [3, 2] , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] } , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )] , "1,23,456.7890_12345_678901" ==> [( mempty { JCC.amount_style_fractioning = Just '.' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping ',' [3, 2] , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] } , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )] , "1.23.456,7890_12345_678901" ==> [( mempty { JCC.amount_style_fractioning = Just ',' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3, 2] , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] } , JCC.amount { JCC.amount_quantity = Decimal 15 123456789012345678901 } )] , "123456_78901_2345.678_90_1" ==> [( mempty { JCC.amount_style_fractioning = Just '.' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '_' [4, 5, 6] , JCC.amount_style_grouping_fractional = Just $ JCC.Amount_Style_Grouping '_' [3, 2] } , JCC.amount { JCC.amount_quantity = Decimal 6 123456789012345678901 } )] , "$1" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 0 1 , JCC.amount_unit = "$" } )] , "1$" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 0 1 , JCC.amount_unit = "$" } )] , "$ 1" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left , JCC.amount_style_unit_spaced = Just True } , JCC.amount { JCC.amount_quantity = Decimal 0 1 , JCC.amount_unit = "$" } )] , "1 $" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right , JCC.amount_style_unit_spaced = Just True } , JCC.amount { JCC.amount_quantity = Decimal 0 1 , JCC.amount_unit = "$" } )] , "-$1" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 0 (-1) , JCC.amount_unit = "$" } )] , "\"4 2\"1" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 0 1 , JCC.amount_unit = "4 2" } )] , "1\"4 2\"" ==> [( mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 0 1 , JCC.amount_unit = "4 2" } )] , "$1.000,00" ==> [( mempty { JCC.amount_style_fractioning = Just ',' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3] , JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 2 100000 , JCC.amount_unit = "$" } )] , "1.000,00$" ==> [( mempty { JCC.amount_style_fractioning = Just ',' , JCC.amount_style_grouping_integral = Just $ JCC.Amount_Style_Grouping '.' [3] , JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Right , JCC.amount_style_unit_spaced = Just False } , JCC.amount { JCC.amount_quantity = Decimal 2 100000 , JCC.amount_unit = "$" } )] ] , testGroup "read_comment" $ let (==>) (txt::Text, end) = testCase (Text.unpack txt) . (@?=) (rights [R.runParser (JCC.read_comment <* end) () "" txt]) in [ ("; some comment", R.eof) ==> [" some comment"] , ("; some comment \n", R.newline <* R.eof) ==> [ " some comment " ] , ("; some comment \r\n", R.string "\r\n" <* R.eof) ==> [ " some comment " ] ] , testGroup "read_comments" $ let (==>) (txt::Text, end) = testCase (Text.unpack txt) . (@?=) (rights [R.runParser (JCC.read_comments <* end) () "" txt]) in [ ("; some comment\n ; some other comment", R.eof) ==> [ [" some comment", " some other comment"] ] , ("; some comment \n", R.string "\n" <* R.eof) ==> [ [" some comment "] ] ] , testGroup "read_transaction_tag" $ let (==>) (txt::Text, end) = testCase (Text.unpack txt) . (@?=) ((\(H.Transaction_Tag t) -> t) <$> rights [R.runParser (JCC.read_transaction_tag <* end) () "" txt]) in [ ("#Name" , R.eof) ==> [ ("Name":|[], "") ] , ("#Name:" , R.eof) ==> [] , ("#Name:name" , R.eof) ==> [ ("Name":|["name"], "") ] , ("#Name=Value" , R.eof) ==> [ ("Name":|[], "Value") ] , ("#Name = Value" , R.eof) ==> [ ("Name":|[], "Value") ] , ("#Name=Value\n" , R.string "\n" <* R.eof) ==> [ ("Name":|[], "Value") ] , ("#Name=Val ue" , R.eof) ==> [ ("Name":|[], "Val ue") ] , ("#Name=," , R.eof) ==> [ ("Name":|[], ",") ] , ("#Name=Val,ue" , R.eof) ==> [ ("Name":|[], "Val,ue") ] , ("#Name=Val,ue:" , R.eof) ==> [ ("Name":|[], "Val,ue:") ] , ("#Name=Val,ue :", R.eof) ==> [ ("Name":|[], "Val,ue :") ] ] , testGroup "read_posting" $ let (==>) (txt::Text) = let context_read = ( JCC.context_read (const ()) JCC.journal ::JCC.Context_Read () ()) in testCase (Text.unpack txt) . (@?=) ( either (const []) -- (error . show) pure $ R.runParserWithError (JCC.read_posting <* R.eof) context_read "" txt) . ((\p -> p { JCC.posting_sourcepos = R.newPos "" 1 1 }) <$>) in [ "/A/B/C" ==> [JCC.posting ("A":|["B", "C"])] , "/A/B/C $1" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [("$", 1)] }] , "/A/B/C $1" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [("$", 1)] }] , "/A/B/C 1€" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [("€", 1)] }] , "/A/B/C $1; some comment" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [("$", 1)] , JCC.posting_comments = [" some comment"] }] , "/A/B/C; some comment" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [] , JCC.posting_comments = [" some comment"] }] , "/A/B/C ; some comment" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [] , JCC.posting_comments = [" some comment"] }] , "/A/B/C ; some comment\n ; some other comment" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [] , JCC.posting_comments = [" some comment", " some other comment"] }] , "/A/B/C $1 ; some comment" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [("$", 1)] , JCC.posting_comments = [" some comment"] }] , "/A/B/C #N=V" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V") ] }] , "/A/B/C #N:O=V" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|["O"], "V") ] }] , "/A/B/C #N=Val;ue" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "Val;ue") ] }] , "/A/B/C #N=Val#ue" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "Val#ue") ] }] , "/A/B/C #N=V ; some comment" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V") ] , JCC.posting_comments = [" some comment"] }] , "/A/B/C #N=V #O" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V"), ("O":|[], "") ] }] , "/A/B/C #N#O" ==> [] , "/A/B/C #N; #O" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "") ] , JCC.posting_comments = [" #O"] }] , "/A/B/C #N #O" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], ""), ("O":|[], "") ] }] , "/A/B/C \n #N=V" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V") ] }] , "/A/B/C ; some comment\n #N=V" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_comments = [" some comment"] , JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V") ] }] , "/A/B/C ; some comment\n #N=V v\n #N2=V2 v2" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_comments = [" some comment"] , JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V v") , ("N2":|[], "V2 v2") ] }] , "/A/B/C\n #N=V\n #N=V2" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V") , ("N":|[], "V2") ] }] , "/A/B/C\n #N=V\n #N2=V" ==> [(JCC.posting ("A":|["B", "C"])) { JCC.posting_tags = H.Posting_Tags $ H.tag_from_List [ ("N":|[], "V") , ("N2":|[], "V") ] }] ] , testGroup "read_transaction" $ let (==>) (txt::Text) = let context_read = ( JCC.context_read (const ()) JCC.journal ::JCC.Context_Read () ()) in testCase (Text.unpack txt) . (@?=) ( either (error . show) pure $ R.runParserWithError (JCC.read_transaction <* R.newline <* R.eof) context_read "" txt) . ((\t -> t { JCC.transaction_sourcepos = R.newPos "" 1 1 }) <$>) in [ Text.unlines [ "2000-01-01 some wording" , " /A/B/C $1" , " /a/b/c $-1" ] ==> [JCC.transaction { JCC.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , JCC.transaction_wording="some wording" , JCC.transaction_postings = JCC.postings_by_account [ (JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [ ("$", 1) ] , JCC.posting_sourcepos = R.newPos "" 2 2 } , (JCC.posting ("a":|["b", "c"])) { JCC.posting_amounts = Map.fromList [ ("$", -1) ] , JCC.posting_sourcepos = R.newPos "" 3 2 } ] }] , Text.unlines [ "2000-01-01 some wording ; some comment" , "; some other;comment" , " ; some last comment" , " /A/B/C $1" , " /a/b/c" ] ==> [JCC.transaction { JCC.transaction_comments = [ " some comment" , " some other;comment" , " some last comment" ] , JCC.transaction_dates= ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , JCC.transaction_wording="some wording" , JCC.transaction_postings = JCC.postings_by_account [ (JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [ ("$", 1) ] , JCC.posting_sourcepos = R.newPos "" 4 2 } , (JCC.posting ("a":|["b", "c"])) { JCC.posting_amounts = Map.fromList [ ("$", -1) ] , JCC.posting_sourcepos = R.newPos "" 5 2 } ] }] ] , testGroup "read_journal" $ let (==>) (txt::Text) e = testCase (Text.unpack txt) $ do jnl <- liftIO $ right (\j -> j{JCC.journal_last_read_time=H.date_epoch}) <$> R.runParserTWithError (JCC.read_journal "" {-<* R.eof-}) ( JCC.context_read id JCC.journal ::JCC.Context_Read (JCC.Charted JCC.Transaction) [JCC.Charted JCC.Transaction]) "" (txt::Text) (@?=) (rights [jnl]) e in [ Text.unlines [ "2000-01-01 1° wording" , " /A/B/C $1" , " /a/b/c" , "2000-01-02 2° wording" , " /A/B/C $1" , " /x/y/z" ] ==> [ JCC.journal { JCC.journal_content = (JCC.Charted mempty <$>) $ [ JCC.transaction { JCC.transaction_dates = ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 02) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , JCC.transaction_wording = "2° wording" , JCC.transaction_postings = JCC.postings_by_account [ (JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [ ("$", 1) ] , JCC.posting_sourcepos = R.newPos "" 5 2 } , (JCC.posting ("x":|["y", "z"])) { JCC.posting_amounts = Map.fromList [ ("$", -1) ] , JCC.posting_sourcepos = R.newPos "" 6 2 } ] , JCC.transaction_sourcepos = R.newPos "" 4 1 } , JCC.transaction { JCC.transaction_dates = ( Time.zonedTimeToUTC $ Time.ZonedTime (Time.LocalTime (Time.fromGregorian 2000 01 01) (Time.TimeOfDay 0 0 0)) (Time.utc) , [] ) , JCC.transaction_wording="1° wording" , JCC.transaction_postings = JCC.postings_by_account [ (JCC.posting ("A":|["B", "C"])) { JCC.posting_amounts = Map.fromList [ ("$", 1) ] , JCC.posting_sourcepos = R.newPos "" 2 2 } , (JCC.posting ("a":|["b", "c"])) { JCC.posting_amounts = Map.fromList [ ("$", -1) ] , JCC.posting_sourcepos = R.newPos "" 3 2 } ] , JCC.transaction_sourcepos = R.newPos "" 1 1 } ] , JCC.journal_files = [""] , JCC.journal_amount_styles = JCC.Amount_Styles $ Map.fromList [ ( JCC.Unit "$" , mempty { JCC.amount_style_unit_side = Just JCC.Amount_Style_Side_Left , JCC.amount_style_unit_spaced = Just False } ) ] } ] ] ]