;lib: postingsReport cleanup
This commit is contained in:
parent
cc05f48697
commit
66b1599058
@ -8,9 +8,17 @@ value of things at a given date.
|
|||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Hledger.Data.MarketPrice
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
|
||||||
|
module Hledger.Data.MarketPrice (
|
||||||
|
showMarketPrice
|
||||||
|
,postingValueAtDate
|
||||||
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
import Data.List
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
import Data.Time.Calendar
|
||||||
|
|
||||||
import Hledger.Data.Amount
|
import Hledger.Data.Amount
|
||||||
import Hledger.Data.Dates
|
import Hledger.Data.Dates
|
||||||
@ -25,3 +33,12 @@ showMarketPrice mp = unwords
|
|||||||
, T.unpack (mpcommodity mp)
|
, T.unpack (mpcommodity mp)
|
||||||
, (showAmount . setAmountPrecision maxprecision) (mpamount mp)
|
, (showAmount . setAmountPrecision maxprecision) (mpamount mp)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
-- | Convert this posting's amount to its value on the given date in
|
||||||
|
-- its default valuation commodity, using market prices from the given journal.
|
||||||
|
postingValueAtDate :: Journal -> Day -> Posting -> Posting
|
||||||
|
postingValueAtDate j d p@Posting{..} = p{pamount=mixedAmountValue prices d pamount}
|
||||||
|
where
|
||||||
|
-- prices are in parse order - sort into date then parse order,
|
||||||
|
-- & reversed for quick lookup of the latest price.
|
||||||
|
prices = reverse $ sortOn mpdate $ jmarketprices j
|
||||||
|
|||||||
@ -72,47 +72,38 @@ postingsReport ropts@ReportOpts{..} q j =
|
|||||||
(precedingps, reportps) = matchedPostingsBeforeAndDuring ropts q j reportspan
|
(precedingps, reportps) = matchedPostingsBeforeAndDuring ropts q j reportspan
|
||||||
|
|
||||||
-- Postings or summary pseudo postings to be displayed.
|
-- Postings or summary pseudo postings to be displayed.
|
||||||
-- If --value-at is present, we'll need to convert them to value in various ways.
|
-- If --value-at is present, we'll need to convert them to value as of various dates.
|
||||||
displayps
|
displayps =
|
||||||
| multiperiod = case mvalueat of
|
let
|
||||||
Just AtTransaction
|
|
||||||
-> [(postingValueAtDate (postingDate p) p, end) | (p,end) <- summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps]
|
|
||||||
Just AtPeriod
|
|
||||||
-> [(postingValueAtDate (
|
|
||||||
maybe (error' "postingsReport: expected a subperiod end date") -- XXX shouldn't happen
|
|
||||||
(addDays (-1)) end) p
|
|
||||||
, end)
|
|
||||||
| (p,end) <- summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps]
|
|
||||||
Just (AtDate d)
|
|
||||||
-> [(postingValueAtDate d p, end) | (p,end) <- summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps]
|
|
||||||
Just AtNow
|
|
||||||
-> [(postingValueAtDate today p, end) | (p,end) <- summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps]
|
|
||||||
Nothing
|
|
||||||
-> [(p, end) | (p,end) <- summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps]
|
|
||||||
| otherwise = case mvalueat of
|
|
||||||
Just AtTransaction
|
|
||||||
-> [(postingValueAtDate (postingDate p) p, Nothing) | p <- reportps]
|
|
||||||
Just AtPeriod
|
|
||||||
-> [(postingValueAtDate reportperiodlastday p, Nothing) | p <- reportps]
|
|
||||||
Just (AtDate d)
|
|
||||||
-> [(postingValueAtDate d p, Nothing) | p <- reportps]
|
|
||||||
Just AtNow
|
|
||||||
-> [(postingValueAtDate today p, Nothing) | p <- reportps]
|
|
||||||
Nothing
|
|
||||||
-> [(p, Nothing) | p <- reportps]
|
|
||||||
where
|
|
||||||
mvalueat = if value_ then Just value_at_ else Nothing
|
|
||||||
multiperiod = interval_ /= NoInterval
|
multiperiod = interval_ /= NoInterval
|
||||||
showempty = empty_ || average_
|
mvalueat = if value_ then Just value_at_ else Nothing
|
||||||
reportperiodlastday =
|
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
||||||
fromMaybe (error' "postingsReport: expected a non-empty journal") -- XXX shouldn't happen
|
in
|
||||||
$ reportPeriodOrJournalLastDay ropts j
|
if multiperiod then
|
||||||
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
let
|
||||||
postingValueAtDate d p@Posting{..} = p{pamount=mixedAmountValue prices d pamount}
|
showempty = empty_ || average_
|
||||||
where
|
summaryps = summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps
|
||||||
-- prices are in parse order - sort into date then parse order,
|
in case mvalueat of
|
||||||
-- & reversed for quick lookup of the latest price.
|
Nothing -> [(p , periodend) | (p,periodend) <- summaryps]
|
||||||
prices = reverse $ sortOn mpdate $ jmarketprices j
|
Just AtTransaction -> [(postingValueAtDate j (postingDate p) p , periodend) | (p,periodend) <- summaryps]
|
||||||
|
Just AtPeriod -> [(postingValueAtDate j periodlastday p , periodend) | (p,periodend) <- summaryps
|
||||||
|
,let periodlastday = maybe
|
||||||
|
(error' "postingsReport: expected a subperiod end date") -- XXX shouldn't happen
|
||||||
|
(addDays (-1))
|
||||||
|
periodend
|
||||||
|
]
|
||||||
|
Just AtNow -> [(postingValueAtDate j today p , periodend) | (p,periodend) <- summaryps]
|
||||||
|
Just (AtDate d) -> [(postingValueAtDate j d p , periodend) | (p,periodend) <- summaryps]
|
||||||
|
else
|
||||||
|
let reportperiodlastday =
|
||||||
|
fromMaybe (error' "postingsReport: expected a non-empty journal") -- XXX shouldn't happen
|
||||||
|
$ reportPeriodOrJournalLastDay ropts j
|
||||||
|
in case mvalueat of
|
||||||
|
Nothing -> [(p , Nothing) | p <- reportps]
|
||||||
|
Just AtTransaction -> [(postingValueAtDate j (postingDate p) p , Nothing) | p <- reportps]
|
||||||
|
Just AtPeriod -> [(postingValueAtDate j reportperiodlastday p, Nothing) | p <- reportps]
|
||||||
|
Just AtNow -> [(postingValueAtDate j today p , Nothing) | p <- reportps]
|
||||||
|
Just (AtDate d) -> [(postingValueAtDate j d p , Nothing) | p <- reportps]
|
||||||
|
|
||||||
-- posting report items ready for display
|
-- posting report items ready for display
|
||||||
items = dbg1 "postingsReport items" $ postingsReportItems displayps (nullposting,Nothing) whichdate depth startbal runningcalc startnum
|
items = dbg1 "postingsReport items" $ postingsReportItems displayps (nullposting,Nothing) whichdate depth startbal runningcalc startnum
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user