{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module Hledger.Reports.PostingsReport (
PostingsReport,
PostingsReportItem,
postingsReport,
mkpostingsReportItem,
SortSpec,
defsortspec,
tests_PostingsReport
)
where
import Data.List (nub, sortBy, sortOn)
import Data.List.Extra (nubSort)
import Data.Maybe (isJust, isNothing, fromMaybe)
import Data.Ord
import Data.Text (Text)
import Data.Time.Calendar (Day)
import Safe (headMay)
import Hledger.Data
import Hledger.Query
import Hledger.Utils
import Hledger.Reports.ReportOptions
type PostingsReport = [PostingsReportItem]
type PostingsReportItem = (Maybe Day
,Maybe Period
,Maybe Text
,Posting
,MixedAmount
)
instance HasAmounts PostingsReportItem where
styleAmounts :: Map CommoditySymbol AmountStyle
-> PostingsReportItem -> PostingsReportItem
styleAmounts Map CommoditySymbol AmountStyle
styles (Maybe Day
a,Maybe Period
b,Maybe CommoditySymbol
c,Posting
d,MixedAmount
e) = (Maybe Day
a,Maybe Period
b,Maybe CommoditySymbol
c,Map CommoditySymbol AmountStyle -> Posting -> Posting
forall a. HasAmounts a => Map CommoditySymbol AmountStyle -> a -> a
styleAmounts Map CommoditySymbol AmountStyle
styles Posting
d,Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
forall a. HasAmounts a => Map CommoditySymbol AmountStyle -> a -> a
styleAmounts Map CommoditySymbol AmountStyle
styles MixedAmount
e)
type SummaryPosting = (Posting, Period)
postingsReport :: ReportSpec -> Journal -> PostingsReport
postingsReport :: ReportSpec -> Journal -> PostingsReport
postingsReport rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ropts :: ReportOpts
ropts@ReportOpts{Bool
Int
[CommoditySymbol]
[Status]
SortSpec
Maybe CommoditySymbol
Maybe NormalSign
Maybe ValuationType
Maybe ConversionOp
DepthSpec
Interval
Period
StringFormat
Layout
AccountListMode
BalanceAccumulation
BalanceCalculation
period_ :: Period
interval_ :: Interval
statuses_ :: [Status]
conversionop_ :: Maybe ConversionOp
value_ :: Maybe ValuationType
infer_prices_ :: Bool
depth_ :: DepthSpec
date2_ :: Bool
empty_ :: Bool
no_elide_ :: Bool
real_ :: Bool
format_ :: StringFormat
balance_base_url_ :: Maybe CommoditySymbol
pretty_ :: Bool
querystring_ :: [CommoditySymbol]
average_ :: Bool
related_ :: Bool
sortspec_ :: SortSpec
txn_dates_ :: Bool
balancecalc_ :: BalanceCalculation
balanceaccum_ :: BalanceAccumulation
budgetpat_ :: Maybe CommoditySymbol
accountlistmode_ :: AccountListMode
drop_ :: Int
declared_ :: Bool
row_total_ :: Bool
no_total_ :: Bool
summary_only_ :: Bool
show_costs_ :: Bool
sort_amount_ :: Bool
percent_ :: Bool
invert_ :: Bool
normalbalance_ :: Maybe NormalSign
color_ :: Bool
transpose_ :: Bool
layout_ :: Layout
period_ :: ReportOpts -> Period
interval_ :: ReportOpts -> Interval
statuses_ :: ReportOpts -> [Status]
conversionop_ :: ReportOpts -> Maybe ConversionOp
value_ :: ReportOpts -> Maybe ValuationType
infer_prices_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> DepthSpec
date2_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
real_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
balance_base_url_ :: ReportOpts -> Maybe CommoditySymbol
pretty_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [CommoditySymbol]
average_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
sortspec_ :: ReportOpts -> SortSpec
txn_dates_ :: ReportOpts -> Bool
balancecalc_ :: ReportOpts -> BalanceCalculation
balanceaccum_ :: ReportOpts -> BalanceAccumulation
budgetpat_ :: ReportOpts -> Maybe CommoditySymbol
accountlistmode_ :: ReportOpts -> AccountListMode
drop_ :: ReportOpts -> Int
declared_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
summary_only_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
invert_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
color_ :: ReportOpts -> Bool
transpose_ :: ReportOpts -> Bool
layout_ :: ReportOpts -> Layout
..}} Journal
j = PostingsReport
items
where
(DateSpan
reportspan, [DateSpan]
colspans) = Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanBothDates Journal
j ReportSpec
rspec
whichdate :: WhichDate
whichdate = ReportOpts -> WhichDate
whichDate ReportOpts
ropts
depthSpec :: DepthSpec
depthSpec = Query -> DepthSpec
queryDepth (Query -> DepthSpec) -> Query -> DepthSpec
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Query
_rsQuery ReportSpec
rspec
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
[(Posting, Maybe Period)]
displayps :: [(Posting, Maybe Period)]
| Bool
multiperiod = [(Posting
p', Period -> Maybe Period
forall a. a -> Maybe a
Just Period
period') | (Posting
p', Period
period') <- [Posting] -> [(Posting, Period)]
summariseps [Posting]
reportps]
| Bool
otherwise = [(Posting
p', Maybe Period
forall a. Maybe a
Nothing) | Posting
p' <- [Posting]
reportps]
where
summariseps :: [Posting] -> [(Posting, Period)]
summariseps = WhichDate
-> Maybe Int
-> Bool
-> [DateSpan]
-> [Posting]
-> [(Posting, Period)]
summarisePostingsByInterval WhichDate
whichdate (DepthSpec -> Maybe Int
dsFlatDepth DepthSpec
depthSpec) Bool
showempty [DateSpan]
colspans
showempty :: Bool
showempty = Bool
empty_ Bool -> Bool -> Bool
|| Bool
average_
sortedps :: [(Posting, Maybe Period)]
sortedps = if SortSpec
sortspec_ SortSpec -> SortSpec -> Bool
forall a. Eq a => a -> a -> Bool
/= SortSpec
defsortspec then ReportOpts
-> SortSpec
-> [(Posting, Maybe Period)]
-> [(Posting, Maybe Period)]
sortPostings ReportOpts
ropts SortSpec
sortspec_ [(Posting, Maybe Period)]
displayps else [(Posting, Maybe Period)]
displayps
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 Period)]
-> (Posting, Maybe Period)
-> WhichDate
-> DepthSpec
-> MixedAmount
-> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
-> Int
-> PostingsReport
postingsReportItems [(Posting, Maybe Period)]
postings (Posting
nullposting,Maybe Period
forall a. Maybe a
Nothing) WhichDate
whichdate DepthSpec
depthSpec MixedAmount
startbal Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalc Int
startnum
where
historical :: Bool
historical = BalanceAccumulation
balanceaccum_ BalanceAccumulation -> BalanceAccumulation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceAccumulation
Historical
startbal :: MixedAmount
startbal | Bool
average_ = if Bool
historical then MixedAmount
precedingavg else MixedAmount
nullmixedamt
| Bool
otherwise = if Bool
historical then MixedAmount
precedingsum else MixedAmount
nullmixedamt
where
precedingsum :: MixedAmount
precedingsum = [Posting] -> MixedAmount
sumPostings [Posting]
precedingps
precedingavg :: MixedAmount
precedingavg = 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 a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Posting]
precedingps) MixedAmount
precedingsum
runningcalc :: Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalc = ReportOpts -> Int -> MixedAmount -> MixedAmount -> MixedAmount
registerRunningCalculationFn ReportOpts
ropts
startnum :: Int
startnum = if Bool
historical then [Posting] -> Int
forall a. [a] -> 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
postings :: [(Posting, Maybe Period)]
postings | Bool
historical = if SortSpec
sortspec_ SortSpec -> SortSpec -> Bool
forall a. Eq a => a -> a -> Bool
/= SortSpec
defsortspec
then String -> [(Posting, Maybe Period)]
forall a. HasCallStack => String -> a
error String
"--historical and --sort should not be used together"
else [(Posting, Maybe Period)]
sortedps
| Bool
otherwise = [(Posting, Maybe Period)]
sortedps
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
`maPlus` Quantity -> MixedAmount -> MixedAmount
divideMixedAmount (Int -> Quantity
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) (MixedAmount
amt MixedAmount -> MixedAmount -> MixedAmount
`maMinus` MixedAmount
avg)
| Bool
otherwise = \Int
_ MixedAmount
bal MixedAmount
amt -> MixedAmount
bal MixedAmount -> MixedAmount -> MixedAmount
`maPlus` MixedAmount
amt
comparePostings :: ReportOpts -> SortSpec -> (Posting, Maybe Period) -> (Posting, Maybe Period) -> Ordering
comparePostings :: ReportOpts
-> SortSpec
-> (Posting, Maybe Period)
-> (Posting, Maybe Period)
-> Ordering
comparePostings ReportOpts
_ [] (Posting, Maybe Period)
_ (Posting, Maybe Period)
_ = Ordering
EQ
comparePostings ReportOpts
ropts (SortField
ex:SortSpec
es) (Posting
a, Maybe Period
pa) (Posting
b, Maybe Period
pb) =
let
getDescription :: Posting -> CommoditySymbol
getDescription Posting
p =
let tx :: Maybe Transaction
tx = Posting -> Maybe Transaction
ptransaction Posting
p
description :: Maybe CommoditySymbol
description = (Transaction -> CommoditySymbol)
-> Maybe Transaction -> Maybe CommoditySymbol
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Transaction
t -> Transaction -> CommoditySymbol
tdescription Transaction
t) Maybe Transaction
tx
in CommoditySymbol -> Maybe CommoditySymbol -> CommoditySymbol
forall a. a -> Maybe a -> a
fromMaybe CommoditySymbol
"" Maybe CommoditySymbol
description
comparison :: Ordering
comparison = case SortField
ex of
AbsAmount' Bool
False -> MixedAmount -> MixedAmount -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (MixedAmount -> MixedAmount
forall a. Num a => a -> a
abs (Posting -> MixedAmount
pamount Posting
a)) (MixedAmount -> MixedAmount
forall a. Num a => a -> a
abs (Posting -> MixedAmount
pamount Posting
b))
Amount' Bool
False -> MixedAmount -> MixedAmount -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Posting -> MixedAmount
pamount Posting
a) (Posting -> MixedAmount
pamount Posting
b)
Account' Bool
False -> CommoditySymbol -> CommoditySymbol -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Posting -> CommoditySymbol
paccount Posting
a) (Posting -> CommoditySymbol
paccount Posting
b)
Date' Bool
False -> Day -> Day -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate ReportOpts
ropts) Posting
a) (WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate ReportOpts
ropts) Posting
b)
Description' Bool
False -> CommoditySymbol -> CommoditySymbol -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Posting -> CommoditySymbol
getDescription Posting
a) (Posting -> CommoditySymbol
getDescription Posting
b)
AbsAmount' Bool
True -> Down MixedAmount -> Down MixedAmount -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (MixedAmount -> Down MixedAmount
forall a. a -> Down a
Down (MixedAmount -> MixedAmount
forall a. Num a => a -> a
abs (Posting -> MixedAmount
pamount Posting
a))) (MixedAmount -> Down MixedAmount
forall a. a -> Down a
Down (MixedAmount -> MixedAmount
forall a. Num a => a -> a
abs (Posting -> MixedAmount
pamount Posting
b)))
Amount' Bool
True -> Down MixedAmount -> Down MixedAmount -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (MixedAmount -> Down MixedAmount
forall a. a -> Down a
Down (Posting -> MixedAmount
pamount Posting
a)) (MixedAmount -> Down MixedAmount
forall a. a -> Down a
Down (Posting -> MixedAmount
pamount Posting
b))
Account' Bool
True -> Down CommoditySymbol -> Down CommoditySymbol -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (CommoditySymbol -> Down CommoditySymbol
forall a. a -> Down a
Down (Posting -> CommoditySymbol
paccount Posting
a)) (CommoditySymbol -> Down CommoditySymbol
forall a. a -> Down a
Down (Posting -> CommoditySymbol
paccount Posting
b))
Date' Bool
True -> Down Day -> Down Day -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Day -> Down Day
forall a. a -> Down a
Down (WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate ReportOpts
ropts) Posting
a)) (Day -> Down Day
forall a. a -> Down a
Down (WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate ReportOpts
ropts) Posting
b))
Description' Bool
True -> Down CommoditySymbol -> Down CommoditySymbol -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (CommoditySymbol -> Down CommoditySymbol
forall a. a -> Down a
Down (Posting -> CommoditySymbol
getDescription Posting
a)) (CommoditySymbol -> Down CommoditySymbol
forall a. a -> Down a
Down (Posting -> CommoditySymbol
getDescription Posting
b))
in
if Ordering
comparison Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ then ReportOpts
-> SortSpec
-> (Posting, Maybe Period)
-> (Posting, Maybe Period)
-> Ordering
comparePostings ReportOpts
ropts SortSpec
es (Posting
a, Maybe Period
pa) (Posting
b, Maybe Period
pb) else Ordering
comparison
sortPostings :: ReportOpts -> SortSpec -> [(Posting, Maybe Period)] -> [(Posting, Maybe Period)]
sortPostings :: ReportOpts
-> SortSpec
-> [(Posting, Maybe Period)]
-> [(Posting, Maybe Period)]
sortPostings ReportOpts
ropts SortSpec
sspec = ((Posting, Maybe Period) -> (Posting, Maybe Period) -> Ordering)
-> [(Posting, Maybe Period)] -> [(Posting, Maybe Period)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (ReportOpts
-> SortSpec
-> (Posting, Maybe Period)
-> (Posting, Maybe Period)
-> Ordering
comparePostings ReportOpts
ropts SortSpec
sspec)
matchedPostingsBeforeAndDuring :: ReportSpec -> Journal -> DateSpan -> ([Posting],[Posting])
matchedPostingsBeforeAndDuring :: ReportSpec -> Journal -> DateSpan -> ([Posting], [Posting])
matchedPostingsBeforeAndDuring rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts,_rsQuery :: ReportSpec -> Query
_rsQuery=Query
q} Journal
j DateSpan
reportspan =
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 EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DateSpan -> Maybe Day
spanStart DateSpan
reportspan)
beforeandduringps :: [Posting]
beforeandduringps =
(Posting -> Day) -> [Posting] -> [Posting]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate ReportOpts
ropts))
([Posting] -> [Posting])
-> (Journal -> [Posting]) -> Journal -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if ReportOpts -> Bool
invert_ ReportOpts
ropts then (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Posting
postingNegateMainAmount else [Posting] -> [Posting]
forall a. a -> a
id)
([Posting] -> [Posting])
-> (Journal -> [Posting]) -> Journal -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Journal -> [Posting]
journalPostings
(Journal -> [Posting])
-> (Journal -> Journal) -> Journal -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if ReportOpts -> Bool
show_costs_ ReportOpts
ropts then Journal -> Journal
forall a. a -> a
id else (MixedAmount -> MixedAmount) -> Journal -> Journal
journalMapPostingAmounts MixedAmount -> MixedAmount
mixedAmountStripCosts)
(Journal -> [Posting]) -> Journal -> [Posting]
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Journal -> Journal
journalValueAndFilterPostings ReportSpec
rspec{_rsQuery=beforeandduringq} Journal
j
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 EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DateSpan -> Maybe Day
spanEnd DateSpan
reportspan)
dateqtype :: DateSpan -> Query
dateqtype = if Query -> Bool
queryIsDate2 Query
dateq Bool -> Bool -> Bool
|| (Query -> Bool
queryIsDate Query
dateq Bool -> Bool -> Bool
&& ReportOpts -> Bool
date2_ ReportOpts
ropts) then DateSpan -> Query
Date2 else DateSpan -> Query
Date
where
dateq :: Query
dateq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg4 String
"matchedPostingsBeforeAndDuring 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
"matchedPostingsBeforeAndDuring q" Query
q
postingsReportItems :: [(Posting,Maybe Period)] -> (Posting,Maybe Period) -> WhichDate -> DepthSpec -> MixedAmount -> (Int -> MixedAmount -> MixedAmount -> MixedAmount) -> Int -> [PostingsReportItem]
postingsReportItems :: [(Posting, Maybe Period)]
-> (Posting, Maybe Period)
-> WhichDate
-> DepthSpec
-> MixedAmount
-> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
-> Int
-> PostingsReport
postingsReportItems [] (Posting, Maybe Period)
_ WhichDate
_ DepthSpec
_ MixedAmount
_ Int -> MixedAmount -> MixedAmount -> MixedAmount
_ Int
_ = []
postingsReportItems ((Posting
p,Maybe Period
mperiod):[(Posting, Maybe Period)]
ps) (Posting
pprev,Maybe Period
mperiodprev) WhichDate
wd DepthSpec
d MixedAmount
b Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalcfn Int
itemnum =
PostingsReportItem
iPostingsReportItem -> PostingsReport -> PostingsReport
forall a. a -> [a] -> [a]
:([(Posting, Maybe Period)]
-> (Posting, Maybe Period)
-> WhichDate
-> DepthSpec
-> MixedAmount
-> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
-> Int
-> PostingsReport
postingsReportItems [(Posting, Maybe Period)]
ps (Posting
p,Maybe Period
mperiod) WhichDate
wd DepthSpec
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 Period
-> Posting
-> MixedAmount
-> PostingsReportItem
mkpostingsReportItem Bool
showdate Bool
showdesc WhichDate
wd Maybe Period
mperiod Posting
p' MixedAmount
b'
(Bool
showdate, Bool
showdesc) | Maybe Period -> Bool
forall a. Maybe a -> Bool
isJust Maybe Period
mperiod = (Maybe Period
mperiod Maybe Period -> Maybe Period -> Bool
forall a. Eq a => a -> a -> Bool
/= Maybe Period
mperiodprev, 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= clipOrEllipsifyAccountName d $ paccount p}
b' :: MixedAmount
b' = Int -> MixedAmount -> MixedAmount -> MixedAmount
runningcalcfn Int
itemnum MixedAmount
b (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p
mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Period -> Posting -> MixedAmount -> PostingsReportItem
mkpostingsReportItem :: Bool
-> Bool
-> WhichDate
-> Maybe Period
-> Posting
-> MixedAmount
-> PostingsReportItem
mkpostingsReportItem Bool
showdate Bool
showdesc WhichDate
wd Maybe Period
mperiod Posting
p MixedAmount
b =
(if Bool
showdate then Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ WhichDate -> Posting -> Day
postingDateOrDate2 WhichDate
wd Posting
p else Maybe Day
forall a. Maybe a
Nothing
,Maybe Period
mperiod
,if Bool
showdesc then Transaction -> CommoditySymbol
tdescription (Transaction -> CommoditySymbol)
-> Maybe Transaction -> Maybe CommoditySymbol
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Posting -> Maybe Transaction
ptransaction Posting
p else Maybe CommoditySymbol
forall a. Maybe a
Nothing
,Posting
p
,MixedAmount
b
)
summarisePostingsByInterval :: WhichDate -> Maybe Int -> Bool -> [DateSpan] -> [Posting] -> [SummaryPosting]
summarisePostingsByInterval :: WhichDate
-> Maybe Int
-> Bool
-> [DateSpan]
-> [Posting]
-> [(Posting, Period)]
summarisePostingsByInterval WhichDate
wd Maybe Int
mdepth Bool
showempty [DateSpan]
colspans =
((DateSpan, [Posting]) -> [(Posting, Period)])
-> [(DateSpan, [Posting])] -> [(Posting, Period)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(DateSpan
s,[Posting]
ps) -> DateSpan
-> WhichDate
-> Maybe Int
-> Bool
-> [Posting]
-> [(Posting, Period)]
summarisePostingsInDateSpan DateSpan
s WhichDate
wd Maybe Int
mdepth Bool
showempty [Posting]
ps)
([(DateSpan, [Posting])] -> [(Posting, Period)])
-> ([Posting] -> [(DateSpan, [Posting])])
-> [Posting]
-> [(Posting, Period)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> (Posting -> Day)
-> [DateSpan]
-> [Posting]
-> [(DateSpan, [Posting])]
forall a.
Bool -> (a -> Day) -> [DateSpan] -> [a] -> [(DateSpan, [a])]
groupByDateSpan Bool
showempty (WhichDate -> Posting -> Day
postingDateOrDate2 WhichDate
wd) [DateSpan]
colspans
summarisePostingsInDateSpan :: DateSpan -> WhichDate -> Maybe Int -> Bool -> [Posting] -> [SummaryPosting]
summarisePostingsInDateSpan :: DateSpan
-> WhichDate
-> Maybe Int
-> Bool
-> [Posting]
-> [(Posting, Period)]
summarisePostingsInDateSpan spn :: DateSpan
spn@(DateSpan Maybe EFDay
b Maybe EFDay
e) WhichDate
wd Maybe Int
mdepth Bool
showempty [Posting]
ps
| [Posting] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
ps Bool -> Bool -> Bool
&& (Maybe EFDay -> Bool
forall a. Maybe a -> Bool
isNothing Maybe EFDay
b Bool -> Bool -> Bool
|| Maybe EFDay -> Bool
forall a. Maybe a -> Bool
isNothing Maybe EFDay
e) = []
| [Posting] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
ps Bool -> Bool -> Bool
&& Bool
showempty = [(Posting
summaryp, DateSpan -> Period
dateSpanAsPeriod DateSpan
spn)]
| Bool
otherwise = [(Posting, Period)]
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 -> (EFDay -> Day) -> Maybe EFDay -> Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (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) EFDay -> Day
fromEFDay Maybe EFDay
b
summaryp :: Posting
summaryp = Posting
nullposting{pdate=Just b'}
clippedanames :: [CommoditySymbol]
clippedanames = [CommoditySymbol] -> [CommoditySymbol]
forall a. Eq a => [a] -> [a]
nub ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ (CommoditySymbol -> CommoditySymbol)
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map (DepthSpec -> CommoditySymbol -> CommoditySymbol
clipAccountName (Maybe Int -> [(Regexp, Int)] -> DepthSpec
DepthSpec Maybe Int
mdepth [])) [CommoditySymbol]
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="...",pamount=sumPostings ps}]
| Bool
otherwise = [Posting
summaryp{paccount=a,pamount=balance a} | CommoditySymbol
a <- [CommoditySymbol]
clippedanames]
summarypes :: [(Posting, Period)]
summarypes = (Posting -> (Posting, Period)) -> [Posting] -> [(Posting, Period)]
forall a b. (a -> b) -> [a] -> [b]
map (, DateSpan -> Period
dateSpanAsPeriod DateSpan
spn) ([Posting] -> [(Posting, Period)])
-> [Posting] -> [(Posting, Period)]
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 :: [CommoditySymbol]
anames = [CommoditySymbol] -> [CommoditySymbol]
forall a. Ord a => [a] -> [a]
nubSort ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ (Posting -> CommoditySymbol) -> [Posting] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> CommoditySymbol
paccount [Posting]
ps
accts :: [Account]
accts = [Posting] -> [Account]
accountsFromPostings [Posting]
ps
balance :: CommoditySymbol -> MixedAmount
balance CommoditySymbol
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
$ CommoditySymbol -> [Account] -> Maybe Account
lookupAccount CommoditySymbol
a [Account]
accts
where
bal :: Account -> MixedAmount
bal = if CommoditySymbol -> Bool
isclipped CommoditySymbol
a then Account -> MixedAmount
aibalance else Account -> MixedAmount
aebalance
isclipped :: CommoditySymbol -> Bool
isclipped CommoditySymbol
a' = Bool -> (Int -> Bool) -> Maybe Int -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (CommoditySymbol -> Int
accountNameLevel CommoditySymbol
a' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=) Maybe Int
mdepth
tests_PostingsReport :: TestTree
tests_PostingsReport = String -> [TestTree] -> TestTree
testGroup String
"PostingsReport" [
String -> Assertion -> TestTree
testCase 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 a. [a] -> 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} 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 (CommoditySymbol -> Regexp
toRegex' CommoditySymbol
"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 (CommoditySymbol -> Regexp
toRegex' CommoditySymbol
"expenses")], Journal
samplejournal) (Query, Journal) -> Int -> Assertion
`gives` Int
2
(PostingsReport -> Int
forall a. [a] -> 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 a. [a] -> 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{_rsReportOpts=defreportopts{interval_=Months 1}} Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
11
(PostingsReport -> Int
forall a. [a] -> 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{_rsReportOpts=defreportopts{interval_=Months 1, empty_=True}} Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
20
(PostingsReport -> Int
forall a. [a] -> 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=Acct $ toRegex' "assets:bank:checking"} Journal
samplejournal) Int -> Int -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int
5
,String -> Assertion -> TestTree
testCase String
"summarisePostingsByInterval" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
WhichDate
-> Maybe Int
-> Bool
-> [DateSpan]
-> [Posting]
-> [(Posting, Period)]
summarisePostingsByInterval WhichDate
PrimaryDate Maybe Int
forall a. Maybe a
Nothing Bool
False [Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing Maybe EFDay
forall a. Maybe a
Nothing] [] [(Posting, Period)] -> [(Posting, Period)] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= []
]