Ajout : Lib.TreeMap pour Calc.Balance.Expanded
authorJulien Moutinho <julm+hcompta@autogeree.net>
Tue, 5 May 2015 19:07:12 +0000 (21:07 +0200)
committerJulien Moutinho <julm+hcompta@autogeree.net>
Tue, 5 May 2015 19:21:07 +0000 (21:21 +0200)
cli/Hcompta/CLI/Command/Balance.hs
lib/Hcompta/Calc/Balance.hs
lib/Hcompta/Format/Ledger/Read.hs
lib/Hcompta/Format/Ledger/Write.hs
lib/Hcompta/Lib/TreeMap.hs [new file with mode: 0644]
lib/Hcompta/Model/Account.hs
lib/Hcompta/Model/Transaction/Posting.hs
lib/Test/Main.hs
lib/hcompta-lib.cabal

index 350d8aaface24598f42f480ed4bae03ebc2f34f5..dbbb683cdbd9b84b8ea504f1dfac39526c2d78cc 100644 (file)
@@ -1,9 +1,15 @@
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE TupleSections #-}
 module Hcompta.CLI.Command.Balance where
 
 import           Control.Monad.IO.Class (liftIO)
 import           Control.Monad.Trans.Except (runExceptT)
 import qualified Data.Either
+-- import qualified Data.Foldable
 import qualified Data.List
+import qualified Data.Map
+import qualified Data.Text.Lazy as TL
 import           System.Console.GetOpt
                  ( ArgDescr(..)
                  , OptDescr(..)
@@ -12,14 +18,21 @@ import           System.Console.GetOpt
 import           System.Environment as Env (getProgName)
 import           System.Exit (exitWith, ExitCode(..))
 import qualified System.IO as IO
+import Text.Show.Pretty (ppShow)
 
 import qualified Hcompta.CLI.Args as Args
 import qualified Hcompta.CLI.Context as Context
-import qualified Hcompta.CLI.Write as Write
 import qualified Hcompta.CLI.Format.Ledger as CLI.Ledger
-import qualified Hcompta.Calc.Balance
+import qualified Hcompta.CLI.Write as Write
+import qualified Hcompta.Calc.Balance as Balance
 import qualified Hcompta.Format.Ledger.Journal
-import qualified Hcompta.Format.Ledger.Read
+import qualified Hcompta.Format.Ledger.Read as Ledger.Read
+import qualified Hcompta.Format.Ledger.Write as Ledger.Write
+import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
+import qualified Hcompta.Lib.Leijen as W
+import           Hcompta.Lib.Leijen ((<>))
+import qualified Hcompta.Model.Amount as Amount
+import qualified Hcompta.Model.Transaction.Posting as Posting
 -- import qualified Hcompta.Format.Ledger.Write
 
 data Ctx
@@ -62,7 +75,7 @@ run context args = do
        CLI.Ledger.paths context $ ctx_input ctx
        >>= do mapM $ \path -> do
                liftIO $ runExceptT $
-                       Hcompta.Format.Ledger.Read.file path
+                       Ledger.Read.file path
                >>= \x -> case x of
                 Left  ko -> return $ Left (path, ko)
                 Right ok -> return $ Right ok
@@ -73,9 +86,82 @@ run context args = do
                        Write.fatal context $ ko
         ([], journals) -> do
                CLI.Ledger.equilibre context journals
-               putStrLn $ show $
+               let balance =
                        Data.List.foldl
-                        (\b j -> Hcompta.Calc.Balance.journal
+                        (\b j -> Balance.journal
                                 (Hcompta.Format.Ledger.Journal.to_Model j) b)
-                        Hcompta.Calc.Balance.nil
+                        Balance.nil
                         journals
+               Write.debug context $ ppShow $ balance
+               Write.debug context $ ppShow $
+                       Lib.TreeMap.flatten (const ()) (Balance.by_account balance)
+               let expanded = Balance.expand $ Balance.by_account balance
+               Write.debug context $ ppShow $ expanded
+               with_color <- Write.with_color context IO.stdout
+               Ledger.Write.put with_color IO.stdout $ do
+                       let (max_amount_length, accounts) = write_accounts expanded
+                       accounts <> do
+                       W.bold $ W.dullblack $
+                               W.text (TL.pack $ replicate max_amount_length '-') <> W.line <> do
+                       write_amounts max_amount_length $
+                               Data.Map.map Balance.amount $
+                               (Balance.by_unit balance)
+
+write_accounts :: Balance.Expanded -> (Int, W.Doc)
+write_accounts accounts = do
+       let max_amount_length =
+               uncurry (+) $
+               Lib.TreeMap.foldlWithKey
+                (\(len, plus) _k amounts ->
+                       ( Data.Map.foldr
+                                (max . Ledger.Write.amount_length)
+                                len (Balance.inclusive amounts)
+                       , if Data.Map.size (Balance.inclusive amounts) > 1
+                               then 2
+                               else plus
+                       ))
+                (0, 0) accounts
+       (max_amount_length,) $ do
+       Lib.TreeMap.foldlWithKey
+        (\doc account amounts ->
+               if Data.Map.null $ Balance.exclusive amounts
+               then doc
+               else
+                       doc <> Data.Map.foldl
+                        (\doc_ amount ->
+                               doc_ <>
+                               (if W.is_empty doc_
+                               then do
+                                       W.fill (max_amount_length - Ledger.Write.amount_length amount) W.empty <> do
+                                       Ledger.Write.amount amount <> do
+                                       W.space <> do
+                                       Ledger.Write.account Posting.Type_Regular account
+                               else do
+                                       (W.text "+" <> W.space) <> do
+                                       W.fill (max_amount_length - Ledger.Write.amount_length amount - 2) W.empty <> do
+                                       Ledger.Write.amount amount) <> do
+                               W.line
+                        ) W.empty (Balance.inclusive amounts)
+        )
+        W.empty accounts
+
+write_amounts :: Int -> Amount.By_Unit -> W.Doc
+write_amounts max_amount_length_ amounts = do
+       let max_amount_length =
+               Data.Map.foldr
+                (max . Ledger.Write.amount_length)
+                max_amount_length_ amounts
+       (if Data.Map.size amounts > 1
+               then W.space <> W.space
+               else W.empty) <> do
+       W.intercalate
+        (W.line <> W.text "+" <> W.space)
+        (\amount ->
+               let len =
+                       max_amount_length
+                       - Ledger.Write.amount_length amount
+                       - (if Data.Map.size amounts > 1 then 2 else 0) in
+               W.fill len W.empty <> do
+               Ledger.Write.amount amount)
+        amounts <> do
+       W.line
index c491c4d81cc2b9b0e8de8b7e709fee105b74504f..a5d557bfaa3a537bce79cfd004c1256264052a91 100644 (file)
@@ -9,10 +9,12 @@ import qualified Data.List
 import qualified Data.Map.Strict as Data.Map
 import           Data.Map.Strict (Map)
 import           Data.Typeable ()
+import           Data.Maybe (fromMaybe)
 import qualified GHC.Num
 
 import qualified Hcompta.Model as Model ()
 import qualified Hcompta.Model.Account as Account
+import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
 import           Hcompta.Model.Account (Account)
 import qualified Hcompta.Model.Amount as Amount
 import           Hcompta.Model.Amount (Amount, Unit)
@@ -32,7 +34,7 @@ data Balance
  } deriving (Data, Eq, Read, Show, Typeable)
 
 type By_Account
- = Map Account Account_Sum
+ = Lib.TreeMap.TreeMap Account.Name Account_Sum
 -- | A sum of 'Amount's,
 -- concerning a single 'Account'.
 type Account_Sum
@@ -53,13 +55,13 @@ data Unit_Sum
 nil :: Balance
 nil =
        Balance
-        { by_account = Data.Map.empty
+        { by_account = Lib.TreeMap.empty
         , by_unit    = Data.Map.empty
         }
 
 nil_By_Account :: By_Account
 nil_By_Account =
-       Data.Map.empty
+       Lib.TreeMap.empty
 
 nil_By_Unit :: By_Unit
 nil_By_Unit =
@@ -98,7 +100,7 @@ posting :: Posting -> Balance -> Balance
 posting post balance =
        balance
         { by_account =
-               Data.Map.insertWith
+               Lib.TreeMap.insert
                 (Data.Map.unionWith (GHC.Num.+))
                 (Posting.account post)
                 (Posting.amounts post)
@@ -177,7 +179,7 @@ union :: Balance -> Balance -> Balance
 union b0 b1 =
        b0
         { by_account =
-               Data.Map.unionWith
+               Lib.TreeMap.union
                 (Data.Map.unionWith (GHC.Num.+))
                 (by_account b0)
                 (by_account b1)
@@ -207,29 +209,26 @@ newtype Equilibre
 -- (i.e. now mapping to accounts __not__ involved to build the 'Unit_Sum').
 equilibre :: Balance -> Equilibre
 equilibre balance = do
-       let max_accounts = Data.Map.size $ by_account balance
-       Equilibre $ Data.Map.foldlWithKey
-        (\m unit Unit_Sum{amount, accounts} ->
-               if Amount.is_zero $ amount
-               then m
-               else
-                       case Data.Map.size accounts of
-                        n | n == max_accounts ->
-                               Data.Map.insert unit Unit_Sum{amount, accounts=Data.Map.empty} m
-                        _ -> do
-                               let d = Data.Map.map (const ()) $
-                                       Data.Map.difference (by_account balance) accounts
-                               Data.Map.insert unit Unit_Sum{amount, accounts=d} m
-        )
-        Data.Map.empty
-        (by_unit balance)
+       let all_accounts = Lib.TreeMap.flatten (const ()) (by_account balance)
+       let max_accounts = Data.Map.size all_accounts
+       Equilibre $
+               Data.Map.foldlWithKey
+                (\m unit Unit_Sum{amount, accounts} ->
+                       if Amount.is_zero amount
+                       then m
+                       else
+                               case Data.Map.size accounts of
+                                n | n == max_accounts ->
+                                       Data.Map.insert unit Unit_Sum{amount, accounts=Data.Map.empty} m
+                                _ -> do
+                                       let diff = Data.Map.difference all_accounts accounts
+                                       Data.Map.insert unit Unit_Sum{amount, accounts=diff} m
+                )
+                Data.Map.empty
+                (by_unit balance)
 
 -- ** Tests
 
--- | Return 'True' if and only if the given 'Equilibre' maps no 'Unit'.
-is_equilibrated :: Equilibre -> Bool
-is_equilibrated (Equilibre eq) = Data.Map.null eq
-
 -- | Return 'True' if and only if the given 'Equilibre' satisfies:
 --
 -- * 'is_equilibrated',
@@ -238,6 +237,10 @@ is_equilibrable :: Equilibre -> Bool
 is_equilibrable e@(Equilibre eq) =
        Data.Map.null eq || is_inferrable e
 
+-- | Return 'True' if and only if the given 'Equilibre' maps no 'Unit'.
+is_equilibrated :: Equilibre -> Bool
+is_equilibrated (Equilibre eq) = Data.Map.null eq
+
 -- | Return 'True' if and only if the given 'Equilibre'
 -- maps only to 'Unit_Sum's whose 'accounts'
 -- maps exactly one 'Account'.
@@ -259,8 +262,12 @@ is_non_inferrable (Equilibre eq) =
 -- * The 'Expanded' type
 
 -- | See 'expand'.
-newtype Expanded
- =      Expanded By_Account
+type Expanded = Lib.TreeMap.TreeMap Account.Name Account_Sum_Expanded
+data Account_Sum_Expanded
+ =   Account_Sum_Expanded
+ { inclusive :: Amount.By_Unit
+ , exclusive :: Amount.By_Unit
+ }
  deriving (Data, Eq, Read, Show, Typeable)
 
 -- | Return the given 'By_Account' with:
@@ -271,26 +278,17 @@ newtype Expanded
 -- added with any Amount.'Amount.By_Unit'
 -- of the 'Account's’ for which it is 'Account.ascending'.
 expand :: By_Account -> Expanded
-expand balance =
-       -- TODO: because (+) is associative
-       --       the complexity could be improved a bit
-       --       by only adding to the longest 'Account.ascending'
-       --       and reuse this result thereafter,
-       --       but coding this requires access
-       --       to the hidden constructors of 'Data.Map.Map',
-       --       which could be done through TemplateHaskell and lens:
-       --       https://stackoverflow.com/questions/24153577/pattern-matching-on-data-map-for-implementing-map
-       --
-       -- a0' = a0 + a1 + a2 + a3   <-- current calculus
-       --     = a0 + a1'            <-- improved calculus todo
-       -- a1' =      a1 + a2 + a3
-       --     =      a1 + a2'
-       -- a2' =           a2 + a3
-       -- a3' =                a3
-       Expanded $
-               Data.Map.foldrWithKey
-                (\account amt ->
-                       Account.fold (Account.ascending account)
-                        (\prefix -> Data.Map.insertWith (+) prefix amt))
-                balance
-                balance
+expand =
+       Lib.TreeMap.depth_first_map
+        (\descendants content ->
+               let exc = fromMaybe Data.Map.empty content in
+               Account_Sum_Expanded
+                { exclusive = exc
+                , inclusive =
+                       Data.Map.foldr
+                        ( Data.Map.unionWith (GHC.Num.+)
+                        . ( inclusive
+                                . fromMaybe (error "Oops, should not happen")
+                                . Lib.TreeMap.node_content) )
+                        exc descendants
+                })
index ad76439dff73c4ad4337b3ca5a0a879920cbe811..e7402b21ece426e195cbd8fef564ef475c76e239 100644 (file)
@@ -52,7 +52,7 @@ import qualified Hcompta.Lib.Path as Path
 
 data Context
  =   Context
- { context_account_prefix :: !Account
+ { context_account_prefix :: !(Maybe Account)
  , context_aliases_exact :: !(Data.Map.Map Account Account)
  , context_aliases_joker :: ![(Account.Joker, Account)]
  , context_aliases_regex :: ![(Regex, Account)]
@@ -65,7 +65,7 @@ data Context
 nil_Context :: Context
 nil_Context =
        Context
-        { context_account_prefix = []
+        { context_account_prefix = Nothing
         , context_aliases_exact = Data.Map.empty
         , context_aliases_joker = []
         , context_aliases_regex = []
@@ -93,6 +93,7 @@ account_name_sep = ':'
 account :: Stream s m Char => ParsecT s u m Account
 account = do
        R.notFollowedBy $ space_horizontal
+       Account.from_List <$> do
        many1_separated account_name $ R.char account_name_sep
 
 -- | Parse an Account.'Account.Name'.
index 4af9fc73e2540d5a950ef59eab95e55250c161eb..d83e936a184488ef0814db13dc7feae15edd70b0 100644 (file)
@@ -9,7 +9,9 @@ import           Control.Arrow ((***))
 import           Data.Decimal (DecimalRaw(..))
 import qualified Data.Char (isSpace)
 import           Data.Fixed (showFixed)
+import qualified Data.Foldable
 import qualified Data.List
+import qualified Data.List.NonEmpty
 import qualified Data.Map.Strict as Data.Map
 import           Data.Maybe (fromMaybe)
 import qualified Data.Text.Lazy as TL
@@ -65,9 +67,10 @@ account type_ =
                account_ :: Account -> Doc
                account_ acct =
                        W.align $ W.hcat $
-                               Data.List.intersperse
+                               Data.List.NonEmpty.toList $
+                               Data.List.NonEmpty.intersperse
                                 (W.bold $ W.dullblack $ W.char Read.account_name_sep)
-                                (Data.List.map account_name acct)
+                                (Data.List.NonEmpty.map account_name acct)
 
 account_name :: Account.Name -> Doc
 account_name = W.strict_text
@@ -76,9 +79,9 @@ account_name = W.strict_text
 
 account_length :: Posting.Type -> Account -> Int
 account_length type_ acct =
-       Data.List.foldl
+       Data.Foldable.foldl
         (\acc -> (1 +) . (acc +) . Text.length)
-        (if acct == [] then 0 else (- 1)) acct +
+        (- 1) acct +
        case type_ of
         Posting.Type_Regular -> 0
         Posting.Type_Virtual -> 2
diff --git a/lib/Hcompta/Lib/TreeMap.hs b/lib/Hcompta/Lib/TreeMap.hs
new file mode 100644 (file)
index 0000000..4881b5d
--- /dev/null
@@ -0,0 +1,246 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE NamedFieldPuns #-}
+
+-- | This module implements a tree of 'Data.Map.Map'.
+module Hcompta.Lib.TreeMap where
+
+import           Control.Applicative ((<$>), (<*>), pure)
+import           Data.Data (Data)
+import           Data.Foldable (Foldable(..))
+import qualified Data.List
+import qualified Data.List.NonEmpty
+import           Data.List.NonEmpty (NonEmpty(..))
+import qualified Data.Map
+import           Data.Monoid (Monoid(..))
+import           Data.Traversable (Traversable(..))
+import           Data.Typeable (Typeable)
+
+-- * The 'Path' type
+
+-- | A 'Path' is a non-empty list.
+type Path k = NonEmpty k
+
+path :: k -> [k] -> Path k
+path = (:|)
+
+list :: Path k -> [k]
+list = Data.List.NonEmpty.toList
+
+rev :: Path k -> Path k
+rev = Data.List.NonEmpty.reverse
+
+-- * The 'TreeMap' type
+
+type TreeMap k x = Data.Map.Map k (Node k x)
+data Ord k => Node k x
+ =   Node
+ { node_size        :: Int -- ^ The number of non-'Nothing' 'node_content's reachable from this 'Node'.
+ , node_content     :: Maybe x -- ^ Some content, or 'Nothing' if this 'Node' is intermediary.
+ , node_descendants :: TreeMap k x -- ^ Descendants 'Node's.
+ } deriving (Data, Eq, Read, Show, Typeable)
+
+instance (Ord k, Monoid v) => Monoid (Node k v) where
+       mempty =
+               Node
+                { node_content = Nothing
+                , node_size = 0
+                , node_descendants = mempty
+                }
+       mappend
+        Node{node_content=x0, node_descendants=m0}
+        Node{node_content=x1, node_descendants=m1} =
+               let m = union const m0 m1 in
+               let x = x0 `mappend` x1 in
+               Node
+                { node_content = x
+                , node_size = size m + maybe 0 (const 1) x
+                , node_descendants = union const m0 m1
+                }
+       -- mconcat = Data.List.foldr mappend mempty
+
+instance Ord k => Functor (Node k) where
+       fmap f Node{node_content=x, node_descendants=m, node_size} =
+               Node
+                { node_content = fmap f x
+                , node_descendants = Hcompta.Lib.TreeMap.map f m
+                , node_size
+                }
+
+instance Ord k => Foldable (Node k) where
+       foldMap f Node{node_content=Nothing, node_descendants=m} =
+               foldMap (foldMap f) m
+       foldMap f Node{node_content=Just x, node_descendants=m} =
+               f x `mappend` foldMap (foldMap f) m
+
+instance Ord k => Traversable (Node k) where
+       traverse f Node{node_content=Nothing, node_descendants=m, node_size} =
+               Node node_size <$> pure Nothing <*> traverse (traverse f) m
+       traverse f Node{node_content=Just x, node_descendants=m, node_size} =
+               Node node_size <$> (Just <$> f x) <*> traverse (traverse f) m
+
+-- * Contructors
+
+empty :: TreeMap k x
+empty = Data.Map.empty
+
+singleton :: Ord k => Path k -> x -> TreeMap k x
+singleton ks x = insert const ks x Data.Map.empty
+
+leaf :: Ord k => x -> Node k x
+leaf x =
+       Node
+        { node_content     = Just x
+        , node_descendants = Data.Map.empty
+        , node_size        = 1
+        }
+
+-- | Return the given 'TreeMap' associating the given 'Path' with the given content,
+-- merging contents if the given 'TreeMap' already associates the given 'Path'
+-- with a non-'Nothing' 'node_content'.
+insert :: Ord k => (x -> x -> x) -> Path k -> x -> TreeMap k x -> TreeMap k x
+insert merge (k:|[]) x m =
+       Data.Map.insertWith
+        (\_ Node{node_content=x1, node_descendants=m1, node_size=s1} ->
+               Node
+                { node_content = maybe (Just x) (Just . merge x) x1
+                , node_descendants = m1
+                , node_size = maybe (s1 + 1) (const s1) x1
+                })
+        k (leaf x) m
+insert merge (k:|k':ks) x m =
+       Data.Map.insertWith
+        (\_ Node{node_content=x1, node_descendants=m1} ->
+               let m' = insert merge (path k' ks) x m1 in
+               Node{node_content=x1, node_descendants=m', node_size=size m' + maybe 0 (const 1) x1})
+        k
+        (Node
+                { node_content = Nothing
+                , node_descendants = insert merge (path k' ks) x Data.Map.empty
+                , node_size = 1
+                })
+        m
+
+-- | Return a 'TreeMap' associating the given 'Path' to the given content,
+-- merging content of identical 'Path's (in respective order).
+from_List :: Ord k => (x -> x -> x) -> [(Path k, x)] -> TreeMap k x
+from_List merge = Data.List.foldl (\acc (p, x) -> insert merge p x acc) empty
+
+-- | Return a 'TreeMap' associating the same 'Path's as both given 'TreeMap's,
+-- merging contents (in respective order) when a 'Path' leads
+-- to a non-'Nothing' 'node_content' in both given 'TreeMap's.
+union :: Ord k => (x -> x -> x) -> TreeMap k x -> TreeMap k x -> TreeMap k x
+union merge =
+       Data.Map.unionWith
+        (\Node{node_content=x0, node_descendants=m0}
+          Node{node_content=x1, node_descendants=m1} ->
+               let m = union merge m0 m1 in
+               let x = maybe x1 (\x0' -> maybe (Just x0') (Just . merge x0') x1) x0 in
+               Node
+                { node_content = x
+                , node_descendants = m
+                , node_size = size m + maybe 0 (const 1) x
+                })
+
+-- | Return the 'union' of the given 'TreeMap's.
+--
+-- NOTE: use 'Data.List.foldl'' to reduce demand on the control-stack.
+unions :: Ord k => (x -> x -> x) -> [TreeMap k x] -> TreeMap k x
+unions merge ts = Data.List.foldl' (union merge) empty ts
+
+-- foldl' :: (a -> b -> a) -> a -> [b] -> a
+-- foldl' f = go
+--     where
+--             go z []     = z
+--             go z (x:xs) = z `seq` go (f z x) xs
+
+-- | Return the given 'TreeMap' with each non-'Nothing' 'node_content'
+-- mapped by the given function.
+map :: Ord k => (x -> y) -> TreeMap k x -> TreeMap k y
+map f =
+       Data.Map.map
+        (\n@Node{node_content=x, node_descendants=m} ->
+               n{ node_content=maybe Nothing (Just . f) x
+                , node_descendants=Hcompta.Lib.TreeMap.map f m
+                })
+
+-- | Return the given 'TreeMap' with each 'node_content'
+-- mapped by the given function supplied with
+-- the already mapped 'node_descendants' of the current 'Node'.
+depth_first_map :: Ord k => (TreeMap k y -> Maybe x -> y) -> TreeMap k x -> TreeMap k y
+depth_first_map f =
+       Data.Map.map
+        (\n@Node{node_content, node_descendants} ->
+               let m = depth_first_map f node_descendants in
+               let x = f m node_content in
+               n{ node_content = Just x
+                , node_descendants = m
+                , node_size = size m + 1
+                })
+
+-- * Extractors
+
+-- | Return the number of non-'Nothing' 'node_content's in the given 'TreeMap'.
+size :: Ord k => TreeMap k x -> Int
+size = Data.Map.foldr ((+) . node_size) 0
+
+-- | Return the content (if any) associated with the given 'Path'.
+find :: Ord k => Path k -> TreeMap k x -> Maybe x
+find (k:|[]) m = maybe Nothing node_content $ Data.Map.lookup k m
+find (k:|k':ks) m =
+       maybe Nothing (find (path k' ks) . node_descendants) $
+       Data.Map.lookup k m
+
+-- | Return the given accumulator folded by the given function
+-- applied on non-'Nothing' 'node_content's
+-- from left to right through the given 'TreeMap'.
+foldlWithKey :: Ord k => (a -> Path k -> x -> a) -> a -> TreeMap k x -> a
+foldlWithKey =
+       foldp []
+       where
+               foldp :: Ord k
+                => [k] -> (a -> Path k -> x -> a)
+                -> a -> TreeMap k x -> a
+               foldp p fct =
+                       Data.Map.foldlWithKey
+                        (\acc k Node{node_content, node_descendants} ->
+                               let p' = path k p in
+                               let acc' = maybe acc (fct acc (rev p')) node_content in
+                               foldp (k:p) fct acc' node_descendants)
+
+-- | Return the given accumulator folded by the given function
+-- applied on non-'Nothing' 'node_content's
+-- from right to left through the given 'TreeMap'.
+foldrWithKey :: Ord k => (Path k -> x -> a -> a) -> a -> TreeMap k x -> a
+foldrWithKey =
+       foldp []
+       where
+               foldp :: Ord k
+                => [k] -> (Path k -> x -> a -> a)
+                -> a -> TreeMap k x -> a
+               foldp p fct =
+                       Data.Map.foldrWithKey
+                        (\k Node{node_content, node_descendants} acc ->
+                               let p' = path k p in
+                               let acc' = foldp (k:p) fct acc node_descendants in
+                               maybe acc' (\x -> fct (rev p') x acc') node_content)
+
+-- | Return a 'Data.Map.Map' associating each 'Path'
+-- leading to a non-'Nothing' 'node_content' in the given 'TreeMap',
+-- with its content mapped by the given function.
+flatten :: Ord k => (x -> y) -> TreeMap k x -> Data.Map.Map (Path k) y
+flatten =
+       flat_map []
+       where
+               flat_map :: Ord k
+                => [k] -> (x -> y)
+                -> TreeMap k x
+                -> Data.Map.Map (Path k) y
+               flat_map p f m =
+                       Data.Map.unions $
+                       (
+                       Data.Map.mapKeysMonotonic (rev . flip path p) $
+                       Data.Map.mapMaybe (\Node{node_content=x} -> f <$> x) m
+                       ) :
+                       Data.Map.foldrWithKey
+                        (\k -> (:) . flat_map (k:p) f . node_descendants)
+                        [] m
index f39d108f821ddd3543bdba6f668bd6f04067f145..66922fca5b48e6b2098de92e643f56dcb9966786 100644 (file)
@@ -3,6 +3,9 @@ module Hcompta.Model.Account where
 
 import           Data.Data (Data)
 import qualified Data.List
+import qualified Data.List.NonEmpty
+import           Data.List.NonEmpty (NonEmpty(..))
+import           Data.Semigroup ((<>))
 import           Data.Typeable (Typeable)
 -- import qualified Text.Parsec as P
 -- import           Text.Parsec (Stream, ParsecT, (<|>), (<?>))
@@ -10,35 +13,39 @@ import           Data.Text (Text)
 
 -- import qualified Hcompta.Model.Account.Path as Path
 import           Hcompta.Lib.Regex (Regex)
+import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
 
 -- * The 'Account' type
 
-type Account = [Name]
-type Name = Text -- TODO: use Text?
+-- | An 'Account' is a non-empty list of 'Name'.
+type Account = NonEmpty Name
+type Name = Text
+type Map x = Lib.TreeMap.TreeMap Name x
 
-nil :: Account
-nil = []
+-- | Return the given 'Account' without its last 'Name' if any.
+ascending :: Account -> Maybe Account
+ascending (_:|[]) = Nothing
+ascending (n:|ns) = Just (n:|Data.List.init ns)
+{-# INLINE ascending #-}
 
--- | Return the given 'Account' without its last 'Name' is any.
-ascending :: Account -> Account
-ascending [] = []
-ascending [_] = []
-ascending (n:a) = n:ascending a
-
--- | Apply the given function to all the prefixes of the given 'Account'.
-fold :: Account -> (Account -> a -> a) -> a -> a
-fold = loop []
+-- | Apply the given function to all the prefixes
+-- of the given 'Account' (including itself).
+foldr :: Account -> (Account -> a -> a) -> a -> a
+foldr (n0:|n0s) = go [] n0s
        where
-               loop :: Account -> Account -> (Account -> a -> a) -> a -> a
-               loop _path [] _f acc = acc
-               loop path (name:account) f acc =
-                       let next = (Hcompta.Model.Account.++) path  [name] in
-                       loop next account f (f next acc)
+               go :: [Name] -> [Name] -> (Account -> a -> a) -> a -> a
+               go s [] f acc = f (n0:|s) acc
+               go s (n:ns) f acc =
+                       go ((Data.List.++) s [n]) ns f (f (n0:|s) acc)
 
 
 -- | Return the concatenation of the given 'Account'.
 (++) :: Account -> Account -> Account
-(++) = (Data.List.++)
+(++) = (<>)
+
+-- | Return an 'Account' from the given list.
+from_List :: [Name] -> Account
+from_List = Data.List.NonEmpty.fromList
 
 -- * The 'Joker' type
 
index b8779ec1d0be68cfffa44f6a91fd77085bdecefb..60590703b095f891ecbad8be4ca087bc1e2dfa54 100644 (file)
@@ -43,10 +43,10 @@ data Type
 
 -- ** Convenient constructors
 
-nil :: Posting
-nil =
+nil :: Account -> Posting
+nil acct =
        Posting
-        { account = []
+        { account = acct
         , amounts = Data.Map.empty
         , comments = []
         , dates = []
index 61daea1cf7aee3ad4030e0862963079729ed5232..04d47f538da96c51dcdc1bb616ae69862f545501 100644 (file)
@@ -11,6 +11,7 @@ import           Control.Monad.IO.Class (liftIO)
 import           Data.Decimal (DecimalRaw(..))
 import qualified Data.Either
 import qualified Data.List
+import           Data.List.NonEmpty (NonEmpty(..))
 import qualified Data.Map.Strict as Data.Map
 import           Data.Text (Text)
 import qualified Data.Time.Calendar  as Time
@@ -29,6 +30,7 @@ import qualified Hcompta.Calc.Balance as Calc.Balance
 import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
 import qualified Hcompta.Format.Ledger.Journal as Format.Ledger.Journal
 import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
+import qualified Hcompta.Lib.TreeMap as Lib.TreeMap
 
 --instance Eq Text.Parsec.ParseError where
 -- (==) = const (const False)
@@ -41,25 +43,21 @@ test_Hcompta =
        TestList
         [ "Model" ~: TestList
                 [ "Account" ~: TestList
-                        [ "fold" ~: TestList
-                                [ "[] = []" ~:
-                                       (reverse $ Account.fold [] (:) []) ~?= []
-                                , "[A] = [[A]]" ~:
-                                       (reverse $ Account.fold ["A"] (:) []) ~?= [["A"]]
-                                , "[A, B] = [[A], [A, B]]" ~:
-                                       (reverse $ Account.fold ["A", "B"] (:) []) ~?= [["A"], ["A", "B"]]
-                                , "[A, B, C] = [[A], [A, B], [A, B, C]]" ~:
-                                       (reverse $ Account.fold ["A", "B", "C"] (:) []) ~?= [["A"], ["A", "B"], ["A", "B", "C"]]
+                        [ "foldr" ~: TestList
+                                [ "[A]" ~:
+                                       (reverse $ Account.foldr ("A":|[]) (:) []) ~?= ["A":|[]]
+                                , "[A, B]" ~:
+                                       (reverse $ Account.foldr ("A":|["B"]) (:) []) ~?= ["A":|[], "A":|["B"]]
+                                , "[A, B, C]" ~:
+                                       (reverse $ Account.foldr ("A":|["B", "C"]) (:) []) ~?= ["A":|[], "A":|["B"], "A":|["B", "C"]]
                                 ]
                         , "ascending" ~: TestList
-                                [ "[] = []" ~:
-                                       Account.ascending [] ~?= []
-                                , "[A] = []" ~:
-                                       Account.ascending ["A"] ~?= []
-                                , "[A, B] = [A]" ~:
-                                       Account.ascending ["A", "B"] ~?= ["A"]
-                                , "[A, B, C] = [A, B]" ~:
-                                       Account.ascending ["A", "B", "C"] ~?= ["A", "B"]
+                                [ "[A]" ~:
+                                       Account.ascending ("A":|[]) ~?= Nothing
+                                , "[A, B]" ~:
+                                       Account.ascending ("A":|["B"]) ~?= Just ("A":|[])
+                                , "[A, B, C]" ~:
+                                       Account.ascending ("A":|["B", "C"]) ~?= Just ("A":|["B"])
                                 ]
                         ]
                 , "Amount" ~: TestList
@@ -125,23 +123,22 @@ test_Hcompta =
                         [ "posting" ~: TestList
                                 [ "[A+$1] = A+$1 & $+1" ~:
                                         (Calc.Balance.posting
-                                                Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
+                                                (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
                                                         }
                                                 Calc.Balance.nil)
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
                                                        Data.List.map Calc.Balance.assoc_unit_sum $
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -149,27 +146,25 @@ test_Hcompta =
                                         (Data.List.foldl
                                                 (flip Calc.Balance.posting)
                                                 Calc.Balance.nil
-                                                [ Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
+                                                [ (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
                                                         }
-                                                , Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
+                                                , (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
                                                         }
                                                 ])
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 0 ]) ]
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ]) ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
                                                        Data.List.map Calc.Balance.assoc_unit_sum $
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -177,32 +172,30 @@ test_Hcompta =
                                         (Data.List.foldl
                                                 (flip Calc.Balance.posting)
                                                 Calc.Balance.nil
-                                                [ Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
+                                                [ (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
                                                         }
-                                                , Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.eur $ -1 ]
+                                                , (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.eur $ -1 ]
                                                         }
                                                 ])
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1, Amount.eur $ -1 ]) ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
                                                        Data.List.map Calc.Balance.assoc_unit_sum $
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ -1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -210,21 +203,19 @@ test_Hcompta =
                                         (Data.List.foldl
                                                 (flip Calc.Balance.posting)
                                                 Calc.Balance.nil
-                                                [ Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
+                                                [ (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ 1 ]
                                                         }
-                                                , Posting.nil
-                                                        { Posting.account=["B"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
+                                                , (Posting.nil ("B":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ -1 ]
                                                         }
                                                 ])
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                        , (["B"], Amount.from_List [ Amount.usd $ -1 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -232,7 +223,7 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -240,20 +231,18 @@ test_Hcompta =
                                         (Data.List.foldl
                                                 (flip Calc.Balance.posting)
                                                 Calc.Balance.nil
-                                                [ Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
+                                                [ (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2 ]
                                                         }
-                                                , Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
+                                                , (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2 ]
                                                         }
                                                 ])
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -261,12 +250,12 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -274,21 +263,19 @@ test_Hcompta =
                                         (Data.List.foldl
                                                 (flip Calc.Balance.posting)
                                                 Calc.Balance.nil
-                                                [ Posting.nil
-                                                        { Posting.account=["A"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
+                                                [ (Posting.nil ("A":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ 1, Amount.eur $ 2, Amount.gbp $ 3 ]
                                                         }
-                                                , Posting.nil
-                                                        { Posting.account=["B"]
-                                                        , Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
+                                                , (Posting.nil ("B":|[]))
+                                                        { Posting.amounts=Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ]
                                                         }
                                                 ])
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $  1, Amount.eur $  2, Amount.gbp $  3 ])
-                                                        , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $  1, Amount.eur $  2, Amount.gbp $  3 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -296,17 +283,17 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.gbp $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -322,44 +309,44 @@ test_Hcompta =
                                         Calc.Balance.union
                                                 (Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
                                                                Data.List.map Calc.Balance.assoc_unit_sum $
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.usd $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["A"]]
+                                                                        ["A":|[]]
                                                                 }
                                                                ]
                                                         })
                                                 (Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
                                                                Data.List.map Calc.Balance.assoc_unit_sum $
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.usd $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["A"]]
+                                                                        ["A":|[]]
                                                                 }
                                                                ]
                                                         })
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 2 ]) ]
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 2 ]) ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
                                                        Data.List.map Calc.Balance.assoc_unit_sum $
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 2
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -367,45 +354,45 @@ test_Hcompta =
                                         Calc.Balance.union
                                                 (Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
                                                                Data.List.map Calc.Balance.assoc_unit_sum $
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.usd $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["A"]]
+                                                                        ["A":|[]]
                                                                 }
                                                                ]
                                                         })
                                                 (Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["B"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
                                                                Data.List.map Calc.Balance.assoc_unit_sum $
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.usd $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["B"]]
+                                                                        ["B":|[]]
                                                                 }
                                                                ]
                                                         })
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                        , (["B"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
                                                        Data.List.map Calc.Balance.assoc_unit_sum $
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 2
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -413,163 +400,217 @@ test_Hcompta =
                                         Calc.Balance.union
                                                 (Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ]
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
                                                                Data.List.map Calc.Balance.assoc_unit_sum $
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.usd $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["A"]]
+                                                                        ["A":|[]]
                                                                 }
                                                                ]
                                                         })
                                                 (Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["B"], Amount.from_List [ Amount.eur $ 1 ]) ]
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
                                                                Data.List.map Calc.Balance.assoc_unit_sum $
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.eur $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["B"]]
+                                                                        ["B":|[]]
                                                                 }
                                                                ]
                                                         })
                                         ~?=
                                         Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                        , (["B"], Amount.from_List [ Amount.eur $ 1 ]) ]
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.eur $ 1 ]) ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
                                                        Data.List.map Calc.Balance.assoc_unit_sum $
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["B"]]
+                                                                ["B":|[]]
                                                         }
                                                        ]
                                                 }
                                 ]
                         , "expand" ~: TestList
-                                [ "nil_By_Account = nil_By_Account" ~:
+                                [ "nil_By_Account" ~:
                                         Calc.Balance.expand
                                                 Calc.Balance.nil_By_Account
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Calc.Balance.nil_By_Account)
+                                        Lib.TreeMap.empty
                                 , "A+$1 = A+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ]) ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                ])
                                 , "A/A+$1 = A+$1 A/A+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|["A"], Amount.from_List [ Amount.usd $ 1 ]) ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List []
+                                                        })
+                                                , ("A":|["A"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                ])
                                 , "A/B+$1 = A+$1 A/B+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ]) ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List []
+                                                        })
+                                                , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                ])
                                 , "A/B/C+$1 = A+$1 A/B+$1 A/B/C+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List []
+                                                        })
+                                                , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List []
+                                                        })
+                                                , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                ])
                                 , "A+$1 A/B+$1 = A+$2 A/B+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
+                                                ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 2 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                ])
                                 , "A+$1 A/B+$1 A/B/C+$1 = A+$3 A/B+$2 A/B/C+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
                                                 ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 3 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 2 ])
-                                                , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
                                                 ])
                                 , "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" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B", "C"], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
                                                 ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 4 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 3 ])
-                                                , (["A", "B", "C"], Amount.from_List [ Amount.usd $ 2 ])
-                                                , (["A", "B", "C", "D"], Amount.from_List [ Amount.usd $ 1 ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 4 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B", "C"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 2 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B", "C", "D"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
                                                 ])
-                                , "A+$1 A/B+$1 B/A+$1 = A+$2 A/B+$1 B/A+$1" ~:
+                                , "A+$1 A/B+$1 A/BB+$1 AA/B+$1 = A+$3 A/B+$1 A/BB+$1 AA+$1 AA/B+$1" ~:
                                         Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
-                                        ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 2 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
-                                , "A+$1 A/B+$1 B/A+$1 = A+$2 A/B+$1 B/A+$1" ~:
-                                        Calc.Balance.expand
-                                               (Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                               (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["B"], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("A":|["BB"], Amount.from_List [ Amount.usd $ 1 ])
+                                                , ("AA":|["B"], Amount.from_List [ Amount.usd $ 1 ])
+                                                ])
                                         ~?=
-                                        (Calc.Balance.Expanded $
-                                               Data.Map.fromList
-                                                [ (["A"], Amount.from_List [ Amount.usd $ 2 ])
-                                                , (["A", "B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["B"], Amount.from_List [ Amount.usd $ 1 ])
-                                                , (["B", "A"], Amount.from_List [ Amount.usd $ 1 ]) ])
+                                        (Lib.TreeMap.from_List const
+                                                [ ("A":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 3 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("A":|["BB"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                , ("AA":|[], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List []
+                                                        })
+                                                , ("AA":|["B"], Calc.Balance.Account_Sum_Expanded
+                                                        { Calc.Balance.inclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        , Calc.Balance.exclusive = Amount.from_List [ Amount.usd $ 1 ]
+                                                        })
+                                                ])
                                 ]
                         , "is_equilibrable" ~: TestList
                                 [ "nil" ~: TestCase $
@@ -583,8 +624,8 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 0 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 0 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -592,7 +633,7 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -602,8 +643,8 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -611,7 +652,7 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -621,8 +662,8 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 0, Amount.eur $ 0 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -630,12 +671,12 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        ]
                                                 }
@@ -645,9 +686,9 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $  1 ])
-                                                        , (["B"], Amount.from_List [ Amount.usd $ -1 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $  1 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.usd $ -1 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -655,7 +696,7 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -665,9 +706,9 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                 Calc.Balance.Balance
                                                         { Calc.Balance.by_account =
-                                                               Data.Map.fromList
-                                                                [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                                , (["B"], Amount.from_List [])
+                                                               Lib.TreeMap.from_List const
+                                                                [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                                , ("B":|[], Amount.from_List [])
                                                                 ]
                                                         , Calc.Balance.by_unit =
                                                                Data.Map.fromList $
@@ -675,7 +716,7 @@ test_Hcompta =
                                                                [ Calc.Balance.Unit_Sum
                                                                 { Calc.Balance.amount = Amount.usd $ 1
                                                                 , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                        [["A"]]
+                                                                        ["A":|[]]
                                                                 }
                                                                ]
                                                         }
@@ -685,9 +726,9 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                        , (["B"], Amount.from_List [ Amount.eur $ 1 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.eur $ 1 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -695,12 +736,12 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"]]
+                                                                ["A":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["B"]]
+                                                                ["B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -710,9 +751,9 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $ 1 ])
-                                                        , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $ 1 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ 1 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -720,12 +761,12 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 1
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["B"]]
+                                                                ["B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -735,9 +776,9 @@ test_Hcompta =
                                                Calc.Balance.equilibre $
                                                Calc.Balance.Balance
                                                 { Calc.Balance.by_account =
-                                                       Data.Map.fromList
-                                                        [ (["A"], Amount.from_List [ Amount.usd $  1, Amount.eur $  2, Amount.gbp $  3 ])
-                                                        , (["B"], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
+                                                       Lib.TreeMap.from_List const
+                                                        [ ("A":|[], Amount.from_List [ Amount.usd $  1, Amount.eur $  2, Amount.gbp $  3 ])
+                                                        , ("B":|[], Amount.from_List [ Amount.usd $ -1, Amount.eur $ -2, Amount.gbp $ -3 ])
                                                         ]
                                                 , Calc.Balance.by_unit =
                                                        Data.Map.fromList $
@@ -745,17 +786,17 @@ test_Hcompta =
                                                        [ Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.usd $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.eur $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        , Calc.Balance.Unit_Sum
                                                         { Calc.Balance.amount = Amount.gbp $ 0
                                                         , Calc.Balance.accounts = Data.Map.fromList $ Data.List.map (,())
-                                                                [["A"], ["B"]]
+                                                                ["A":|[], "B":|[]]
                                                         }
                                                        ]
                                                 }
@@ -935,7 +976,7 @@ test_Hcompta =
                                                         (Format.Ledger.Read.account <* P.eof)
                                                         () "" ("A"::Text)])
                                                 ~?=
-                                                [["A"]]
+                                                ["A":|[]]
                                         , "\"A:\" = Left" ~:
                                                 (Data.Either.rights $
                                                        [P.runParser
@@ -970,35 +1011,35 @@ test_Hcompta =
                                                         (Format.Ledger.Read.account <* P.eof)
                                                         () "" ("A:B"::Text)])
                                                 ~?=
-                                                [["A", "B"]]
+                                                ["A":|["B"]]
                                         , "\"A:B:C\" = Right [\"A\", \"B\", \"C\"]" ~:
                                                 (Data.Either.rights $
                                                        [P.runParser
                                                         (Format.Ledger.Read.account <* P.eof)
                                                         () "" ("A:B:C"::Text)])
                                                 ~?=
-                                                [["A", "B", "C"]]
+                                                ["A":|["B", "C"]]
                                         , "\"Aa:Bbb:Cccc\" = Right [\"Aa\", \"Bbb\", \":Cccc\"]" ~:
                                                 (Data.Either.rights $
                                                        [P.runParser
                                                         (Format.Ledger.Read.account <* P.eof)
                                                         () "" ("Aa:Bbb:Cccc"::Text)])
                                                 ~?=
-                                                [["Aa", "Bbb", "Cccc"]]
+                                                ["Aa":|["Bbb", "Cccc"]]
                                         , "\"A a : B b b : C c c c\" = Right [\"A a \", \" B b b \", \": C c c c\"]" ~:
                                                 (Data.Either.rights $
                                                        [P.runParser
                                                         (Format.Ledger.Read.account <* P.eof)
                                                         () "" ("A a : B b b : C c c c"::Text)])
                                                 ~?=
-                                                [["A a ", " B b b ", " C c c c"]]
+                                                ["A a ":|[" B b b ", " C c c c"]]
                                         , "\"A: :C\" = Right [\"A\", \" \", \"C\"]" ~:
                                                 (Data.Either.rights $
                                                        [P.runParser
                                                         (Format.Ledger.Read.account <* P.eof)
                                                         () "" ("A: :C"::Text)])
                                                 ~?=
-                                                [["A", " ", "C"]]
+                                                ["A":|[" ", "C"]]
                                         , "\"A::C\" = Left" ~:
                                                 (Data.Either.rights $
                                                        [P.runParser
@@ -1888,9 +1929,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
                                                 ~?=
-                                                [ ( Posting.nil
-                                                                { Posting.account = ["A","B","C"]
-                                                                , Posting.sourcepos = P.newPos "" 1 1
+                                                [ ( (Posting.nil ("A":|["B", "C"]))
+                                                                { Posting.sourcepos = P.newPos "" 1 1
                                                                 }
                                                         , Posting.Type_Regular
                                                         )
@@ -1902,9 +1942,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.sourcepos = P.newPos "" 1 1
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.sourcepos = P.newPos "" 1 1
                                                         , Posting.status = True
                                                         }
                                                 ]
@@ -1915,9 +1954,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList []
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList []
                                                         , Posting.comments = []
                                                         , Posting.dates = []
                                                         , Posting.status = True
@@ -1932,9 +1970,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C $1"]
-                                                        , Posting.sourcepos = P.newPos "" 1 1
+                                                [ (Posting.nil ("A":|["B","C $1"]))
+                                                        { Posting.sourcepos = P.newPos "" 1 1
                                                         }
                                                 ]
                                         , " A:B:C  $1 = Right A:B:C  $1" ~:
@@ -1944,9 +1981,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C  $1"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList
                                                                 [ ("$", Amount.nil
                                                                         { Amount.quantity = 1
                                                                         , Amount.style = Amount.Style.nil
@@ -1966,9 +2002,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C  $1 + 1€"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList
                                                                 [ ("$", Amount.nil
                                                                         { Amount.quantity = 1
                                                                         , Amount.style = Amount.Style.nil
@@ -1996,9 +2031,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C  $1 + 1$"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList
                                                                 [ ("$", Amount.nil
                                                                         { Amount.quantity = 2
                                                                         , Amount.style = Amount.Style.nil
@@ -2018,9 +2052,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C  $1 + 1$ + 1$"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList
                                                                 [ ("$", Amount.nil
                                                                         { Amount.quantity = 3
                                                                         , Amount.style = Amount.Style.nil
@@ -2040,9 +2073,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList []
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList []
                                                         , Posting.comments = [" some comment"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         }
@@ -2054,9 +2086,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n  ; some other comment"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList []
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList []
                                                         , Posting.comments = [" some comment", " some other comment"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         }
@@ -2068,9 +2099,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C  $1 ; some comment"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.amounts = Data.Map.fromList
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.amounts = Data.Map.fromList
                                                                 [ ("$", Amount.nil
                                                                         { Amount.quantity = 1
                                                                         , Amount.style = Amount.Style.nil
@@ -2091,9 +2121,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.comments = [" N:V"]
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.comments = [" N:V"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         , Posting.tags = Data.Map.fromList
                                                                 [ ("N", ["V"])
@@ -2107,9 +2136,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.comments = [" some comment N:V"]
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.comments = [" some comment N:V"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         , Posting.tags = Data.Map.fromList
                                                                 [ ("N", ["V"])
@@ -2123,9 +2151,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting )
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.comments = [" some comment N:V v, N2:V2 v2"]
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.comments = [" some comment N:V v, N2:V2 v2"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         , Posting.tags = Data.Map.fromList
                                                                 [ ("N", ["V v"])
@@ -2140,9 +2167,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.comments = [" N:V", " N:V2"]
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.comments = [" N:V", " N:V2"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         , Posting.tags = Data.Map.fromList
                                                                 [ ("N", ["V", "V2"])
@@ -2156,9 +2182,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.comments = [" N:V", " N2:V"]
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.comments = [" N:V", " N2:V"]
                                                         , Posting.sourcepos = P.newPos "" 1 1
                                                         , Posting.tags = Data.Map.fromList
                                                                 [ ("N", ["V"])
@@ -2173,9 +2198,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
                                                 ~?=
-                                                [ Posting.nil
-                                                        { Posting.account = ["A","B","C"]
-                                                        , Posting.comments = [" date:2001/01/01"]
+                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                        { Posting.comments = [" date:2001/01/01"]
                                                         , Posting.dates =
                                                                 [ Time.ZonedTime
                                                                         (Time.LocalTime
@@ -2195,9 +2219,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
                                                 ~?=
-                                                [ ( Posting.nil
-                                                                { Posting.account = ["A","B","C"]
-                                                                , Posting.sourcepos = P.newPos "" 1 1
+                                                [ ( (Posting.nil ("A":|["B", "C"]))
+                                                                { Posting.sourcepos = P.newPos "" 1 1
                                                                 }
                                                         , Posting.Type_Virtual
                                                         )
@@ -2208,9 +2231,8 @@ test_Hcompta =
                                                         (Format.Ledger.Read.posting <* P.eof)
                                                                Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
                                                 ~?=
-                                                [ ( Posting.nil
-                                                                { Posting.account = ["A","B","C"]
-                                                                , Posting.sourcepos = P.newPos "" 1 1
+                                                [ ( (Posting.nil ("A":|["B", "C"]))
+                                                                { Posting.sourcepos = P.newPos "" 1 1
                                                                 }
                                                         , Posting.Type_Virtual_Balanced
                                                         )
@@ -2233,9 +2255,8 @@ test_Hcompta =
                                                                 , [] )
                                                         , Transaction.description="some description"
                                                         , Transaction.postings = Posting.from_List
-                                                                [ Posting.nil
-                                                                        { Posting.account = ["A","B","C"]
-                                                                        , Posting.amounts = Data.Map.fromList
+                                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                                        { Posting.amounts = Data.Map.fromList
                                                                                 [ ("$", Amount.nil
                                                                                         { Amount.quantity = 1
                                                                                         , Amount.style = Amount.Style.nil
@@ -2247,9 +2268,8 @@ test_Hcompta =
                                                                                 ]
                                                                         , Posting.sourcepos = P.newPos "" 2 1
                                                                         }
-                                                                , Posting.nil
-                                                                        { Posting.account = ["a","b","c"]
-                                                                        , Posting.sourcepos = P.newPos "" 3 1
+                                                                , (Posting.nil ("a":|["b", "c"]))
+                                                                        { Posting.sourcepos = P.newPos "" 3 1
                                                                         }
                                                                 ]
                                                         , Transaction.sourcepos = P.newPos "" 1 1
@@ -2271,9 +2291,8 @@ test_Hcompta =
                                                                 , [] )
                                                         , Transaction.description="some description"
                                                         , Transaction.postings = Posting.from_List
-                                                                [ Posting.nil
-                                                                        { Posting.account = ["A","B","C"]
-                                                                        , Posting.amounts = Data.Map.fromList
+                                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                                        { Posting.amounts = Data.Map.fromList
                                                                                 [ ("$", Amount.nil
                                                                                         { Amount.quantity = 1
                                                                                         , Amount.style = Amount.Style.nil
@@ -2285,9 +2304,8 @@ test_Hcompta =
                                                                                 ]
                                                                         , Posting.sourcepos = P.newPos "" 2 1
                                                                         }
-                                                                , Posting.nil
-                                                                        { Posting.account = ["a","b","c"]
-                                                                        , Posting.sourcepos = P.newPos "" 3 1
+                                                                , (Posting.nil ("a":|["b", "c"]))
+                                                                        { Posting.sourcepos = P.newPos "" 3 1
                                                                         }
                                                                 ]
                                                         , Transaction.sourcepos = P.newPos "" 1 1
@@ -2315,9 +2333,8 @@ test_Hcompta =
                                                                 , [] )
                                                         , Transaction.description="some description"
                                                         , Transaction.postings = Posting.from_List
-                                                                [ Posting.nil
-                                                                        { Posting.account = ["A","B","C"]
-                                                                        , Posting.amounts = Data.Map.fromList
+                                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                                        { Posting.amounts = Data.Map.fromList
                                                                                 [ ("$", Amount.nil
                                                                                         { Amount.quantity = 1
                                                                                         , Amount.style = Amount.Style.nil
@@ -2329,9 +2346,8 @@ test_Hcompta =
                                                                                 ]
                                                                         , Posting.sourcepos = P.newPos "" 5 1
                                                                         }
-                                                                , Posting.nil
-                                                                        { Posting.account = ["a","b","c"]
-                                                                        , Posting.sourcepos = P.newPos "" 6 1
+                                                                , (Posting.nil ("a":|["b", "c"]))
+                                                                        { Posting.sourcepos = P.newPos "" 6 1
                                                                         , Posting.tags = Data.Map.fromList []
                                                                         }
                                                                 ]
@@ -2365,9 +2381,8 @@ test_Hcompta =
                                                                                 , [] )
                                                                         , Transaction.description="1° description"
                                                                         , Transaction.postings = Posting.from_List
-                                                                                [ Posting.nil
-                                                                                        { Posting.account = ["A","B","C"]
-                                                                                        , Posting.amounts = Data.Map.fromList
+                                                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                                                        { Posting.amounts = Data.Map.fromList
                                                                                                 [ ("$", Amount.nil
                                                                                                         { Amount.quantity = 1
                                                                                                         , Amount.style = Amount.Style.nil
@@ -2379,9 +2394,8 @@ test_Hcompta =
                                                                                                 ]
                                                                                         , Posting.sourcepos = P.newPos "" 2 1
                                                                                         }
-                                                                                , Posting.nil
-                                                                                        { Posting.account = ["a","b","c"]
-                                                                                        , Posting.sourcepos = P.newPos "" 3 1
+                                                                                , (Posting.nil ("a":|["b", "c"]))
+                                                                                        { Posting.sourcepos = P.newPos "" 3 1
                                                                                         }
                                                                                 ]
                                                                         , Transaction.sourcepos = P.newPos "" 1 1
@@ -2396,9 +2410,8 @@ test_Hcompta =
                                                                                 , [] )
                                                                         , Transaction.description="2° description"
                                                                         , Transaction.postings = Posting.from_List
-                                                                                [ Posting.nil
-                                                                                        { Posting.account = ["A","B","C"]
-                                                                                        , Posting.amounts = Data.Map.fromList
+                                                                                [ (Posting.nil ("A":|["B", "C"]))
+                                                                                        { Posting.amounts = Data.Map.fromList
                                                                                                 [ ("$", Amount.nil
                                                                                                         { Amount.quantity = 1
                                                                                                         , Amount.style = Amount.Style.nil
@@ -2410,9 +2423,8 @@ test_Hcompta =
                                                                                                 ]
                                                                                         , Posting.sourcepos = P.newPos "" 5 1
                                                                                         }
-                                                                                , Posting.nil
-                                                                                        { Posting.account = ["x","y","z"]
-                                                                                        , Posting.sourcepos = P.newPos "" 6 1
+                                                                                , (Posting.nil ("x":|["y", "z"]))
+                                                                                        { Posting.sourcepos = P.newPos "" 6 1
                                                                                         }
                                                                                 ]
                                                                         , Transaction.sourcepos = P.newPos "" 4 1
@@ -2424,34 +2436,28 @@ test_Hcompta =
                                 ]
                         , "Write" ~: TestList
                                 [ "account" ~: TestList
-                                        [ "nil" ~:
-                                               ((Format.Ledger.Write.show False $
-                                               Format.Ledger.Write.account Posting.Type_Regular
-                                               Account.nil)
-                                               ~?=
-                                               "")
-                                        , "A" ~:
+                                        [ "A" ~:
                                                ((Format.Ledger.Write.show False $
-                                               Format.Ledger.Write.account Posting.Type_Regular
-                                               ["A"])
+                                               Format.Ledger.Write.account Posting.Type_Regular $
+                                               "A":|[])
                                                ~?=
                                                "A")
                                         , "A:B:C" ~:
                                                ((Format.Ledger.Write.show False $
-                                               Format.Ledger.Write.account Posting.Type_Regular
-                                               ["A", "B", "C"])
+                                               Format.Ledger.Write.account Posting.Type_Regular $
+                                               "A":|["B", "C"])
                                                ~?=
                                                "A:B:C")
                                         , "(A:B:C)" ~:
                                                ((Format.Ledger.Write.show False $
-                                               Format.Ledger.Write.account Posting.Type_Virtual
-                                               ["A", "B", "C"])
+                                               Format.Ledger.Write.account Posting.Type_Virtual $
+                                               "A":|["B", "C"])
                                                ~?=
                                                "(A:B:C)")
                                         , "[A:B:C]" ~:
                                                ((Format.Ledger.Write.show False $
-                                               Format.Ledger.Write.account Posting.Type_Virtual_Balanced
-                                               ["A", "B", "C"])
+                                               Format.Ledger.Write.account Posting.Type_Virtual_Balanced $
+                                               "A":|["B", "C"])
                                                ~?=
                                                "[A:B:C]")
                                         ]
@@ -2805,9 +2811,8 @@ test_Hcompta =
                                                         , [] )
                                                 , Transaction.description="some description"
                                                 , Transaction.postings = Posting.from_List
-                                                        [ Posting.nil
-                                                                { Posting.account = ["A","B","C"]
-                                                                , Posting.amounts = Data.Map.fromList
+                                                        [ (Posting.nil ("A":|["B", "C"]))
+                                                                { Posting.amounts = Data.Map.fromList
                                                                         [ ("$", Amount.nil
                                                                                 { Amount.quantity = 1
                                                                                 , Amount.style = Amount.Style.nil
@@ -2818,9 +2823,8 @@ test_Hcompta =
                                                                                 })
                                                                         ]
                                                                 }
-                                                        , Posting.nil
-                                                                { Posting.account = ["a","b","c"]
-                                                                , Posting.comments = ["first comment","second comment","third comment"]
+                                                        , (Posting.nil ("a":|["b", "c"]))
+                                                                { Posting.comments = ["first comment","second comment","third comment"]
                                                                 }
                                                         ]
                                                 })
@@ -2839,9 +2843,8 @@ test_Hcompta =
                                                         , [] )
                                                 , Transaction.description="some description"
                                                 , Transaction.postings = Posting.from_List
-                                                        [ Posting.nil
-                                                                { Posting.account = ["A","B","C"]
-                                                                , Posting.amounts = Data.Map.fromList
+                                                        [ (Posting.nil ("A":|["B", "C"]))
+                                                                { Posting.amounts = Data.Map.fromList
                                                                         [ ("$", Amount.nil
                                                                                 { Amount.quantity = 1
                                                                                 , Amount.style = Amount.Style.nil
@@ -2852,9 +2855,8 @@ test_Hcompta =
                                                                                 })
                                                                         ]
                                                                 }
-                                                        , Posting.nil
-                                                                { Posting.account = ["AA","BB","CC"]
-                                                                , Posting.amounts = Data.Map.fromList
+                                                        , (Posting.nil ("AA":|["BB", "CC"]))
+                                                                { Posting.amounts = Data.Map.fromList
                                                                         [ ("$", Amount.nil
                                                                                 { Amount.quantity = 123
                                                                                 , Amount.style = Amount.Style.nil
index 4e921ca77dfa8b720fde8d471b727c62c8f39e8e..54355375d6530eb118f3735204deaf6432ea9b72 100644 (file)
@@ -62,6 +62,7 @@ Library
     Hcompta.Lib.Parsec
     Hcompta.Lib.Path
     Hcompta.Lib.Regex
+    Hcompta.Lib.TreeMap
     Hcompta.Model
     Hcompta.Model.Account
     Hcompta.Model.Amount
@@ -87,11 +88,13 @@ Library
     , directory
     , filepath
     , HUnit
+    , lens
     -- , mtl >= 2.0
     , parsec >= 3.1.2 && < 4
              -- NOTE: needed for Text.Parsec.Text
     , regex-tdfa
     -- , safe >= 0.2
+    , semigroups
     , text
     , time
     , transformers >= 0.4 && < 0.5
@@ -112,6 +115,7 @@ test-suite Test
     , HUnit
     , parsec >= 3.1.2 && < 4
     -- , safe
+    , semigroups
     , test-framework
     , test-framework-hunit
     , text