2008-10-03 06:04:15 +04:00
|
|
|
{-|
|
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
A 'Journal' is a parsed ledger file, containing 'Transaction's.
|
|
|
|
It can be filtered and massaged in various ways, then \"crunched\"
|
|
|
|
to form a 'Ledger'.
|
2008-10-03 06:04:15 +04:00
|
|
|
|
|
|
|
-}
|
|
|
|
|
2010-05-20 03:08:53 +04:00
|
|
|
module Hledger.Data.Journal
|
2007-07-02 23:15:39 +04:00
|
|
|
where
|
2008-10-15 04:34:02 +04:00
|
|
|
import qualified Data.Map as Map
|
2009-12-09 23:51:00 +03:00
|
|
|
import Data.Map (findWithDefault, (!))
|
2009-08-12 13:21:46 +04:00
|
|
|
import System.Time (ClockTime(TOD))
|
2010-05-20 03:08:53 +04:00
|
|
|
import Hledger.Data.Utils
|
|
|
|
import Hledger.Data.Types
|
|
|
|
import Hledger.Data.AccountName
|
|
|
|
import Hledger.Data.Amount
|
|
|
|
import Hledger.Data.Transaction (ledgerTransactionWithDate)
|
|
|
|
import Hledger.Data.Posting
|
|
|
|
import Hledger.Data.TimeLog
|
2007-07-02 23:15:39 +04:00
|
|
|
|
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
instance Show Journal where
|
2009-12-21 08:23:07 +03:00
|
|
|
show j = printf "Journal with %d transactions, %d accounts: %s"
|
|
|
|
(length (jtxns j) +
|
|
|
|
length (jmodifiertxns j) +
|
|
|
|
length (jperiodictxns j))
|
2008-10-09 13:25:58 +04:00
|
|
|
(length accounts)
|
|
|
|
(show accounts)
|
2009-12-16 10:00:43 +03:00
|
|
|
-- ++ (show $ journalTransactions l)
|
2009-12-21 08:23:07 +03:00
|
|
|
where accounts = flatten $ journalAccountNameTree j
|
2008-10-03 16:10:05 +04:00
|
|
|
|
2009-12-20 18:50:54 +03:00
|
|
|
nulljournal :: Journal
|
|
|
|
nulljournal = Journal { jmodifiertxns = []
|
|
|
|
, jperiodictxns = []
|
|
|
|
, jtxns = []
|
|
|
|
, open_timelog_entries = []
|
|
|
|
, historical_prices = []
|
|
|
|
, final_comment_lines = []
|
|
|
|
, filepath = ""
|
|
|
|
, filereadtime = TOD 0 0
|
2009-12-21 08:43:10 +03:00
|
|
|
, jtext = ""
|
2009-12-20 18:50:54 +03:00
|
|
|
}
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-12-16 11:07:26 +03:00
|
|
|
addTransaction :: Transaction -> Journal -> Journal
|
2009-12-16 20:58:51 +03:00
|
|
|
addTransaction t l0 = l0 { jtxns = t : jtxns l0 }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
addModifierTransaction :: ModifierTransaction -> Journal -> Journal
|
2009-12-16 20:58:51 +03:00
|
|
|
addModifierTransaction mt l0 = l0 { jmodifiertxns = mt : jmodifiertxns l0 }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
addPeriodicTransaction :: PeriodicTransaction -> Journal -> Journal
|
2009-12-16 20:58:51 +03:00
|
|
|
addPeriodicTransaction pt l0 = l0 { jperiodictxns = pt : jperiodictxns l0 }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
addHistoricalPrice :: HistoricalPrice -> Journal -> Journal
|
2009-09-22 20:51:27 +04:00
|
|
|
addHistoricalPrice h l0 = l0 { historical_prices = h : historical_prices l0 }
|
2008-12-16 13:54:20 +03:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
addTimeLogEntry :: TimeLogEntry -> Journal -> Journal
|
2009-09-22 20:51:27 +04:00
|
|
|
addTimeLogEntry tle l0 = l0 { open_timelog_entries = tle : open_timelog_entries l0 }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-12-19 08:57:54 +03:00
|
|
|
journalPostings :: Journal -> [Posting]
|
|
|
|
journalPostings = concatMap tpostings . jtxns
|
2008-10-03 16:10:05 +04:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
journalAccountNamesUsed :: Journal -> [AccountName]
|
2009-12-19 08:57:54 +03:00
|
|
|
journalAccountNamesUsed = accountNamesFromPostings . journalPostings
|
2008-10-03 16:10:05 +04:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
journalAccountNames :: Journal -> [AccountName]
|
|
|
|
journalAccountNames = sort . expandAccountNames . journalAccountNamesUsed
|
2008-10-03 16:10:05 +04:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
journalAccountNameTree :: Journal -> Tree AccountName
|
|
|
|
journalAccountNameTree = accountNameTreeFrom . journalAccountNames
|
2008-10-10 08:23:25 +04:00
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
-- Various kinds of filtering on journals. We do it differently depending
|
|
|
|
-- on the command.
|
|
|
|
|
|
|
|
-- | Keep only transactions we are interested in, as described by
|
|
|
|
-- the filter specification. May also massage the data a little.
|
|
|
|
filterJournalTransactions :: FilterSpec -> Journal -> Journal
|
|
|
|
filterJournalTransactions FilterSpec{datespan=datespan
|
|
|
|
,cleared=cleared
|
|
|
|
-- ,real=real
|
|
|
|
-- ,empty=empty
|
|
|
|
-- ,costbasis=_
|
|
|
|
,acctpats=apats
|
|
|
|
,descpats=dpats
|
|
|
|
,whichdate=whichdate
|
|
|
|
,depth=depth
|
|
|
|
} =
|
|
|
|
filterJournalTransactionsByClearedStatus cleared .
|
|
|
|
filterJournalPostingsByDepth depth .
|
|
|
|
filterJournalTransactionsByAccount apats .
|
|
|
|
filterJournalTransactionsByDescription dpats .
|
|
|
|
filterJournalTransactionsByDate datespan .
|
|
|
|
journalSelectingDate whichdate
|
|
|
|
|
|
|
|
-- | Keep only postings we are interested in, as described by
|
|
|
|
-- the filter specification. May also massage the data a little.
|
|
|
|
-- This can leave unbalanced transactions.
|
|
|
|
filterJournalPostings :: FilterSpec -> Journal -> Journal
|
|
|
|
filterJournalPostings FilterSpec{datespan=datespan
|
|
|
|
,cleared=cleared
|
|
|
|
,real=real
|
|
|
|
,empty=empty
|
|
|
|
-- ,costbasis=costbasis
|
|
|
|
,acctpats=apats
|
|
|
|
,descpats=dpats
|
|
|
|
,whichdate=whichdate
|
|
|
|
,depth=depth
|
|
|
|
} =
|
|
|
|
filterJournalPostingsByRealness real .
|
|
|
|
filterJournalPostingsByClearedStatus cleared .
|
|
|
|
filterJournalPostingsByEmpty empty .
|
|
|
|
filterJournalPostingsByDepth depth .
|
|
|
|
filterJournalPostingsByAccount apats .
|
|
|
|
filterJournalTransactionsByDescription dpats .
|
|
|
|
filterJournalTransactionsByDate datespan .
|
|
|
|
journalSelectingDate whichdate
|
2009-04-03 14:58:05 +04:00
|
|
|
|
|
|
|
-- | Keep only ledger transactions whose description matches the description patterns.
|
2009-12-16 11:07:26 +03:00
|
|
|
filterJournalTransactionsByDescription :: [String] -> Journal -> Journal
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalTransactionsByDescription pats j@Journal{jtxns=ts} = j{jtxns=filter matchdesc ts}
|
2009-12-16 20:58:51 +03:00
|
|
|
where matchdesc = matchpats pats . tdescription
|
2009-04-03 14:58:05 +04:00
|
|
|
|
2009-07-31 21:02:47 +04:00
|
|
|
-- | Keep only ledger transactions which fall between begin and end dates.
|
2009-04-03 14:58:05 +04:00
|
|
|
-- We include transactions on the begin date and exclude transactions on the end
|
2008-10-10 08:23:25 +04:00
|
|
|
-- date, like ledger. An empty date string means no restriction.
|
2009-12-16 11:07:26 +03:00
|
|
|
filterJournalTransactionsByDate :: DateSpan -> Journal -> Journal
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalTransactionsByDate (DateSpan begin end) j@Journal{jtxns=ts} = j{jtxns=filter match ts}
|
|
|
|
where match t = maybe True (tdate t>=) begin && maybe True (tdate t<) end
|
2008-10-10 08:23:25 +04:00
|
|
|
|
2009-04-03 15:45:56 +04:00
|
|
|
-- | Keep only ledger transactions which have the requested
|
|
|
|
-- cleared/uncleared status, if there is one.
|
2009-12-21 08:23:07 +03:00
|
|
|
filterJournalTransactionsByClearedStatus :: Maybe Bool -> Journal -> Journal
|
|
|
|
filterJournalTransactionsByClearedStatus Nothing j = j
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalTransactionsByClearedStatus (Just val) j@Journal{jtxns=ts} = j{jtxns=filter match ts}
|
|
|
|
where match = (==val).tstatus
|
2009-12-21 08:23:07 +03:00
|
|
|
|
|
|
|
-- | Keep only postings which have the requested cleared/uncleared status,
|
|
|
|
-- if there is one.
|
2009-12-16 10:58:06 +03:00
|
|
|
filterJournalPostingsByClearedStatus :: Maybe Bool -> Journal -> Journal
|
2009-12-19 08:57:54 +03:00
|
|
|
filterJournalPostingsByClearedStatus Nothing j = j
|
2009-12-21 08:23:07 +03:00
|
|
|
filterJournalPostingsByClearedStatus (Just c) j@Journal{jtxns=ts} = j{jtxns=map filterpostings ts}
|
|
|
|
where filterpostings t@Transaction{tpostings=ps} = t{tpostings=filter ((==c) . postingCleared) ps}
|
2008-10-15 04:34:02 +04:00
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
-- | Strip out any virtual postings, if the flag is true, otherwise do
|
2008-10-17 04:57:00 +04:00
|
|
|
-- no filtering.
|
2009-12-16 10:00:43 +03:00
|
|
|
filterJournalPostingsByRealness :: Bool -> Journal -> Journal
|
|
|
|
filterJournalPostingsByRealness False l = l
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalPostingsByRealness True j@Journal{jtxns=ts} = j{jtxns=map filterpostings ts}
|
2009-12-21 08:23:07 +03:00
|
|
|
where filterpostings t@Transaction{tpostings=ps} = t{tpostings=filter isReal ps}
|
|
|
|
|
|
|
|
-- | Strip out any postings with zero amount, unless the flag is true.
|
|
|
|
filterJournalPostingsByEmpty :: Bool -> Journal -> Journal
|
|
|
|
filterJournalPostingsByEmpty True l = l
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalPostingsByEmpty False j@Journal{jtxns=ts} = j{jtxns=map filterpostings ts}
|
2009-12-21 08:23:07 +03:00
|
|
|
where filterpostings t@Transaction{tpostings=ps} = t{tpostings=filter (not . isEmptyPosting) ps}
|
|
|
|
|
|
|
|
-- | Keep only transactions which affect accounts deeper than the specified depth.
|
|
|
|
filterJournalTransactionsByDepth :: Maybe Int -> Journal -> Journal
|
|
|
|
filterJournalTransactionsByDepth Nothing j = j
|
|
|
|
filterJournalTransactionsByDepth (Just d) j@Journal{jtxns=ts} =
|
|
|
|
j{jtxns=(filter (any ((<= d+1) . accountNameLevel . paccount) . tpostings) ts)}
|
2009-04-03 14:58:05 +04:00
|
|
|
|
|
|
|
-- | Strip out any postings to accounts deeper than the specified depth
|
|
|
|
-- (and any ledger transactions which have no postings as a result).
|
2009-12-21 08:23:07 +03:00
|
|
|
filterJournalPostingsByDepth :: Maybe Int -> Journal -> Journal
|
|
|
|
filterJournalPostingsByDepth Nothing j = j
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalPostingsByDepth (Just d) j@Journal{jtxns=ts} =
|
|
|
|
j{jtxns=filter (not . null . tpostings) $ map filtertxns ts}
|
2009-12-16 20:58:51 +03:00
|
|
|
where filtertxns t@Transaction{tpostings=ps} =
|
2009-12-21 08:23:07 +03:00
|
|
|
t{tpostings=filter ((<= d) . accountNameLevel . paccount) ps}
|
2009-04-03 14:58:05 +04:00
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
-- | Keep only transactions which affect accounts matched by the account patterns.
|
|
|
|
filterJournalTransactionsByAccount :: [String] -> Journal -> Journal
|
2009-12-21 08:43:10 +03:00
|
|
|
filterJournalTransactionsByAccount apats j@Journal{jtxns=ts} = j{jtxns=filter match ts}
|
|
|
|
where match = any (matchpats apats . paccount) . tpostings
|
2008-11-22 09:35:10 +03:00
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
-- | Keep only postings which affect accounts matched by the account patterns.
|
|
|
|
-- This can leave transactions unbalanced.
|
|
|
|
filterJournalPostingsByAccount :: [String] -> Journal -> Journal
|
|
|
|
filterJournalPostingsByAccount apats j@Journal{jtxns=ts} = j{jtxns=map filterpostings ts}
|
|
|
|
where filterpostings t@Transaction{tpostings=ps} = t{tpostings=filter (matchpats apats . paccount) ps}
|
|
|
|
|
|
|
|
-- | Convert this journal's transactions' primary date to either the
|
2009-07-09 23:22:27 +04:00
|
|
|
-- actual or effective date.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalSelectingDate :: WhichDate -> Journal -> Journal
|
2009-12-19 08:57:54 +03:00
|
|
|
journalSelectingDate ActualDate j = j
|
|
|
|
journalSelectingDate EffectiveDate j =
|
|
|
|
j{jtxns=map (ledgerTransactionWithDate EffectiveDate) $ jtxns j}
|
2009-07-09 23:22:27 +04:00
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
-- | Convert all the journal's amounts to their canonical display settings.
|
|
|
|
-- Ie, in each commodity, amounts will use the display settings of the first
|
|
|
|
-- amount detected, and the greatest precision of the amounts detected.
|
2009-11-25 15:15:53 +03:00
|
|
|
-- Also, missing unit prices are added if known from the price history.
|
|
|
|
-- Also, amounts are converted to cost basis if that flag is active.
|
2009-12-09 23:51:00 +03:00
|
|
|
-- XXX refactor
|
2009-12-16 10:00:43 +03:00
|
|
|
canonicaliseAmounts :: Bool -> Journal -> Journal
|
2009-12-21 08:43:10 +03:00
|
|
|
canonicaliseAmounts costbasis j@Journal{jtxns=ts} = j{jtxns=map fixledgertransaction ts}
|
2009-07-31 21:02:47 +04:00
|
|
|
where
|
2009-12-16 11:07:26 +03:00
|
|
|
fixledgertransaction (Transaction d ed s c de co ts pr) = Transaction d ed s c de co (map fixrawposting ts) pr
|
2009-11-25 15:15:53 +03:00
|
|
|
where
|
2009-12-19 06:44:52 +03:00
|
|
|
fixrawposting (Posting s ac a c t txn) = Posting s ac (fixmixedamount a) c t txn
|
2009-11-25 15:15:53 +03:00
|
|
|
fixmixedamount (Mixed as) = Mixed $ map fixamount as
|
|
|
|
fixamount = (if costbasis then costOfAmount else id) . fixprice . fixcommodity
|
|
|
|
fixcommodity a = a{commodity=c} where c = canonicalcommoditymap ! symbol (commodity a)
|
|
|
|
canonicalcommoditymap =
|
|
|
|
Map.fromList [(s,firstc{precision=maxp}) | s <- commoditysymbols,
|
2008-12-05 05:09:19 +03:00
|
|
|
let cs = commoditymap ! s,
|
|
|
|
let firstc = head cs,
|
|
|
|
let maxp = maximum $ map precision cs
|
|
|
|
]
|
2009-11-25 15:15:53 +03:00
|
|
|
commoditymap = Map.fromList [(s,commoditieswithsymbol s) | s <- commoditysymbols]
|
|
|
|
commoditieswithsymbol s = filter ((s==) . symbol) commodities
|
|
|
|
commoditysymbols = nub $ map symbol commodities
|
2009-12-19 08:57:54 +03:00
|
|
|
commodities = map commodity (concatMap (amounts . pamount) (journalPostings j)
|
|
|
|
++ concatMap (amounts . hamount) (historical_prices j))
|
2009-12-09 23:51:00 +03:00
|
|
|
fixprice :: Amount -> Amount
|
2009-11-25 15:15:53 +03:00
|
|
|
fixprice a@Amount{price=Just _} = a
|
2009-12-19 08:57:54 +03:00
|
|
|
fixprice a@Amount{commodity=c} = a{price=journalHistoricalPriceFor j d c}
|
2009-12-09 23:51:00 +03:00
|
|
|
|
|
|
|
-- | Get the price for a commodity on the specified day from the price database, if known.
|
|
|
|
-- Does only one lookup step, ie will not look up the price of a price.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalHistoricalPriceFor :: Journal -> Day -> Commodity -> Maybe MixedAmount
|
2009-12-19 08:57:54 +03:00
|
|
|
journalHistoricalPriceFor j d Commodity{symbol=s} = do
|
|
|
|
let ps = reverse $ filter ((<= d).hdate) $ filter ((s==).hsymbol) $ sortBy (comparing hdate) $ historical_prices j
|
2009-12-09 23:51:00 +03:00
|
|
|
case ps of (HistoricalPrice{hamount=a}:_) -> Just $ canonicaliseCommodities a
|
2009-11-25 15:15:53 +03:00
|
|
|
_ -> Nothing
|
2009-12-09 23:51:00 +03:00
|
|
|
where
|
|
|
|
canonicaliseCommodities (Mixed as) = Mixed $ map canonicaliseCommodity as
|
|
|
|
where canonicaliseCommodity a@Amount{commodity=Commodity{symbol=s}} =
|
|
|
|
a{commodity=findWithDefault (error "programmer error: canonicaliseCommodity failed") s canonicalcommoditymap}
|
2008-11-09 00:44:41 +03:00
|
|
|
|
2008-11-22 23:35:17 +03:00
|
|
|
-- | Get just the amounts from a ledger, in the order parsed.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalAmounts :: Journal -> [MixedAmount]
|
2009-12-19 08:57:54 +03:00
|
|
|
journalAmounts = map pamount . journalPostings
|
2008-11-22 23:35:17 +03:00
|
|
|
|
2008-12-05 05:09:19 +03:00
|
|
|
-- | Get just the ammount commodities from a ledger, in the order parsed.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalCommodities :: Journal -> [Commodity]
|
|
|
|
journalCommodities = map commodity . concatMap amounts . journalAmounts
|
2008-12-05 05:09:19 +03:00
|
|
|
|
2008-11-09 01:04:59 +03:00
|
|
|
-- | Get just the amount precisions from a ledger, in the order parsed.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalPrecisions :: Journal -> [Int]
|
|
|
|
journalPrecisions = map precision . journalCommodities
|
2008-11-09 00:44:41 +03:00
|
|
|
|
2009-01-25 10:06:59 +03:00
|
|
|
-- | Close any open timelog sessions using the provided current time.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalConvertTimeLog :: LocalTime -> Journal -> Journal
|
2009-12-16 20:58:51 +03:00
|
|
|
journalConvertTimeLog t l0 = l0 { jtxns = convertedTimeLog ++ jtxns l0
|
2009-01-25 10:06:59 +03:00
|
|
|
, open_timelog_entries = []
|
|
|
|
}
|
|
|
|
where convertedTimeLog = entriesFromTimeLogEntries t $ open_timelog_entries l0
|
2008-12-08 06:45:35 +03:00
|
|
|
|
2009-05-29 14:02:14 +04:00
|
|
|
-- | The (fully specified) date span containing all the raw ledger's transactions,
|
2009-04-04 15:19:15 +04:00
|
|
|
-- or DateSpan Nothing Nothing if there are none.
|
2009-12-16 10:00:43 +03:00
|
|
|
journalDateSpan :: Journal -> DateSpan
|
2009-12-19 08:57:54 +03:00
|
|
|
journalDateSpan j
|
2009-04-04 15:19:15 +04:00
|
|
|
| null ts = DateSpan Nothing Nothing
|
2009-12-16 20:58:51 +03:00
|
|
|
| otherwise = DateSpan (Just $ tdate $ head ts) (Just $ addDays 1 $ tdate $ last ts)
|
2009-04-04 15:19:15 +04:00
|
|
|
where
|
2009-12-19 08:57:54 +03:00
|
|
|
ts = sortBy (comparing tdate) $ jtxns j
|
2009-05-29 15:31:51 +04:00
|
|
|
|
|
|
|
-- | Check if a set of ledger account/description patterns matches the
|
|
|
|
-- given account name or entry description. Patterns are case-insensitive
|
|
|
|
-- regular expression strings; those beginning with - are anti-patterns.
|
|
|
|
matchpats :: [String] -> String -> Bool
|
|
|
|
matchpats pats str =
|
|
|
|
(null positives || any match positives) && (null negatives || not (any match negatives))
|
|
|
|
where
|
|
|
|
(negatives,positives) = partition isnegativepat pats
|
|
|
|
match "" = True
|
2009-06-04 03:19:47 +04:00
|
|
|
match pat = containsRegex (abspat pat) str
|
2009-05-29 15:31:51 +04:00
|
|
|
negateprefix = "not:"
|
2009-09-22 19:56:59 +04:00
|
|
|
isnegativepat = (negateprefix `isPrefixOf`)
|
2009-05-29 15:31:51 +04:00
|
|
|
abspat pat = if isnegativepat pat then drop (length negateprefix) pat else pat
|
2009-12-21 08:23:07 +03:00
|
|
|
|
|
|
|
-- | Calculate the account tree and account balances from a journal's
|
|
|
|
-- postings, and return the results for efficient lookup.
|
2010-05-23 02:05:12 +04:00
|
|
|
journalAccountInfo :: Journal -> (Tree AccountName, Map.Map AccountName Account)
|
|
|
|
journalAccountInfo j = (ant, amap)
|
2009-12-21 08:23:07 +03:00
|
|
|
where
|
2010-05-23 02:05:12 +04:00
|
|
|
(ant, psof, _, inclbalof) = (groupPostings . journalPostings) j
|
2009-12-21 08:23:07 +03:00
|
|
|
amap = Map.fromList [(a, acctinfo a) | a <- flatten ant]
|
|
|
|
acctinfo a = Account a (psof a) (inclbalof a)
|
|
|
|
|
|
|
|
-- | Given a list of postings, return an account name tree and three query
|
|
|
|
-- functions that fetch postings, balance, and subaccount-including
|
|
|
|
-- balance by account name. This factors out common logic from
|
|
|
|
-- cacheLedger and summarisePostingsInDateSpan.
|
|
|
|
groupPostings :: [Posting] -> (Tree AccountName,
|
|
|
|
(AccountName -> [Posting]),
|
|
|
|
(AccountName -> MixedAmount),
|
|
|
|
(AccountName -> MixedAmount))
|
2010-05-23 02:05:12 +04:00
|
|
|
groupPostings ps = (ant, psof, exclbalof, inclbalof)
|
2009-12-21 08:23:07 +03:00
|
|
|
where
|
|
|
|
anames = sort $ nub $ map paccount ps
|
|
|
|
ant = accountNameTreeFrom $ expandAccountNames anames
|
|
|
|
allanames = flatten ant
|
|
|
|
pmap = Map.union (postingsByAccount ps) (Map.fromList [(a,[]) | a <- allanames])
|
|
|
|
psof = (pmap !)
|
|
|
|
balmap = Map.fromList $ flatten $ calculateBalances ant psof
|
|
|
|
exclbalof = fst . (balmap !)
|
|
|
|
inclbalof = snd . (balmap !)
|
|
|
|
|
|
|
|
-- | Add subaccount-excluding and subaccount-including balances to a tree
|
|
|
|
-- of account names somewhat efficiently, given a function that looks up
|
|
|
|
-- transactions by account name.
|
|
|
|
calculateBalances :: Tree AccountName -> (AccountName -> [Posting]) -> Tree (AccountName, (MixedAmount, MixedAmount))
|
|
|
|
calculateBalances ant psof = addbalances ant
|
|
|
|
where
|
|
|
|
addbalances (Node a subs) = Node (a,(bal,bal+subsbal)) subs'
|
|
|
|
where
|
|
|
|
bal = sumPostings $ psof a
|
|
|
|
subsbal = sum $ map (snd . snd . root) subs'
|
|
|
|
subs' = map addbalances subs
|
|
|
|
|
|
|
|
-- | Convert a list of postings to a map from account name to that
|
|
|
|
-- account's postings.
|
|
|
|
postingsByAccount :: [Posting] -> Map.Map AccountName [Posting]
|
|
|
|
postingsByAccount ps = m'
|
|
|
|
where
|
|
|
|
sortedps = sortBy (comparing paccount) ps
|
|
|
|
groupedps = groupBy (\p1 p2 -> paccount p1 == paccount p2) sortedps
|
|
|
|
m' = Map.fromList [(paccount $ head g, g) | g <- groupedps]
|