2009-05-29 07:00:56 +04:00
|
|
|
{-# LANGUAGE NoMonomorphismRestriction#-}
|
2008-10-03 06:04:15 +04:00
|
|
|
{-|
|
|
|
|
|
|
|
|
'AccountName's are strings like @assets:cash:petty@.
|
|
|
|
From a set of these we derive the account hierarchy.
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2008-10-03 04:40:06 +04:00
|
|
|
module Ledger.AccountName
|
2007-02-18 21:12:02 +03:00
|
|
|
where
|
2008-10-03 04:05:16 +04:00
|
|
|
import Ledger.Utils
|
2008-10-03 04:12:59 +04:00
|
|
|
import Ledger.Types
|
2009-06-05 13:44:20 +04:00
|
|
|
import Data.Map (Map)
|
2009-05-29 07:00:56 +04:00
|
|
|
import qualified Data.Map as M
|
|
|
|
|
2007-02-18 21:12:02 +03:00
|
|
|
|
2008-10-10 12:16:55 +04:00
|
|
|
|
2008-11-24 03:22:47 +03:00
|
|
|
-- change to use a different separator for nested accounts
|
|
|
|
acctsepchar = ':'
|
2007-07-03 12:46:39 +04:00
|
|
|
|
2007-02-18 21:12:02 +03:00
|
|
|
accountNameComponents :: AccountName -> [String]
|
2008-11-24 03:22:47 +03:00
|
|
|
accountNameComponents = splitAtElement acctsepchar
|
2007-02-18 21:12:02 +03:00
|
|
|
|
|
|
|
accountNameFromComponents :: [String] -> AccountName
|
2008-11-24 03:22:47 +03:00
|
|
|
accountNameFromComponents = concat . intersperse [acctsepchar]
|
2007-02-18 21:12:02 +03:00
|
|
|
|
|
|
|
accountLeafName :: AccountName -> String
|
2007-03-11 00:24:57 +03:00
|
|
|
accountLeafName = last . accountNameComponents
|
2007-02-18 21:12:02 +03:00
|
|
|
|
|
|
|
accountNameLevel :: AccountName -> Int
|
2007-07-03 12:46:39 +04:00
|
|
|
accountNameLevel "" = 0
|
2009-09-22 15:55:11 +04:00
|
|
|
accountNameLevel a = length (filter (==acctsepchar) a) + 1
|
2007-02-18 21:12:02 +03:00
|
|
|
|
2008-10-01 04:29:58 +04:00
|
|
|
-- | ["a:b:c","d:e"] -> ["a","a:b","a:b:c","d","d:e"]
|
2007-02-18 21:12:02 +03:00
|
|
|
expandAccountNames :: [AccountName] -> [AccountName]
|
2009-09-22 16:25:31 +04:00
|
|
|
expandAccountNames as = nub $ concatMap expand as
|
2009-09-22 19:56:59 +04:00
|
|
|
where expand = map accountNameFromComponents . tail . inits . accountNameComponents
|
2007-02-18 21:12:02 +03:00
|
|
|
|
2008-10-01 04:29:58 +04:00
|
|
|
-- | ["a:b:c","d:e"] -> ["a","d"]
|
2007-02-18 21:12:02 +03:00
|
|
|
topAccountNames :: [AccountName] -> [AccountName]
|
|
|
|
topAccountNames as = [a | a <- expandAccountNames as, accountNameLevel a == 1]
|
|
|
|
|
2007-02-20 00:20:06 +03:00
|
|
|
parentAccountName :: AccountName -> AccountName
|
2009-09-22 19:56:59 +04:00
|
|
|
parentAccountName = accountNameFromComponents . init . accountNameComponents
|
2007-02-20 00:20:06 +03:00
|
|
|
|
|
|
|
parentAccountNames :: AccountName -> [AccountName]
|
|
|
|
parentAccountNames a = parentAccountNames' $ parentAccountName a
|
|
|
|
where
|
|
|
|
parentAccountNames' "" = []
|
2009-09-23 13:22:53 +04:00
|
|
|
parentAccountNames' a = a : parentAccountNames' (parentAccountName a)
|
2007-02-18 21:12:02 +03:00
|
|
|
|
2007-07-03 12:46:39 +04:00
|
|
|
isAccountNamePrefixOf :: AccountName -> AccountName -> Bool
|
2009-09-22 19:56:59 +04:00
|
|
|
isAccountNamePrefixOf = isPrefixOf . (++ [acctsepchar])
|
2007-07-03 12:46:39 +04:00
|
|
|
|
|
|
|
isSubAccountNameOf :: AccountName -> AccountName -> Bool
|
2007-02-18 21:12:02 +03:00
|
|
|
s `isSubAccountNameOf` p =
|
2007-07-03 03:41:07 +04:00
|
|
|
(p `isAccountNamePrefixOf` s) && (accountNameLevel s == (accountNameLevel p + 1))
|
2007-02-18 21:12:02 +03:00
|
|
|
|
2009-05-29 07:00:56 +04:00
|
|
|
-- | From a list of account names, select those which are direct
|
|
|
|
-- subaccounts of the given account name.
|
2007-02-18 21:12:02 +03:00
|
|
|
subAccountNamesFrom :: [AccountName] -> AccountName -> [AccountName]
|
|
|
|
subAccountNamesFrom accts a = filter (`isSubAccountNameOf` a) accts
|
|
|
|
|
2009-05-29 07:00:56 +04:00
|
|
|
-- | Convert a list of account names to a tree.
|
2007-02-18 21:12:02 +03:00
|
|
|
accountNameTreeFrom :: [AccountName] -> Tree AccountName
|
2009-05-29 07:00:56 +04:00
|
|
|
accountNameTreeFrom = accountNameTreeFrom1
|
|
|
|
|
|
|
|
accountNameTreeFrom1 accts =
|
|
|
|
Node "top" (accounttreesfrom (topAccountNames accts))
|
2007-02-18 21:12:02 +03:00
|
|
|
where
|
2009-05-29 07:00:56 +04:00
|
|
|
accounttreesfrom :: [AccountName] -> [Tree AccountName]
|
|
|
|
accounttreesfrom [] = []
|
|
|
|
accounttreesfrom as = [Node a (accounttreesfrom $ subs a) | a <- as]
|
2009-03-15 07:02:04 +03:00
|
|
|
subs = subAccountNamesFrom (expandAccountNames accts)
|
2007-02-18 21:12:02 +03:00
|
|
|
|
2009-05-29 07:00:56 +04:00
|
|
|
accountNameTreeFrom2 accts =
|
|
|
|
Node "top" $ unfoldForest (\a -> (a, subs a)) $ topAccountNames accts
|
|
|
|
where
|
|
|
|
subs = subAccountNamesFrom allaccts
|
|
|
|
allaccts = expandAccountNames accts
|
|
|
|
-- subs' a = subsmap ! a
|
|
|
|
-- subsmap :: Map AccountName [AccountName]
|
|
|
|
-- subsmap = Data.Map.fromList [(a, subAccountNamesFrom allaccts a) | a <- allaccts]
|
|
|
|
|
|
|
|
accountNameTreeFrom3 accts =
|
|
|
|
Node "top" $ forestfrom allaccts $ topAccountNames accts
|
|
|
|
where
|
|
|
|
-- drop accts from the list of potential subs as we add them to the tree
|
|
|
|
forestfrom :: [AccountName] -> [AccountName] -> Forest AccountName
|
|
|
|
forestfrom subaccts accts =
|
|
|
|
[let subaccts' = subaccts \\ accts in Node a $ forestfrom subaccts' (subAccountNamesFrom subaccts' a) | a <- accts]
|
|
|
|
allaccts = expandAccountNames accts
|
|
|
|
|
|
|
|
|
|
|
|
-- a more efficient tree builder from Cale Gibbard
|
|
|
|
newtype Tree' a = T (Map a (Tree' a))
|
|
|
|
deriving (Show, Eq, Ord)
|
|
|
|
|
|
|
|
mergeTrees :: (Ord a) => Tree' a -> Tree' a -> Tree' a
|
|
|
|
mergeTrees (T m) (T m') = T (M.unionWith mergeTrees m m')
|
|
|
|
|
|
|
|
emptyTree = T M.empty
|
|
|
|
|
|
|
|
pathtree :: [a] -> Tree' a
|
|
|
|
pathtree [] = T M.empty
|
|
|
|
pathtree (x:xs) = T (M.singleton x (pathtree xs))
|
|
|
|
|
|
|
|
fromPaths :: (Ord a) => [[a]] -> Tree' a
|
|
|
|
fromPaths = foldl' mergeTrees emptyTree . map pathtree
|
|
|
|
|
|
|
|
-- the above, but trying to build Tree directly
|
|
|
|
|
|
|
|
-- mergeTrees' :: (Ord a) => Tree a -> Tree a -> Tree a
|
|
|
|
-- mergeTrees' (Node m ms) (Node m' ms') = Node undefined (ms `union` ms')
|
|
|
|
|
|
|
|
-- emptyTree' = Node "top" []
|
|
|
|
|
|
|
|
-- pathtree' :: [a] -> Tree a
|
|
|
|
-- pathtree' [] = Node undefined []
|
|
|
|
-- pathtree' (x:xs) = Node x [pathtree' xs]
|
|
|
|
|
|
|
|
-- fromPaths' :: (Ord a) => [[a]] -> Tree a
|
|
|
|
-- fromPaths' = foldl' mergeTrees' emptyTree' . map pathtree'
|
|
|
|
|
2009-05-29 14:06:50 +04:00
|
|
|
|
|
|
|
-- converttree :: [AccountName] -> Tree' AccountName -> [Tree AccountName]
|
|
|
|
-- converttree parents (T m) = [Node (accountNameFromComponents $ parents ++ [a]) (converttree (parents++[a]) b) | (a,b) <- M.toList m]
|
|
|
|
|
|
|
|
-- accountNameTreeFrom4 :: [AccountName] -> Tree AccountName
|
|
|
|
-- accountNameTreeFrom4 accts = Node "top" (converttree [] $ fromPaths $ map accountNameComponents accts)
|
|
|
|
|
|
|
|
converttree :: Tree' AccountName -> [Tree AccountName]
|
|
|
|
converttree (T m) = [Node a (converttree b) | (a,b) <- M.toList m]
|
|
|
|
|
|
|
|
expandTreeNames :: Tree AccountName -> Tree AccountName
|
|
|
|
expandTreeNames (Node x ts) = Node x (map (treemap (\n -> accountNameFromComponents [x,n]) . expandTreeNames) ts)
|
2009-05-29 07:00:56 +04:00
|
|
|
|
|
|
|
accountNameTreeFrom4 :: [AccountName] -> Tree AccountName
|
2009-05-29 14:06:50 +04:00
|
|
|
accountNameTreeFrom4 = Node "top" . map expandTreeNames . converttree . fromPaths . map accountNameComponents
|
2009-05-29 07:00:56 +04:00
|
|
|
|
|
|
|
|
2008-10-15 23:14:34 +04:00
|
|
|
-- | Elide an account name to fit in the specified width.
|
|
|
|
-- From the ledger 2.6 news:
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- What Ledger now does is that if an account name is too long, it will
|
|
|
|
-- start abbreviating the first parts of the account name down to two
|
|
|
|
-- letters in length. If this results in a string that is still too
|
|
|
|
-- long, the front will be elided -- not the end. For example:
|
|
|
|
--
|
|
|
|
-- Expenses:Cash ; OK, not too long
|
|
|
|
-- Ex:Wednesday:Cash ; "Expenses" was abbreviated to fit
|
|
|
|
-- Ex:We:Afternoon:Cash ; "Expenses" and "Wednesday" abbreviated
|
|
|
|
-- ; Expenses:Wednesday:Afternoon:Lunch:Snack:Candy:Chocolate:Cash
|
|
|
|
-- ..:Af:Lu:Sn:Ca:Ch:Cash ; Abbreviated and elided!
|
|
|
|
-- @
|
|
|
|
elideAccountName :: Int -> AccountName -> AccountName
|
|
|
|
elideAccountName width s =
|
|
|
|
elideLeft width $ accountNameFromComponents $ elideparts width [] $ accountNameComponents s
|
|
|
|
where
|
|
|
|
elideparts :: Int -> [String] -> [String] -> [String]
|
|
|
|
elideparts width done ss
|
2009-09-22 15:55:11 +04:00
|
|
|
| length (accountNameFromComponents $ done++ss) <= width = done++ss
|
2008-10-15 23:14:34 +04:00
|
|
|
| length ss > 1 = elideparts width (done++[take 2 $ head ss]) (tail ss)
|
|
|
|
| otherwise = done++ss
|
2008-11-22 08:48:56 +03:00
|
|
|
|
|
|
|
|