hledger/Account.hs
2007-07-02 23:41:07 +00:00

180 lines
5.1 KiB
Haskell

module Account
where
import qualified Data.Map as Map
import Utils
import Types
import AccountName
import Amount
import Entry
import Transaction
import EntryTransaction
import RawLedger
instance Show Account where
show (Account a ts b) = printf "Account %s with %d transactions" a $ length ts
nullacct = Account "" [] nullamt
-- XXX SLOW
rawLedgerAccount :: RawLedger -> AccountName -> Account
rawLedgerAccount l a =
Account
a
(transactionsInAccountNamed l a)
(aggregateBalanceInAccountNamed l a)
-- queries
balanceInAccountNamed :: RawLedger -> AccountName -> Amount
balanceInAccountNamed l a =
sumEntryTransactions (transactionsInAccountNamed l a)
aggregateBalanceInAccountNamed :: RawLedger -> AccountName -> Amount
aggregateBalanceInAccountNamed l a =
sumEntryTransactions (aggregateTransactionsInAccountNamed l a)
transactionsInAccountNamed :: RawLedger -> AccountName -> [EntryTransaction]
transactionsInAccountNamed l a =
rawLedgerTransactionsMatching (["^" ++ a ++ "$"], []) l
aggregateTransactionsInAccountNamed :: RawLedger -> AccountName -> [EntryTransaction]
aggregateTransactionsInAccountNamed l a =
rawLedgerTransactionsMatching (["^" ++ a ++ "(:.+)?$"], []) l
-- build a tree of Accounts
addDataToAccountNameTree :: RawLedger -> Tree AccountName -> Tree Account
addDataToAccountNameTree l ant =
Node
(rawLedgerAccount l $ root ant)
(map (addDataToAccountNameTree l) $ branches ant)
-- balance report support
--
-- examples, ignoring the issue of eliding boring accounts:
-- here is a sample account tree:
--
-- assets
-- cash
-- checking
-- saving
-- equity
-- expenses
-- food
-- shelter
-- income
-- salary
-- liabilities
-- debts
--
-- standard balance command shows all top-level accounts:
--
-- > ledger bal
-- $ assets
-- $ equity
-- $ expenses
-- $ income
-- $ liabilities
--
-- with an account pattern, show only the ones with matching names:
--
-- > ledger bal asset
-- $ assets
--
-- with -s, show all subaccounts of matched accounts:
--
-- > ledger -s bal asset
-- $ assets
-- $ cash
-- $ checking
-- $ saving
showRawLedgerAccounts :: RawLedger -> [String] -> Bool -> Int -> String
showRawLedgerAccounts l acctpats showsubs maxdepth =
concatMap
(showAccountTree l)
(branches (rawLedgerAccountTreeMatching l acctpats showsubs maxdepth))
rawLedgerAccountTreeMatching :: RawLedger -> [String] -> Bool -> Int -> Tree Account
rawLedgerAccountTreeMatching l [] showsubs maxdepth =
rawLedgerAccountTreeMatching l [".*"] showsubs maxdepth
rawLedgerAccountTreeMatching l acctpats showsubs maxdepth =
addDataToAccountNameTree l $
filterAccountNameTree acctpats showsubs maxdepth $
rawLedgerAccountNameTree l
-- when displaying an account tree, we elide boring accounts.
-- 1. leaf accounts and branches with 0 balance or 0 transactions are omitted
-- 2. inner accounts with 0 transactions and 1 subaccount are displayed as
-- a prefix of the sub
--
-- example:
--
-- a (0 txns)
-- b (0 txns)
-- c
-- d
-- e (0 txns)
-- f
-- g
-- h (0 txns)
-- i (0 balance)
--
-- displays as:
--
-- a:b:c
-- d
-- e
-- f
-- g
showAccountTree :: RawLedger -> Tree Account -> String
showAccountTree l = showAccountTree' l 0 . interestingAccountsFrom
showAccountTree' :: RawLedger -> Int -> Tree Account -> String
showAccountTree' l indentlevel t
-- if this acct is boring, don't show it
| isBoringInnerAccount l acct = subacctsindented 0
-- otherwise show normal indented account name with balance,
-- prefixing the names of any boring parents
| otherwise =
bal ++ " " ++ indent ++ prefix ++ leafname ++ "\n" ++ (subacctsindented 1)
where
acct = root t
subacctsindented i = concatMap (showAccountTree' l (indentlevel+i)) $ branches t
bal = printf "%20s" $ show $ abalance $ acct
indent = replicate (indentlevel * 2) ' '
prefix = concatMap (++ ":") $ map accountLeafName boringparents
boringparents = takeWhile (isBoringInnerAccountName l) $ parentAccountNames $ aname acct
leafname = accountLeafName $ aname acct
isBoringInnerAccount :: RawLedger -> Account -> Bool
isBoringInnerAccount l a
| name == "top" = False
| (length txns == 0) && ((length subs) == 1) = True
| otherwise = False
where
name = aname a
txns = atransactions a
subs = subAccountNamesFrom (rawLedgerAccountNames l) name
-- darnit, still need this
isBoringInnerAccountName :: RawLedger -> AccountName -> Bool
isBoringInnerAccountName l name
| name == "top" = False
| (length txns == 0) && ((length subs) == 1) = True
| otherwise = False
where
txns = transactionsInAccountNamed l name
subs = subAccountNamesFrom (rawLedgerAccountNames l) name
interestingAccountsFrom :: Tree Account -> Tree Account
interestingAccountsFrom =
treefilter hastxns . treefilter hasbalance
where
hasbalance = (/= 0) . abalance
hastxns = (> 0) . length . atransactions
rawLedgerAccountTree :: RawLedger -> Tree Account
rawLedgerAccountTree l = addDataToAccountNameTree l (rawLedgerAccountNameTree l)