{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module Hledger.Reports.PostingsReport (
PostingsReport,
PostingsReportItem,
postingsReport,
mkpostingsReportItem,
tests_PostingsReport
)
where
import Data.List
import Data.List.Extra (nubSort)
import Data.Maybe
import Data.Text (Text)
import Data.Time.Calendar
import Safe (headMay, lastMay)
import Hledger.Data
import Hledger.Query
import Hledger.Utils
import Hledger.Reports.ReportOptions
type PostingsReport = [PostingsReportItem]
type PostingsReportItem = (Maybe Day
,Maybe Day
,Maybe Text
,Posting
,MixedAmount
)
type SummaryPosting = (Posting, Day)
postingsReport :: ReportSpec -> Journal -> PostingsReport
postingsReport :: ReportSpec -> Journal -> PostingsReport
postingsReport rspec :: ReportSpec
rspec@ReportSpec{rsOpts :: ReportSpec -> ReportOpts
rsOpts=ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe NormalSign
Maybe DateSpan
Maybe ValuationType
Interval
Period
StringFormat
Costing
AccountListMode
BalanceType
ReportType
transpose_ :: ReportOpts -> Bool
forecast_ :: ReportOpts -> Maybe DateSpan
color_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
invert_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
pretty_tables_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
drop_ :: ReportOpts -> Int
accountlistmode_ :: ReportOpts -> AccountListMode
balancetype_ :: ReportOpts -> BalanceType
reporttype_ :: ReportOpts -> ReportType
txn_dates_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
average_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
format_ :: ReportOpts -> StringFormat
real_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
date2_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
infer_value_ :: ReportOpts -> Bool
value_ :: ReportOpts -> Maybe ValuationType
cost_ :: ReportOpts -> Costing
statuses_ :: ReportOpts -> [Status]
interval_ :: ReportOpts -> Interval
period_ :: ReportOpts -> Period
transpose_ :: Bool
forecast_ :: Maybe DateSpan
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
pretty_tables_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
balancetype_ :: BalanceType
reporttype_ :: ReportType
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_value_ :: Bool
value_ :: Maybe ValuationType
cost_ :: Costing
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
..}} Journal
j = PostingsReport
items
where
reportspan :: DateSpan
reportspan = Journal -> ReportSpec -> DateSpan
reportSpanBothDates Journal
j ReportSpec
rspec
whichdate :: WhichDate
whichdate = ReportOpts -> WhichDate
whichDateFromOpts ReportOpts
ropts
mdepth :: Maybe Int
mdepth = Query -> Maybe Int
queryDepth (Query -> Maybe Int) -> Query -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Query
rsQuery ReportSpec
rspec
styles :: Map Text AmountStyle
styles = Journal -> Map Text AmountStyle
journalCommodityStyles Journal
j
priceoracle :: PriceOracle
priceoracle = Bool -> Journal -> PriceOracle
journalPriceOracle Bool
infer_value_ Journal
j
multiperiod :: Bool
multiperiod = Interval
interval_ Interval -> Interval -> Bool
forall a. Eq a => a -> a -> Bool
/= Interval
NoInterval
([Posting]
precedingps, [Posting]
reportps) = ReportSpec -> Journal -> DateSpan -> ([Posting], [Posting])
matchedPostingsBeforeAndDuring ReportSpec
rspec Journal
j DateSpan
reportspan
pvalue :: Day -> Posting -> Posting
pvalue Day
periodlast = PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> Costing
-> Maybe ValuationType
-> Posting
-> Posting
postingApplyCostValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast (ReportSpec -> Day
rsToday ReportSpec
rspec) Costing
cost_ Maybe ValuationType
value_
[(Posting, Maybe Day)]
displayps :: [(Posting, Maybe Day)]
| Bool
multiperiod, Just (AtEnd Maybe Text
_) <- Maybe ValuationType
value_ = [(Day -> Posting -> Posting
pvalue Day
lastday Posting
p, Day -> Maybe Day
forall a. a -> Maybe a
Just Day
periodend) | (Posting
p, Day
periodend) <- [Posting] -> [(Posting, Day)]
summariseps [Posting]
reportps, let lastday :: Day
lastday = Integer -> Day -> Day
addDays (-Integer
1) Day
periodend]
| Bool
multiperiod = [(Posting
p, Day -> Maybe Day
forall a. a -> Maybe a
Just Day
periodend) | (Posting
p, Day
periodend) <- [Posting] -> [(Posting, Day)]
summariseps [Posting]
valuedps]
| Bool
otherwise = [(Posting
p, Maybe Day
forall a. Maybe a
Nothing) | Posting
p <- [Posting]
valuedps]
where
summariseps :: [Posting] -> [(Posting, Day)]
summariseps = Interval
-> WhichDate
-> Maybe Int
-> Bool
-> DateSpan
-> [Posting]
-> [(Posting, Day)]
summarisePostingsByInterval Interval
interval_ WhichDate
whichdate Maybe Int
mdepth Bool
showempty DateSpan
reportspan
valuedps :: [Posting]
valuedps = (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Day -> Posting -> Posting
pvalue Day
reportorjournallast) [Posting]
reportps
showempty :: Bool
showempty = Bool
empty_ Bool -> Bool -> Bool
|| Bool
average_
reportorjournallast :: Day
reportorjournallast =
Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe (String -> Day
forall a. String -> a
error' String
"postingsReport: expected a non-empty journal") (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$
ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalLastDay ReportSpec
rspec Journal
j
items :: PostingsReport
items =
String -> PostingsReport -> PostingsReport
forall a. Show a => String -> a -> a
dbg4 String
"postingsReport items" (PostingsReport -> PostingsReport)
-> PostingsReport -> PostingsReport
forall a b. (a -> b) -> a -> b
$
[(Posting, Maybe Day)]
-> (Posting, Maybe Day)
-> WhichDate
-> Maybe Int
-> MixedAmount
-> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
-> Int
-> PostingsReport
postingsReportItems [(Posting, Maybe Day)]
displayps (Posting
nullposting,Maybe Day
forall a. Maybe a
Nothing) WhichDate
whichdate Maybe Int
mdepth MixedAmount
startbal Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalc Int
startnum
where
historical :: Bool
historical = BalanceType
balancetype_ BalanceType -> BalanceType -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceType
HistoricalBalance
startbal :: MixedAmount
startbal | Bool
average_ = if Bool
historical then MixedAmount
precedingavg else MixedAmount
0
| Bool
otherwise = if Bool
historical then MixedAmount
precedingsum else MixedAmount
0
where
precedingsum :: MixedAmount
precedingsum = [Posting] -> MixedAmount
sumPostings ([Posting] -> MixedAmount) -> [Posting] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Day -> Posting -> Posting
pvalue Day
daybeforereportstart) [Posting]
precedingps
precedingavg :: MixedAmount
precedingavg | [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
precedingps = MixedAmount
0
| Bool
otherwise = Quantity -> MixedAmount -> MixedAmount
divideMixedAmount (Int -> Quantity
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Quantity) -> Int -> Quantity
forall a b. (a -> b) -> a -> b
$ [Posting] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Posting]
precedingps) MixedAmount
precedingsum
daybeforereportstart :: Day
daybeforereportstart =
Day -> (Day -> Day) -> Maybe Day -> Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Day
forall a. String -> a
error' String
"postingsReport: expected a non-empty journal")
(Integer -> Day -> Day
addDays (-Integer
1))
(Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalStart ReportSpec
rspec Journal
j
runningcalc :: Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalc = ReportOpts -> Int -> MixedAmount -> MixedAmount -> MixedAmount
registerRunningCalculationFn ReportOpts
ropts
startnum :: Int
startnum = if Bool
historical then [Posting] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Posting]
precedingps Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
1
registerRunningCalculationFn :: ReportOpts -> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
registerRunningCalculationFn :: ReportOpts -> Int -> MixedAmount -> MixedAmount -> MixedAmount
registerRunningCalculationFn ReportOpts
ropts
| ReportOpts -> Bool
average_ ReportOpts
ropts = \Int
i MixedAmount
avg MixedAmount
amt -> MixedAmount
avg MixedAmount -> MixedAmount -> MixedAmount
forall a. Num a => a -> a -> a
+ Quantity -> MixedAmount -> MixedAmount
divideMixedAmount (Int -> Quantity
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) (MixedAmount
amt MixedAmount -> MixedAmount -> MixedAmount
forall a. Num a => a -> a -> a
- MixedAmount
avg)
| Bool
otherwise = \Int
_ MixedAmount
bal MixedAmount
amt -> MixedAmount
bal MixedAmount -> MixedAmount -> MixedAmount
forall a. Num a => a -> a -> a
+ MixedAmount
amt
matchedPostingsBeforeAndDuring :: ReportSpec -> Journal -> DateSpan -> ([Posting],[Posting])
matchedPostingsBeforeAndDuring :: ReportSpec -> Journal -> DateSpan -> ([Posting], [Posting])
matchedPostingsBeforeAndDuring ReportSpec{rsOpts :: ReportSpec -> ReportOpts
rsOpts=ReportOpts
ropts,rsQuery :: ReportSpec -> Query
rsQuery=Query
q} Journal
j (DateSpan Maybe Day
mstart Maybe Day
mend) =
String -> ([Posting], [Posting]) -> ([Posting], [Posting])
forall a. Show a => String -> a -> a
dbg5 String
"beforeps, duringps" (([Posting], [Posting]) -> ([Posting], [Posting]))
-> ([Posting], [Posting]) -> ([Posting], [Posting])
forall a b. (a -> b) -> a -> b
$ (Posting -> Bool) -> [Posting] -> ([Posting], [Posting])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Query
beforestartq Query -> Posting -> Bool
`matchesPosting`) [Posting]
beforeandduringps
where
beforestartq :: Query
beforestartq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg3 String
"beforestartq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ DateSpan -> Query
dateqtype (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing Maybe Day
mstart
beforeandduringps :: [Posting]
beforeandduringps =
String -> [Posting] -> [Posting]
forall a. Show a => String -> a -> a
dbg5 String
"ps5" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ (Posting -> Day) -> [Posting] -> [Posting]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Posting -> Day
sortdate ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$
String -> [Posting] -> [Posting]
forall a. Show a => String -> a -> a
dbg5 String
"ps4" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ (if ReportOpts -> Bool
invert_ ReportOpts
ropts then (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Posting
negatePostingAmount else [Posting] -> [Posting]
forall a. a -> a
id) ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$
String -> [Posting] -> [Posting]
forall a. Show a => String -> a -> a
dbg5 String
"ps3" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Query -> Posting -> Posting
filterPostingAmount Query
symq) ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$
String -> [Posting] -> [Posting]
forall a. Show a => String -> a -> a
dbg5 String
"ps2" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ (if ReportOpts -> Bool
related_ ReportOpts
ropts then (Posting -> [Posting]) -> [Posting] -> [Posting]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Posting -> [Posting]
relatedPostings else [Posting] -> [Posting]
forall a. a -> a
id) ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$
String -> [Posting] -> [Posting]
forall a. Show a => String -> a -> a
dbg5 String
"ps1" ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query
beforeandduringq Query -> Posting -> Bool
`matchesPosting`) ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$
Journal -> [Posting]
journalPostings (Journal -> [Posting]) -> Journal -> [Posting]
forall a b. (a -> b) -> a -> b
$
ReportOpts -> Journal -> Journal
journalSelectingAmountFromOpts ReportOpts
ropts Journal
j
where
beforeandduringq :: Query
beforeandduringq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg4 String
"beforeandduringq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query -> Query
depthless (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Query -> Query
dateless Query
q, Query
beforeendq]
where
depthless :: Query -> Query
depthless = (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDepth)
dateless :: Query -> Query
dateless = (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDateOrDate2)
beforeendq :: Query
beforeendq = DateSpan -> Query
dateqtype (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing Maybe Day
mend
sortdate :: Posting -> Day
sortdate = if ReportOpts -> Bool
date2_ ReportOpts
ropts then Posting -> Day
postingDate2 else Posting -> Day
postingDate
symq :: Query
symq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg4 String
"symq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsSym Query
q
dateqtype :: DateSpan -> Query
dateqtype
| Query -> Bool
queryIsDate2 Query
dateq Bool -> Bool -> Bool
|| (Query -> Bool
queryIsDate Query
dateq Bool -> Bool -> Bool
&& ReportOpts -> Bool
date2_ ReportOpts
ropts) = DateSpan -> Query
Date2
| Bool
otherwise = DateSpan -> Query
Date
where
dateq :: Query
dateq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg4 String
"dateq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDateOrDate2 (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ String -> Query -> Query
forall a. Show a => String -> a -> a
dbg4 String
"q" Query
q
postingsReportItems :: [(Posting,Maybe Day)] -> (Posting,Maybe Day) -> WhichDate -> Maybe Int -> MixedAmount -> (Int -> MixedAmount -> MixedAmount -> MixedAmount) -> Int -> [PostingsReportItem]
postingsReportItems :: [(Posting, Maybe Day)]
-> (Posting, Maybe Day)
-> WhichDate
-> Maybe Int
-> MixedAmount
-> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
-> Int
-> PostingsReport
postingsReportItems [] (Posting, Maybe Day)
_ WhichDate
_ Maybe Int
_ MixedAmount
_ Int -> MixedAmount -> MixedAmount -> MixedAmount
_ Int
_ = []
postingsReportItems ((Posting
p,Maybe Day
menddate):[(Posting, Maybe Day)]
ps) (Posting
pprev,Maybe Day
menddateprev) WhichDate
wd Maybe Int
d MixedAmount
b Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalcfn Int
itemnum =
PostingsReportItem
iPostingsReportItem -> PostingsReport -> PostingsReport
forall a. a -> [a] -> [a]
:([(Posting, Maybe Day)]
-> (Posting, Maybe Day)
-> WhichDate
-> Maybe Int
-> MixedAmount
-> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
-> Int
-> PostingsReport
postingsReportItems [(Posting, Maybe Day)]
ps (Posting
p,Maybe Day
menddate) WhichDate
wd Maybe Int
d MixedAmount
b' Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalcfn (Int
itemnumInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
where
i :: PostingsReportItem
i = Bool
-> Bool
-> WhichDate
-> Maybe Day
-> Posting
-> MixedAmount
-> PostingsReportItem
mkpostingsReportItem Bool
showdate Bool
showdesc WhichDate
wd Maybe Day
menddate Posting
p' MixedAmount
b'
(Bool
showdate, Bool
showdesc) | Maybe Day -> Bool
forall a. Maybe a -> Bool
isJust Maybe Day
menddate = (Maybe Day
menddate Maybe Day -> Maybe Day -> Bool
forall a. Eq a => a -> a -> Bool
/= Maybe Day
menddateprev, Bool
False)
| Bool
otherwise = (Bool
isfirstintxn Bool -> Bool -> Bool
|| Bool
isdifferentdate, Bool
isfirstintxn)
isfirstintxn :: Bool
isfirstintxn = Posting -> Maybe Transaction
ptransaction Posting
p Maybe Transaction -> Maybe Transaction -> Bool
forall a. Eq a => a -> a -> Bool
/= Posting -> Maybe Transaction
ptransaction Posting
pprev
isdifferentdate :: Bool
isdifferentdate = case WhichDate
wd of WhichDate
PrimaryDate -> Posting -> Day
postingDate Posting
p Day -> Day -> Bool
forall a. Eq a => a -> a -> Bool
/= Posting -> Day
postingDate Posting
pprev
WhichDate
SecondaryDate -> Posting -> Day
postingDate2 Posting
p Day -> Day -> Bool
forall a. Eq a => a -> a -> Bool
/= Posting -> Day
postingDate2 Posting
pprev
p' :: Posting
p' = Posting
p{paccount :: Text
paccount= Maybe Int -> Text -> Text
clipOrEllipsifyAccountName Maybe Int
d (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Posting -> Text
paccount Posting
p}
b' :: MixedAmount
b' = Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalcfn Int
itemnum MixedAmount
b (Posting -> MixedAmount
pamount Posting
p)
mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Day -> Posting -> MixedAmount -> PostingsReportItem
mkpostingsReportItem :: Bool
-> Bool
-> WhichDate
-> Maybe Day
-> Posting
-> MixedAmount
-> PostingsReportItem
mkpostingsReportItem Bool
showdate Bool
showdesc WhichDate
wd Maybe Day
menddate Posting
p MixedAmount
b =
(if Bool
showdate then Day -> Maybe Day
forall a. a -> Maybe a
Just Day
date else Maybe Day
forall a. Maybe a
Nothing
,Maybe Day
menddate
,if Bool
showdesc then Transaction -> Text
tdescription (Transaction -> Text) -> Maybe Transaction -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Posting -> Maybe Transaction
ptransaction Posting
p else Maybe Text
forall a. Maybe a
Nothing
,Posting
p
,MixedAmount
b
)
where
date :: Day
date = case WhichDate
wd of WhichDate
PrimaryDate -> Posting -> Day
postingDate Posting
p
WhichDate
SecondaryDate -> Posting -> Day
postingDate2 Posting
p
summarisePostingsByInterval :: Interval -> WhichDate -> Maybe Int -> Bool -> DateSpan -> [Posting] -> [SummaryPosting]
summarisePostingsByInterval :: Interval
-> WhichDate
-> Maybe Int
-> Bool
-> DateSpan
-> [Posting]
-> [(Posting, Day)]
summarisePostingsByInterval Interval
interval WhichDate
wd Maybe Int
mdepth Bool
showempty DateSpan
reportspan [Posting]
ps = (DateSpan -> [(Posting, Day)]) -> [DateSpan] -> [(Posting, Day)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DateSpan -> [(Posting, Day)]
summarisespan ([DateSpan] -> [(Posting, Day)]) -> [DateSpan] -> [(Posting, Day)]
forall a b. (a -> b) -> a -> b
$ Interval -> DateSpan -> [DateSpan]
splitSpan Interval
interval DateSpan
reportspan
where
summarisespan :: DateSpan -> [(Posting, Day)]
summarisespan DateSpan
s = DateSpan
-> WhichDate -> Maybe Int -> Bool -> [Posting] -> [(Posting, Day)]
summarisePostingsInDateSpan DateSpan
s WhichDate
wd Maybe Int
mdepth Bool
showempty (DateSpan -> [Posting]
postingsinspan DateSpan
s)
postingsinspan :: DateSpan -> [Posting]
postingsinspan DateSpan
s = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter (WhichDate -> DateSpan -> Posting -> Bool
isPostingInDateSpan' WhichDate
wd DateSpan
s) [Posting]
ps
summarisePostingsInDateSpan :: DateSpan -> WhichDate -> Maybe Int -> Bool -> [Posting] -> [SummaryPosting]
summarisePostingsInDateSpan :: DateSpan
-> WhichDate -> Maybe Int -> Bool -> [Posting] -> [(Posting, Day)]
summarisePostingsInDateSpan (DateSpan Maybe Day
b Maybe Day
e) WhichDate
wd Maybe Int
mdepth Bool
showempty [Posting]
ps
| [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
ps Bool -> Bool -> Bool
&& (Maybe Day -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Day
b Bool -> Bool -> Bool
|| Maybe Day -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Day
e) = []
| [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
ps Bool -> Bool -> Bool
&& Bool
showempty = [(Posting
summaryp, Day
e')]
| Bool
otherwise = [(Posting, Day)]
summarypes
where
postingdate :: Posting -> Day
postingdate = if WhichDate
wd WhichDate -> WhichDate -> Bool
forall a. Eq a => a -> a -> Bool
== WhichDate
PrimaryDate then Posting -> Day
postingDate else Posting -> Day
postingDate2
b' :: Day
b' = Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe (Day -> (Posting -> Day) -> Maybe Posting -> Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Day
nulldate Posting -> Day
postingdate (Maybe Posting -> Day) -> Maybe Posting -> Day
forall a b. (a -> b) -> a -> b
$ [Posting] -> Maybe Posting
forall a. [a] -> Maybe a
headMay [Posting]
ps) Maybe Day
b
e' :: Day
e' = Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe (Day -> (Posting -> Day) -> Maybe Posting -> Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Integer -> Day -> Day
addDays Integer
1 Day
nulldate) Posting -> Day
postingdate (Maybe Posting -> Day) -> Maybe Posting -> Day
forall a b. (a -> b) -> a -> b
$ [Posting] -> Maybe Posting
forall a. [a] -> Maybe a
lastMay [Posting]
ps) Maybe Day
e
summaryp :: Posting
summaryp = Posting
nullposting{pdate :: Maybe Day
pdate=Day -> Maybe Day
forall a. a -> Maybe a
Just Day
b'}
clippedanames :: [Text]
clippedanames = [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Int -> Text -> Text
clipAccountName Maybe Int
mdepth) [Text]
anames
summaryps :: [Posting]
summaryps | Maybe Int
mdepth Maybe Int -> Maybe Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0 = [Posting
summaryp{paccount :: Text
paccount=Text
"...",pamount :: MixedAmount
pamount=[MixedAmount] -> MixedAmount
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([MixedAmount] -> MixedAmount) -> [MixedAmount] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> MixedAmount
pamount [Posting]
ps}]
| Bool
otherwise = [Posting
summaryp{paccount :: Text
paccount=Text
a,pamount :: MixedAmount
pamount=Text -> MixedAmount
balance Text
a} | Text
a <- [Text]
clippedanames]
summarypes :: [(Posting, Day)]
summarypes = (Posting -> (Posting, Day)) -> [Posting] -> [(Posting, Day)]
forall a b. (a -> b) -> [a] -> [b]
map (, Day
e') ([Posting] -> [(Posting, Day)]) -> [Posting] -> [(Posting, Day)]
forall a b. (a -> b) -> a -> b
$ (if Bool
showempty then [Posting] -> [Posting]
forall a. a -> a
id else (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Posting -> Bool) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> Bool
mixedAmountLooksZero (MixedAmount -> Bool)
-> (Posting -> MixedAmount) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> MixedAmount
pamount)) [Posting]
summaryps
anames :: [Text]
anames = [Text] -> [Text]
forall a. Ord a => [a] -> [a]
nubSort ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Posting -> Text) -> [Posting] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Text
paccount [Posting]
ps
accts :: [Account]
accts = [Posting] -> [Account]
accountsFromPostings [Posting]
ps
balance :: Text -> MixedAmount
balance Text
a = MixedAmount
-> (Account -> MixedAmount) -> Maybe Account -> MixedAmount
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MixedAmount
nullmixedamt Account -> MixedAmount
bal (Maybe Account -> MixedAmount) -> Maybe Account -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Text -> [Account] -> Maybe Account
lookupAccount Text
a [Account]
accts
where
bal :: Account -> MixedAmount
bal = if Text -> Bool
isclipped Text
a then Account -> MixedAmount
aibalance else Account -> MixedAmount
aebalance
isclipped :: Text -> Bool
isclipped Text
a = Bool -> (Int -> Bool) -> Maybe Int -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Text -> Int
accountNameLevel Text
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=) Maybe Int
mdepth
negatePostingAmount :: Posting -> Posting
negatePostingAmount :: Posting -> Posting
negatePostingAmount Posting
p = Posting
p { pamount :: MixedAmount
pamount = MixedAmount -> MixedAmount
forall a. Num a => a -> a
negate (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p }
tests_PostingsReport :: TestTree
tests_PostingsReport = String -> [TestTree] -> TestTree
tests String
"PostingsReport" [
String -> Assertion -> TestTree
test String
"postingsReport" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
let (Query
query, Journal
journal) gives :: (Query, Journal) -> Int -> Assertion
`gives` Int
n = (PostingsReport -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (PostingsReport -> Int) -> PostingsReport -> Int
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PostingsReport
postingsReport ReportSpec
defreportspec{rsQuery :: Query
rsQuery=Query
query} Journal
journal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
n
(Query
Any, Journal
nulljournal) (Query, Journal) -> Int -> Assertion
`gives` Int
0
(Query
Any, Journal
samplejournal) (Query, Journal) -> Int -> Assertion
`gives` Int
13
(Int -> Query
Depth Int
2, Journal
samplejournal) (Query, Journal) -> Int -> Assertion
`gives` Int
13
([Query] -> Query
And [Int -> Query
Depth Int
1, Status -> Query
StatusQ Status
Cleared, Regexp -> Query
Acct (Text -> Regexp
toRegex' Text
"expenses")], Journal
samplejournal) (Query, Journal) -> Int -> Assertion
`gives` Int
2
([Query] -> Query
And [[Query] -> Query
And [Int -> Query
Depth Int
1, Status -> Query
StatusQ Status
Cleared], Regexp -> Query
Acct (Text -> Regexp
toRegex' Text
"expenses")], Journal
samplejournal) (Query, Journal) -> Int -> Assertion
`gives` Int
2
(PostingsReport -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (PostingsReport -> Int) -> PostingsReport -> Int
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PostingsReport
postingsReport ReportSpec
defreportspec Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
13
(PostingsReport -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (PostingsReport -> Int) -> PostingsReport -> Int
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PostingsReport
postingsReport ReportSpec
defreportspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
defreportopts{interval_ :: Interval
interval_=Int -> Interval
Months Int
1}} Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
11
(PostingsReport -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (PostingsReport -> Int) -> PostingsReport -> Int
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PostingsReport
postingsReport ReportSpec
defreportspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
defreportopts{interval_ :: Interval
interval_=Int -> Interval
Months Int
1, empty_ :: Bool
empty_=Bool
True}} Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
20
(PostingsReport -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (PostingsReport -> Int) -> PostingsReport -> Int
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> PostingsReport
postingsReport ReportSpec
defreportspec{rsQuery :: Query
rsQuery=Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"assets:bank:checking"} Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
5
,String -> Assertion -> TestTree
test String
"summarisePostingsByInterval" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
Interval
-> WhichDate
-> Maybe Int
-> Bool
-> DateSpan
-> [Posting]
-> [(Posting, Day)]
summarisePostingsByInterval (Int -> Interval
Quarters Int
1) WhichDate
PrimaryDate Maybe Int
forall a. Maybe a
Nothing Bool
False (Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing Maybe Day
forall a. Maybe a
Nothing) [] [(Posting, Day)] -> [(Posting, Day)] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= []
]