CachedLedger

This commit is contained in:
Simon Michael 2007-07-02 18:57:37 +00:00
parent 630e6d273d
commit df55743697
6 changed files with 100 additions and 34 deletions

49
CachedLedger.hs Normal file
View File

@ -0,0 +1,49 @@
module CachedLedger
where
import qualified Data.Map as Map
import Utils
import Types
import Account
import AccountName
import EntryTransaction
import Ledger
cacheLedger :: Ledger -> CachedLedger
cacheLedger l =
CachedLedger
l
(ledgerAccountNameTree l)
(Map.fromList [(a, ledgerAccount l a) | a <- ledgerAccountNames l])
cLedgerTransactions :: CachedLedger -> [EntryTransaction]
cLedgerTransactions l = concatMap atransactions $ Map.elems $ accounts l
-- unoptimised
cLedgerTransactionsMatching :: ([String],[String]) -> CachedLedger -> [EntryTransaction]
cLedgerTransactionsMatching pats l = ledgerTransactionsMatching pats $ uncached_ledger l
-- XXX optimise
cLedgerTransactionsMatching1 :: ([String],[String]) -> CachedLedger -> [EntryTransaction]
cLedgerTransactionsMatching1 ([],[]) l = ledgerTransactionsMatching ([".*"],[".*"]) (uncached_ledger l)
cLedgerTransactionsMatching1 (rs,[]) l = ledgerTransactionsMatching (rs,[".*"]) (uncached_ledger l)
cLedgerTransactionsMatching1 ([],rs) l = ledgerTransactionsMatching ([".*"],rs) (uncached_ledger l)
cLedgerTransactionsMatching1 (acctregexps,descregexps) l =
intersect
(concat [filter (matchTransactionAccount r) ts | r <- acctregexps])
(concat [filter (matchTransactionDescription r) ts | r <- descregexps])
where ts = cLedgerTransactions l
-- unoptimised
showCLedgerAccounts :: CachedLedger -> [String] -> Bool -> Int -> String
showCLedgerAccounts l acctpats showsubs maxdepth =
showLedgerAccounts (uncached_ledger l) acctpats showsubs maxdepth
-- XXX optimise
showCLedgerAccounts1 :: CachedLedger -> [String] -> Bool -> Int -> String
showCLedgerAccounts1 l acctpats showsubs maxdepth =
concatMap
(showAccountTree (uncached_ledger l))
(branches (ledgerAccountTreeMatching (uncached_ledger l) acctpats showsubs maxdepth))

View File

@ -9,7 +9,8 @@ module Models (
module TimeLog, module TimeLog,
module EntryTransaction, module EntryTransaction,
module Ledger, module Ledger,
module Account module Account,
module CachedLedger,
) )
where where
import qualified Data.Map as Map import qualified Data.Map as Map
@ -24,4 +25,5 @@ import TimeLog
import EntryTransaction import EntryTransaction
import Ledger import Ledger
import Account import Account
import CachedLedger

10
NOTES
View File

@ -2,7 +2,8 @@ hledger project notes
* TO DO * TO DO
** make balance fast ** make balance fast
*** understand balance report execution, slowness, solution *** TODO optimise with CachedLedger
**** original
******** transactionsInAccountNamed Account 12 0.0 0.1 66.7 18.7 ******** transactionsInAccountNamed Account 12 0.0 0.1 66.7 18.7
********* ledgerTransactionsMatching Ledger 24 0.0 8.4 66.7 18.6 ********* ledgerTransactionsMatching Ledger 24 0.0 8.4 66.7 18.6
********** matchTransactionDescription EntryTransaction 48 0.0 0.7 0.0 0.7 ********** matchTransactionDescription EntryTransaction 48 0.0 0.7 0.0 0.7
@ -10,9 +11,10 @@ hledger project notes
********** matchTransactionAccount EntryTransaction 864 66.7 7.3 66.7 7.3 ********** matchTransactionAccount EntryTransaction 864 66.7 7.3 66.7 7.3
*********** account EntryTransaction 864 0.0 0.0 0.0 0.0 *********** account EntryTransaction 864 0.0 0.0 0.0 0.0
*** make it fast **** with cachedledger, unoptimised
**** TODO reorganize Ledger/Account matchTransactionAccount EntryTransaction 619 86602 13.4 2.4 13.5 2.4
**** substitute CookedLedger matchTransactionAccount EntryTransaction 558 91637 22.8 2.8 22.9 2.8
matchTransactionAccount EntryTransaction 520 91637 16.8 2.6 16.9 2.6
** make some decent tests ** make some decent tests
** bugs ** bugs
*** space after account makes it a new account *** space after account makes it a new account

View File

@ -262,6 +262,7 @@ tests = runTestTT $ test [
, test_autofillEntry , test_autofillEntry
, test_expandAccountNames , test_expandAccountNames
, test_ledgerAccountNames , test_ledgerAccountNames
, test_cacheLedger
, 2 @=? 2 , 2 @=? 2
] ]
@ -289,6 +290,10 @@ test_ledgerAccountNames =
"liabilities","liabilities:credit cards","liabilities:credit cards:discover"] "liabilities","liabilities:credit cards","liabilities:credit cards:discover"]
(ledgerAccountNames ledger7) (ledgerAccountNames ledger7)
test_cacheLedger =
assertEqual' 14 (length $ Map.keys $ accounts $ cacheLedger ledger7)
-- quickcheck properties -- quickcheck properties
props = mapM quickCheck props = mapM quickCheck

View File

@ -1,6 +1,7 @@
module Types module Types
where where
import Utils import Utils
import qualified Data.Map as Map
{- {-
@ -16,16 +17,17 @@ hledger
Models Models
TimeLog TimeLog
TimeLogEntry TimeLogEntry
Account CachedLedger
Ledger Account
EntryTransaction Ledger
Entry EntryTransaction
Transaction Entry
AccountName Transaction
Amount AccountName
Currency Amount
Types Currency
Utils Types
Utils
-} -}
@ -78,14 +80,7 @@ data PeriodicEntry = PeriodicEntry {
p_transactions :: [Transaction] p_transactions :: [Transaction]
} deriving (Eq) } deriving (Eq)
-- a parsed ledger file -- we also parse timeclock.el's timelogs (as a ledger)
data Ledger = Ledger {
modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry],
entries :: [Entry]
} deriving (Eq)
-- we also process timeclock.el's timelogs
data TimeLogEntry = TimeLogEntry { data TimeLogEntry = TimeLogEntry {
tcode :: Char, tcode :: Char,
tdatetime :: DateTime, tdatetime :: DateTime,
@ -96,17 +91,30 @@ data TimeLog = TimeLog {
timelog_entries :: [TimeLogEntry] timelog_entries :: [TimeLogEntry]
} deriving (Eq) } deriving (Eq)
-- a parsed ledger file
data Ledger = Ledger {
modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry],
entries :: [Entry]
} deriving (Eq)
-- We convert Transactions into EntryTransactions, which are (entry, -- We convert Transactions into EntryTransactions, which are (entry,
-- transaction) pairs, since I couldn't see how to have transactions -- transaction) pairs, since I couldn't see how to have transactions
-- reference their entry like in OO. These are referred to as just -- reference their entry like in OO. These are referred to as just
-- "transactions" in modules above EntryTransaction. -- "transactions" in modules above EntryTransaction.
type EntryTransaction = (Entry,Transaction) type EntryTransaction = (Entry,Transaction)
-- an Account caches a particular account's name, balance and transactions -- all information for a particular account, derived from a Ledger
-- from a Ledger
data Account = Account { data Account = Account {
aname :: AccountName, aname :: AccountName,
atransactions :: [EntryTransaction], -- excludes sub-accounts atransactions :: [EntryTransaction], -- excludes sub-accounts
abalance :: Amount -- includes sub-accounts abalance :: Amount -- includes sub-accounts
} }
-- a ledger with account info cached for faster queries
data CachedLedger = CachedLedger {
uncached_ledger :: Ledger,
accountnames :: Tree AccountName,
accounts :: Map.Map AccountName Account
}

View File

@ -37,17 +37,17 @@ register :: [Flag] -> [String] -> [String] -> IO ()
register opts acctpats descpats = do register opts acctpats descpats = do
doWithLedger opts printRegister doWithLedger opts printRegister
where where
printRegister ledger = printRegister l =
putStr $ showTransactionsWithBalances putStr $ showTransactionsWithBalances
(ledgerTransactionsMatching (acctpats,descpats) ledger) (cLedgerTransactionsMatching (acctpats,descpats) l)
0 0
balance :: [Flag] -> [String] -> [String] -> IO () balance :: [Flag] -> [String] -> [String] -> IO ()
balance opts acctpats _ = do balance opts acctpats _ = do
doWithLedger opts printBalance doWithLedger opts printBalance
where where
printBalance ledger = printBalance l =
putStr $ showLedgerAccounts ledger acctpats showsubs maxdepth putStr $ showCLedgerAccounts l acctpats showsubs maxdepth
where where
showsubs = (ShowSubs `elem` opts) showsubs = (ShowSubs `elem` opts)
maxdepth = case (acctpats, showsubs) of maxdepth = case (acctpats, showsubs) of
@ -63,14 +63,14 @@ selftest = do
-- utils -- utils
doWithLedger :: [Flag] -> (Ledger -> IO ()) -> IO () doWithLedger :: [Flag] -> (CachedLedger -> IO ()) -> IO ()
doWithLedger opts cmd = do doWithLedger opts cmd = do
ledgerFilePath opts >>= parseLedgerFile >>= doWithParsed cmd ledgerFilePath opts >>= parseLedgerFile >>= doWithParsed cmd
doWithParsed :: Show a => (a -> IO ()) -> (Either ParseError a) -> IO () doWithParsed :: (CachedLedger -> IO ()) -> (Either ParseError Ledger) -> IO ()
doWithParsed action parsed = do doWithParsed cmd parsed = do
case parsed of Left e -> parseError e case parsed of Left e -> parseError e
Right l -> action l Right l -> cmd $ cacheLedger l
-- interactive testing: -- interactive testing:
-- --