module Ledger.Ledger
where
import qualified Data.Map as Map
import Data.Map ((!))
import Ledger.Utils
import Ledger.Types
import Ledger.Amount
import Ledger.AccountName
import Ledger.Account
import Ledger.Transaction
import Ledger.RawLedger
import Ledger.Entry
instance Show Ledger where
show l = printf "Ledger with %d entries, %d accounts\n%s"
((length $ entries $ rawledger l) +
(length $ modifier_entries $ rawledger l) +
(length $ periodic_entries $ rawledger l))
(length $ accountnames l)
(showtree $ accountnametree l)
cacheLedger :: [String] -> RawLedger -> Ledger
cacheLedger apats l = Ledger l ant amap
where
ant = rawLedgerAccountNameTree l
anames = flatten ant
ts = filtertxns apats $ rawLedgerTransactions l
sortedts = sortBy (comparing account) ts
groupedts = groupBy (\t1 t2 -> account t1 == account t2) sortedts
txnmap = Map.union
(Map.fromList [(account $ head g, g) | g <- groupedts])
(Map.fromList [(a,[]) | a <- anames])
txnsof = (txnmap !)
subacctsof a = filter (a `isAccountNamePrefixOf`) anames
subtxnsof a = concat [txnsof a | a <- [a] ++ subacctsof a]
balmap = Map.union
(Map.fromList [(a,(sumTransactions $ subtxnsof a)) | a <- anames])
(Map.fromList [(a,Mixed []) | a <- anames])
amap = Map.fromList [(a, Account a (txnmap ! a) (balmap ! a)) | a <- anames]
filtertxns :: [String] -> [Transaction] -> [Transaction]
filtertxns apats ts = filter (matchpats apats . account) ts
accountnames :: Ledger -> [AccountName]
accountnames l = drop 1 $ flatten $ accountnametree l
ledgerAccount :: Ledger -> AccountName -> Account
ledgerAccount l a = (accountmap l) ! a
accounts :: Ledger -> [Account]
accounts l = drop 1 $ flatten $ ledgerAccountTree 9999 l
topAccounts :: Ledger -> [Account]
topAccounts l = map root $ branches $ ledgerAccountTree 9999 l
accountsMatching :: [String] -> Ledger -> [Account]
accountsMatching pats l = filter (matchpats pats . aname) $ accounts l
subAccounts :: Ledger -> Account -> [Account]
subAccounts l Account{aname=a} =
map (ledgerAccount l) $ filter (a `isAccountNamePrefixOf`) $ accountnames l
ledgerTransactions :: Ledger -> [Transaction]
ledgerTransactions l = rawLedgerTransactions $ rawledger l
ledgerAccountTree :: Int -> Ledger -> Tree Account
ledgerAccountTree depth l = treemap (ledgerAccount l) $ treeprune depth $ accountnametree l
ledgerAccountTreeAt :: Ledger -> Account -> Maybe (Tree Account)
ledgerAccountTreeAt l acct = subtreeat acct $ ledgerAccountTree 9999 l