2008-10-03 06:04:15 +04:00
|
|
|
{-|
|
|
|
|
|
|
|
|
A 'RawLedger' is a parsed ledger file. We call it raw to distinguish from
|
|
|
|
the cached 'Ledger'.
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2008-10-03 04:40:06 +04:00
|
|
|
module Ledger.RawLedger
|
2007-07-02 23:15:39 +04:00
|
|
|
where
|
2008-10-15 04:34:02 +04:00
|
|
|
import qualified Data.Map as Map
|
2008-12-05 05:09:19 +03:00
|
|
|
import Data.Map ((!))
|
2008-10-03 04:05:16 +04:00
|
|
|
import Ledger.Utils
|
2008-10-03 04:12:59 +04:00
|
|
|
import Ledger.Types
|
2008-10-03 04:40:06 +04:00
|
|
|
import Ledger.AccountName
|
2008-10-18 12:39:08 +04:00
|
|
|
import Ledger.Amount
|
2009-07-09 23:22:27 +04:00
|
|
|
import Ledger.LedgerTransaction (ledgerTransactionWithDate)
|
2008-10-03 16:10:05 +04:00
|
|
|
import Ledger.Transaction
|
2009-04-03 14:58:05 +04:00
|
|
|
import Ledger.Posting
|
2008-12-08 06:45:35 +03:00
|
|
|
import Ledger.TimeLog
|
2007-07-02 23:15:39 +04:00
|
|
|
|
|
|
|
|
2008-10-03 02:17:04 +04:00
|
|
|
instance Show RawLedger where
|
2009-04-03 14:58:05 +04:00
|
|
|
show l = printf "RawLedger with %d transactions, %d accounts: %s"
|
|
|
|
((length $ ledger_txns l) +
|
|
|
|
(length $ modifier_txns l) +
|
|
|
|
(length $ periodic_txns l))
|
2008-10-09 13:25:58 +04:00
|
|
|
(length accounts)
|
|
|
|
(show accounts)
|
2008-10-16 01:10:59 +04:00
|
|
|
-- ++ (show $ rawLedgerTransactions l)
|
2008-10-09 13:25:58 +04:00
|
|
|
where accounts = flatten $ rawLedgerAccountNameTree l
|
2008-10-03 16:10:05 +04:00
|
|
|
|
2008-12-08 04:48:03 +03:00
|
|
|
rawLedgerEmpty :: RawLedger
|
2009-04-03 14:58:05 +04:00
|
|
|
rawLedgerEmpty = RawLedger { modifier_txns = []
|
|
|
|
, periodic_txns = []
|
|
|
|
, ledger_txns = []
|
2008-12-08 04:48:03 +03:00
|
|
|
, open_timelog_entries = []
|
2008-12-16 13:54:20 +03:00
|
|
|
, historical_prices = []
|
2008-12-08 04:48:03 +03:00
|
|
|
, final_comment_lines = []
|
2009-04-08 07:40:05 +04:00
|
|
|
, filepath = ""
|
2008-12-08 04:48:03 +03:00
|
|
|
}
|
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
addLedgerTransaction :: LedgerTransaction -> RawLedger -> RawLedger
|
|
|
|
addLedgerTransaction t l0 = l0 { ledger_txns = t : (ledger_txns l0) }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
addModifierTransaction :: ModifierTransaction -> RawLedger -> RawLedger
|
|
|
|
addModifierTransaction mt l0 = l0 { modifier_txns = mt : (modifier_txns l0) }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
addPeriodicTransaction :: PeriodicTransaction -> RawLedger -> RawLedger
|
|
|
|
addPeriodicTransaction pt l0 = l0 { periodic_txns = pt : (periodic_txns l0) }
|
2008-12-08 04:48:03 +03:00
|
|
|
|
2008-12-16 13:54:20 +03:00
|
|
|
addHistoricalPrice :: HistoricalPrice -> RawLedger -> RawLedger
|
|
|
|
addHistoricalPrice h l0 = l0 { historical_prices = h : (historical_prices l0) }
|
|
|
|
|
2008-12-08 04:48:03 +03:00
|
|
|
addTimeLogEntry :: TimeLogEntry -> RawLedger -> RawLedger
|
|
|
|
addTimeLogEntry tle l0 = l0 { open_timelog_entries = tle : (open_timelog_entries l0) }
|
|
|
|
|
2008-10-03 16:10:05 +04:00
|
|
|
rawLedgerTransactions :: RawLedger -> [Transaction]
|
2009-04-03 14:58:05 +04:00
|
|
|
rawLedgerTransactions = txnsof . ledger_txns
|
|
|
|
where txnsof ts = concat $ map flattenLedgerTransaction $ zip ts [1..]
|
2008-10-03 16:10:05 +04:00
|
|
|
|
|
|
|
rawLedgerAccountNamesUsed :: RawLedger -> [AccountName]
|
|
|
|
rawLedgerAccountNamesUsed = accountNamesFromTransactions . rawLedgerTransactions
|
|
|
|
|
|
|
|
rawLedgerAccountNames :: RawLedger -> [AccountName]
|
|
|
|
rawLedgerAccountNames = sort . expandAccountNames . rawLedgerAccountNamesUsed
|
|
|
|
|
|
|
|
rawLedgerAccountNameTree :: RawLedger -> Tree AccountName
|
|
|
|
rawLedgerAccountNameTree l = accountNameTreeFrom $ rawLedgerAccountNames l
|
2008-10-10 08:23:25 +04:00
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
-- | Remove ledger transactions we are not interested in.
|
2008-10-10 08:23:25 +04:00
|
|
|
-- Keep only those which fall between the begin and end dates, and match
|
2008-10-16 13:50:16 +04:00
|
|
|
-- the description pattern, and are cleared or real if those options are active.
|
2009-04-03 15:45:56 +04:00
|
|
|
filterRawLedger :: DateSpan -> [String] -> Maybe Bool -> Bool -> RawLedger -> RawLedger
|
2008-11-27 07:31:01 +03:00
|
|
|
filterRawLedger span pats clearedonly realonly =
|
2009-04-03 14:58:05 +04:00
|
|
|
filterRawLedgerPostingsByRealness realonly .
|
|
|
|
filterRawLedgerTransactionsByClearedStatus clearedonly .
|
|
|
|
filterRawLedgerTransactionsByDate span .
|
|
|
|
filterRawLedgerTransactionsByDescription pats
|
|
|
|
|
|
|
|
-- | Keep only ledger transactions whose description matches the description patterns.
|
|
|
|
filterRawLedgerTransactionsByDescription :: [String] -> RawLedger -> RawLedger
|
2009-04-08 07:40:05 +04:00
|
|
|
filterRawLedgerTransactionsByDescription pats (RawLedger ms ps ts tls hs f fp) =
|
|
|
|
RawLedger ms ps (filter matchdesc ts) tls hs f fp
|
2009-04-03 14:58:05 +04:00
|
|
|
where matchdesc = matchpats pats . ltdescription
|
|
|
|
|
|
|
|
-- | Keep only ledger transactions which fall between begin and end dates.
|
|
|
|
-- 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-04-03 14:58:05 +04:00
|
|
|
filterRawLedgerTransactionsByDate :: DateSpan -> RawLedger -> RawLedger
|
2009-04-08 07:40:05 +04:00
|
|
|
filterRawLedgerTransactionsByDate (DateSpan begin end) (RawLedger ms ps ts tls hs f fp) =
|
|
|
|
RawLedger ms ps (filter matchdate ts) tls hs f fp
|
2008-10-18 04:52:49 +04:00
|
|
|
where
|
2009-04-03 14:58:05 +04:00
|
|
|
matchdate t = (maybe True (ltdate t>=) begin) && (maybe True (ltdate 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.
|
|
|
|
filterRawLedgerTransactionsByClearedStatus :: Maybe Bool -> RawLedger -> RawLedger
|
|
|
|
filterRawLedgerTransactionsByClearedStatus Nothing rl = rl
|
2009-04-08 07:40:05 +04:00
|
|
|
filterRawLedgerTransactionsByClearedStatus (Just val) (RawLedger ms ps ts tls hs f fp) =
|
|
|
|
RawLedger ms ps (filter ((==val).ltstatus) ts) tls hs f fp
|
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-04-03 14:58:05 +04:00
|
|
|
filterRawLedgerPostingsByRealness :: Bool -> RawLedger -> RawLedger
|
|
|
|
filterRawLedgerPostingsByRealness False l = l
|
2009-04-08 07:40:05 +04:00
|
|
|
filterRawLedgerPostingsByRealness True (RawLedger mts pts ts tls hs f fp) =
|
|
|
|
RawLedger mts pts (map filtertxns ts) tls hs f fp
|
2009-04-03 14:58:05 +04:00
|
|
|
where filtertxns t@LedgerTransaction{ltpostings=ps} = t{ltpostings=filter isReal ps}
|
|
|
|
|
|
|
|
-- | Strip out any postings to accounts deeper than the specified depth
|
|
|
|
-- (and any ledger transactions which have no postings as a result).
|
|
|
|
filterRawLedgerPostingsByDepth :: Int -> RawLedger -> RawLedger
|
2009-04-08 07:40:05 +04:00
|
|
|
filterRawLedgerPostingsByDepth depth (RawLedger mts pts ts tls hs f fp) =
|
|
|
|
RawLedger mts pts (filter (not . null . ltpostings) $ map filtertxns ts) tls hs f fp
|
2009-04-03 14:58:05 +04:00
|
|
|
where filtertxns t@LedgerTransaction{ltpostings=ps} =
|
|
|
|
t{ltpostings=filter ((<= depth) . accountNameLevel . paccount) ps}
|
|
|
|
|
|
|
|
-- | Keep only ledger transactions which affect accounts matched by the account patterns.
|
|
|
|
filterRawLedgerTransactionsByAccount :: [String] -> RawLedger -> RawLedger
|
2009-04-08 07:40:05 +04:00
|
|
|
filterRawLedgerTransactionsByAccount apats (RawLedger ms ps ts tls hs f fp) =
|
|
|
|
RawLedger ms ps (filter (any (matchpats apats . paccount) . ltpostings) ts) tls hs f fp
|
2008-11-22 09:35:10 +03:00
|
|
|
|
2009-07-09 23:22:27 +04:00
|
|
|
-- | Convert this ledger's transactions' primary date to either their
|
|
|
|
-- actual or effective date.
|
|
|
|
rawLedgerSelectingDate :: WhichDate -> RawLedger -> RawLedger
|
|
|
|
rawLedgerSelectingDate ActualDate rl = rl
|
|
|
|
rawLedgerSelectingDate EffectiveDate rl =
|
|
|
|
rl{ledger_txns=map (ledgerTransactionWithDate EffectiveDate) $ ledger_txns rl}
|
|
|
|
|
2008-11-09 00:44:41 +03:00
|
|
|
-- | Give all a ledger's amounts their canonical display settings. That
|
2008-11-09 01:02:38 +03:00
|
|
|
-- is, in each commodity, amounts will use the display settings of the
|
|
|
|
-- first amount detected, and the greatest precision of the amounts
|
2008-11-22 23:35:17 +03:00
|
|
|
-- detected. Also, amounts are converted to cost basis if that flag is
|
|
|
|
-- active.
|
|
|
|
canonicaliseAmounts :: Bool -> RawLedger -> RawLedger
|
2009-04-08 07:40:05 +04:00
|
|
|
canonicaliseAmounts costbasis l@(RawLedger ms ps ts tls hs f fp) = RawLedger ms ps (map fixledgertransaction ts) tls hs f fp
|
2008-10-15 04:34:02 +04:00
|
|
|
where
|
2009-07-09 03:37:44 +04:00
|
|
|
fixledgertransaction (LedgerTransaction d ed s c de co ts pr) = LedgerTransaction d ed s c de co (map fixrawposting ts) pr
|
2009-04-03 14:58:05 +04:00
|
|
|
fixrawposting (Posting s ac a c t) = Posting s ac (fixmixedamount a) c t
|
2008-12-05 05:09:19 +03:00
|
|
|
fixmixedamount (Mixed as) = Mixed $ map fixamount as
|
|
|
|
fixamount = fixcommodity . (if costbasis then costOfAmount else id)
|
|
|
|
fixcommodity a = a{commodity=c} where c = canonicalcommoditymap ! (symbol $ commodity a)
|
|
|
|
canonicalcommoditymap =
|
|
|
|
Map.fromList [(s,firstc{precision=maxp}) | s <- commoditysymbols,
|
|
|
|
let cs = commoditymap ! s,
|
|
|
|
let firstc = head cs,
|
|
|
|
let maxp = maximum $ map precision cs
|
|
|
|
]
|
|
|
|
commoditymap = Map.fromList [(s,commoditieswithsymbol s) | s <- commoditysymbols]
|
|
|
|
commoditieswithsymbol s = filter ((s==) . symbol) commodities
|
|
|
|
commoditysymbols = nub $ map symbol commodities
|
2009-04-05 01:26:55 +04:00
|
|
|
commodities = map commodity $ concatMap (amounts . tamount) $ rawLedgerTransactions l
|
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.
|
|
|
|
rawLedgerAmounts :: RawLedger -> [MixedAmount]
|
2009-04-05 01:26:55 +04:00
|
|
|
rawLedgerAmounts = map tamount . rawLedgerTransactions
|
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.
|
|
|
|
rawLedgerCommodities :: RawLedger -> [Commodity]
|
|
|
|
rawLedgerCommodities = map commodity . concatMap amounts . rawLedgerAmounts
|
|
|
|
|
2008-11-09 01:04:59 +03:00
|
|
|
-- | Get just the amount precisions from a ledger, in the order parsed.
|
2008-11-09 00:44:41 +03:00
|
|
|
rawLedgerPrecisions :: RawLedger -> [Int]
|
|
|
|
rawLedgerPrecisions = map precision . rawLedgerCommodities
|
|
|
|
|
2009-01-25 10:06:59 +03:00
|
|
|
-- | Close any open timelog sessions using the provided current time.
|
|
|
|
rawLedgerConvertTimeLog :: LocalTime -> RawLedger -> RawLedger
|
2009-04-03 14:58:05 +04:00
|
|
|
rawLedgerConvertTimeLog t l0 = l0 { ledger_txns = convertedTimeLog ++ ledger_txns 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-04-04 15:19:15 +04: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.
|
|
|
|
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
|
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:"
|
|
|
|
isnegativepat pat = negateprefix `isPrefixOf` pat
|
|
|
|
abspat pat = if isnegativepat pat then drop (length negateprefix) pat else pat
|