datespan utils

This commit is contained in:
Simon Michael 2009-04-04 11:19:15 +00:00
parent ca3f55933b
commit 622db5f25d
4 changed files with 22 additions and 11 deletions

View File

@ -132,8 +132,9 @@ ledgerAccountTree depth l = treemap (ledgerAccount l) $ treeprune depth $ accoun
ledgerAccountTreeAt :: Ledger -> Account -> Maybe (Tree Account)
ledgerAccountTreeAt l acct = subtreeat acct $ ledgerAccountTree 9999 l
-- | The (explicit) date span containing all the ledger's transactions,
-- or DateSpan Nothing Nothing if there are no transactions.
-- | The date span containing all the ledger's (filtered) transactions,
-- or DateSpan Nothing Nothing if there are none.
ledgerDateSpan :: Ledger -> DateSpan
ledgerDateSpan l
| null ts = DateSpan Nothing Nothing
| otherwise = DateSpan (Just $ date $ head ts) (Just $ addDays 1 $ date $ last ts)

View File

@ -163,3 +163,12 @@ rawLedgerConvertTimeLog t l0 = l0 { ledger_txns = convertedTimeLog ++ ledger_txn
}
where convertedTimeLog = entriesFromTimeLogEntries t $ open_timelog_entries l0
-- | The date span containing all the raw ledger's transactions,
-- or DateSpan Nothing Nothing if there are none.
rawLedgerDateSpan :: RawLedger -> DateSpan
rawLedgerDateSpan rl
| null ts = DateSpan Nothing Nothing
| otherwise = DateSpan (Just $ ltdate $ head ts) (Just $ addDays 1 $ ltdate $ last ts)
where
ts = sortBy (comparing ltdate) $ ledger_txns rl

View File

@ -9,6 +9,7 @@ ingrained.
module Ledger.Transaction
where
import Ledger.Dates
import Ledger.Utils
import Ledger.Types
import Ledger.Dates
@ -39,3 +40,11 @@ sumTransactions = sum . map amount
nulltxn :: Transaction
nulltxn = Transaction 0 False (parsedate "1900/1/1") "" "" nullmixedamt RegularPosting
-- | Does the given transaction fall within the given date span ?
isTransactionInDateSpan :: DateSpan -> Transaction -> Bool
isTransactionInDateSpan (DateSpan Nothing Nothing) _ = True
isTransactionInDateSpan (DateSpan Nothing (Just e)) (Transaction{date=d}) = d<e
isTransactionInDateSpan (DateSpan (Just b) Nothing) (Transaction{date=d}) = d>=b
isTransactionInDateSpan (DateSpan (Just b) (Just e)) (Transaction{date=d}) = d>=b && d<e

View File

@ -35,8 +35,7 @@ showRegisterReport opts args l
| otherwise = showtxns summaryts nulltxn startbal
where
interval = intervalFromOpts opts
ts = sort $ filterempties $ filter matchapats $ filterdepth $ ledgerTransactions l
where sort = sortBy (\a b -> compare (date a) (date b))
ts = sortBy (comparing date) $ filterempties $ filter matchapats $ filterdepth $ ledgerTransactions l
filterdepth | interval == NoInterval = filter (\t -> (accountNameLevel $ account t) <= depth)
| otherwise = id
filterempties
@ -97,13 +96,6 @@ clipAccountNames :: Int -> [AccountName] -> [AccountName]
clipAccountNames d as = nub $ map (clip d) as
where clip d = accountNameFromComponents . take d . accountNameComponents
-- | Does the given transaction fall within the given date span ?
isTransactionInDateSpan :: DateSpan -> Transaction -> Bool
isTransactionInDateSpan (DateSpan Nothing Nothing) _ = True
isTransactionInDateSpan (DateSpan Nothing (Just e)) (Transaction{date=d}) = d<e
isTransactionInDateSpan (DateSpan (Just b) Nothing) (Transaction{date=d}) = d>=b
isTransactionInDateSpan (DateSpan (Just b) (Just e)) (Transaction{date=d}) = d>=b && d<e
-- | Show transactions one per line, with each date/description appearing
-- only once, and a running balance.
showtxns [] _ _ = ""