hledger/hledger-lib/Hledger/Data/AccountName.hs

167 lines
6.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE NoMonomorphismRestriction#-}
{-|
'AccountName's are strings like @assets:cash:petty@, with multiple
components separated by ':'. From a set of these we derive the account
hierarchy.
-}
2010-05-20 03:08:53 +04:00
module Hledger.Data.AccountName
where
2011-05-28 08:11:44 +04:00
import Data.List
import Data.Tree
import Test.HUnit
2011-06-11 22:35:20 +04:00
import Text.Printf
2011-05-28 08:11:44 +04:00
import Hledger.Data.Types
import Hledger.Utils
-- change to use a different separator for nested accounts
acctsepchar = ':'
2007-07-03 12:46:39 +04:00
accountNameComponents :: AccountName -> [String]
accountNameComponents = splitAtElement acctsepchar
accountNameFromComponents :: [String] -> AccountName
accountNameFromComponents = concat . intersperse [acctsepchar]
accountLeafName :: AccountName -> String
accountLeafName = last . accountNameComponents
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
accountNameDrop :: Int -> AccountName -> AccountName
accountNameDrop n = accountNameFromComponents . drop n . accountNameComponents
2008-10-01 04:29:58 +04:00
-- | ["a:b:c","d:e"] -> ["a","a:b","a:b:c","d","d:e"]
expandAccountNames :: [AccountName] -> [AccountName]
expandAccountNames as = nub $ concatMap expandAccountName as
-- | "a:b:c" -> ["a","a:b","a:b:c"]
expandAccountName :: AccountName -> [AccountName]
expandAccountName = map accountNameFromComponents . tail . inits . accountNameComponents
2008-10-01 04:29:58 +04:00
-- | ["a:b:c","d:e"] -> ["a","d"]
topAccountNames :: [AccountName] -> [AccountName]
topAccountNames as = [a | a <- expandAccountNames as, accountNameLevel a == 1]
parentAccountName :: AccountName -> AccountName
2009-09-22 19:56:59 +04:00
parentAccountName = accountNameFromComponents . init . accountNameComponents
parentAccountNames :: AccountName -> [AccountName]
parentAccountNames a = parentAccountNames' $ parentAccountName a
where
parentAccountNames' "" = []
2009-09-23 13:22:53 +04:00
parentAccountNames' a = a : parentAccountNames' (parentAccountName a)
-- | Is the first account a parent or other ancestor of (and not the same as) the second ?
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
s `isSubAccountNameOf` p =
2007-07-03 03:41:07 +04:00
(p `isAccountNamePrefixOf` s) && (accountNameLevel s == (accountNameLevel p + 1))
-- | From a list of account names, select those which are direct
-- subaccounts of the given account name.
subAccountNamesFrom :: [AccountName] -> AccountName -> [AccountName]
subAccountNamesFrom accts a = filter (`isSubAccountNameOf` a) accts
-- | Convert a list of account names to a tree.
accountNameTreeFrom :: [AccountName] -> Tree AccountName
accountNameTreeFrom accts =
Node "root" (accounttreesfrom (topAccountNames accts))
where
accounttreesfrom :: [AccountName] -> [Tree AccountName]
accounttreesfrom [] = []
accounttreesfrom as = [Node a (accounttreesfrom $ subs a) | a <- as]
subs = subAccountNamesFrom (expandAccountNames accts)
nullaccountnametree = Node "root" []
2008-10-15 23:14:34 +04:00
-- | Elide an account name to fit in the specified width.
-- From the ledger 2.6 news:
--
2008-10-15 23:14:34 +04:00
-- @
-- 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 =
2008-10-15 23:14:34 +04:00
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
-- | Keep only the first n components of an account name, where n
-- is a positive integer. If n is 0, returns the empty string.
clipAccountName :: Int -> AccountName -> AccountName
clipAccountName n = accountNameFromComponents . take n . accountNameComponents
-- | Keep only the first n components of an account name, where n
-- is a positive integer. If n is 0, returns "...".
clipOrEllipsifyAccountName :: Int -> AccountName -> AccountName
clipOrEllipsifyAccountName 0 = const "..."
clipOrEllipsifyAccountName n = accountNameFromComponents . take n . accountNameComponents
2008-11-22 08:48:56 +03:00
2011-06-11 22:35:20 +04:00
-- | Convert an account name to a regular expression matching it and its subaccounts.
accountNameToAccountRegex :: String -> String
accountNameToAccountRegex "" = ""
accountNameToAccountRegex a = printf "^%s(:|$)" a
2012-04-14 05:11:11 +04:00
-- | Convert an account name to a regular expression matching it but not its subaccounts.
2011-06-11 22:35:20 +04:00
accountNameToAccountOnlyRegex :: String -> String
accountNameToAccountOnlyRegex "" = ""
accountNameToAccountOnlyRegex a = printf "^%s$" a
-- | Convert an exact account-matching regular expression to a plain account name.
accountRegexToAccountName :: String -> String
accountRegexToAccountName = regexReplace "^\\^(.*?)\\(:\\|\\$\\)$" "\\1"
-- | Does this string look like an exact account-matching regular expression ?
isAccountRegex :: String -> Bool
isAccountRegex s = take 1 s == "^" && (take 5 $ reverse s) == ")$|:("
2010-12-27 23:26:22 +03:00
tests_Hledger_Data_AccountName = TestList
[
"accountNameTreeFrom" ~: do
accountNameTreeFrom ["a"] `is` Node "root" [Node "a" []]
accountNameTreeFrom ["a","b"] `is` Node "root" [Node "a" [], Node "b" []]
accountNameTreeFrom ["a","a:b"] `is` Node "root" [Node "a" [Node "a:b" []]]
accountNameTreeFrom ["a:b:c"] `is` Node "root" [Node "a" [Node "a:b" [Node "a:b:c" []]]]
2010-12-27 23:26:22 +03:00
,"expandAccountNames" ~:
expandAccountNames ["assets:cash","assets:checking","expenses:vacation"] `is`
["assets","assets:cash","assets:checking","expenses","expenses:vacation"]
,"isAccountNamePrefixOf" ~: do
"assets" `isAccountNamePrefixOf` "assets" `is` False
"assets" `isAccountNamePrefixOf` "assets:bank" `is` True
"assets" `isAccountNamePrefixOf` "assets:bank:checking" `is` True
"my assets" `isAccountNamePrefixOf` "assets:bank" `is` False
,"isSubAccountNameOf" ~: do
"assets" `isSubAccountNameOf` "assets" `is` False
"assets:bank" `isSubAccountNameOf` "assets" `is` True
"assets:bank:checking" `isSubAccountNameOf` "assets" `is` False
"assets:bank" `isSubAccountNameOf` "my assets" `is` False
]