{-# LANGUAGE FlexibleInstances, RecordWildCards, ScopedTypeVariables, OverloadedStrings #-}
module Hledger.Reports.BalanceReport (
  BalanceReport,
  BalanceReportItem,
  balanceReport,
  flatShowsExclusiveBalance,
  
  tests_BalanceReport
)
where
import Data.Time.Calendar
import Hledger.Data
import Hledger.Read (mamountp')
import Hledger.Query
import Hledger.Utils
import Hledger.Reports.MultiBalanceReport (multiBalanceReport)
import Hledger.Reports.ReportOptions
import Hledger.Reports.ReportTypes
type BalanceReport = ([BalanceReportItem], MixedAmount)
type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount)
flatShowsExclusiveBalance :: Bool
flatShowsExclusiveBalance    = Bool
True
balanceReport :: ReportSpec -> Journal -> BalanceReport
balanceReport :: ReportSpec -> Journal -> BalanceReport
balanceReport ReportSpec
rspec Journal
j = ([(AccountName, AccountName, Int, MixedAmount)]
rows, MixedAmount
total)
  where
    report :: MultiBalanceReport
report = ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport ReportSpec
rspec Journal
j
    rows :: [(AccountName, AccountName, Int, MixedAmount)]
rows = [( PeriodicReportRow DisplayName MixedAmount -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrFullName PeriodicReportRow DisplayName MixedAmount
row
            , PeriodicReportRow DisplayName MixedAmount -> AccountName
forall a. PeriodicReportRow DisplayName a -> AccountName
prrDisplayName PeriodicReportRow DisplayName MixedAmount
row
            , PeriodicReportRow DisplayName MixedAmount -> Int
forall a. PeriodicReportRow DisplayName a -> Int
prrDepth PeriodicReportRow DisplayName MixedAmount
row Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1  
            , PeriodicReportRow DisplayName MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal PeriodicReportRow DisplayName MixedAmount
row
            ) | PeriodicReportRow DisplayName MixedAmount
row <- MultiBalanceReport -> [PeriodicReportRow DisplayName MixedAmount]
forall a b. PeriodicReport a b -> [PeriodicReportRow a b]
prRows MultiBalanceReport
report]
    total :: MixedAmount
total = PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal (PeriodicReportRow () MixedAmount -> MixedAmount)
-> PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MultiBalanceReport -> PeriodicReportRow () MixedAmount
forall a b. PeriodicReport a b -> PeriodicReportRow () b
prTotals MultiBalanceReport
report
Right Journal
samplejournal2 =
  Bool -> Journal -> Either String Journal
journalBalanceTransactions Bool
False
    Journal
nulljournal{
      jtxns :: [Transaction]
jtxns = [
        Transaction -> Transaction
txnTieKnot Transaction :: Integer
-> AccountName
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> AccountName
-> AccountName
-> AccountName
-> [Tag]
-> [Posting]
-> Transaction
Transaction{
          tindex :: Integer
tindex=Integer
0,
          tsourcepos :: GenericSourcePos
tsourcepos=GenericSourcePos
nullsourcepos,
          tdate :: Day
tdate=Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
01 Int
01,
          tdate2 :: Maybe Day
tdate2=Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01,
          tstatus :: Status
tstatus=Status
Unmarked,
          tcode :: AccountName
tcode=AccountName
"",
          tdescription :: AccountName
tdescription=AccountName
"income",
          tcomment :: AccountName
tcomment=AccountName
"",
          ttags :: [Tag]
ttags=[],
          tpostings :: [Posting]
tpostings=
            [Posting
posting {paccount :: AccountName
paccount=AccountName
"assets:bank:checking", pamount :: MixedAmount
pamount=[Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1]}
            ,Posting
posting {paccount :: AccountName
paccount=AccountName
"income:salary", pamount :: MixedAmount
pamount=MixedAmount
missingmixedamt}
            ],
          tprecedingcomment :: AccountName
tprecedingcomment=AccountName
""
        }
      ]
    }
tests_BalanceReport :: TestTree
tests_BalanceReport = String -> [TestTree] -> TestTree
tests String
"BalanceReport" [
  let
    (ReportSpec
rspec,Journal
journal) gives :: (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives` BalanceReport
r = do
      let opts' :: ReportSpec
opts' = ReportSpec
rspec{rsQuery :: Query
rsQuery=[Query] -> Query
And [ReportOpts -> Query
queryFromFlags (ReportOpts -> Query) -> ReportOpts -> Query
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
rsOpts ReportSpec
rspec, ReportSpec -> Query
rsQuery ReportSpec
rspec]}
          ([(AccountName, AccountName, Int, MixedAmount)]
eitems, MixedAmount
etotal) = BalanceReport
r
          ([(AccountName, AccountName, Int, MixedAmount)]
aitems, MixedAmount
atotal) = ReportSpec -> Journal -> BalanceReport
balanceReport ReportSpec
opts' Journal
journal
          showw :: (a, b, c, MixedAmount) -> (a, b, c, String)
showw (a
acct,b
acct',c
indent,MixedAmount
amt) = (a
acct, b
acct', c
indent, MixedAmount -> String
showMixedAmountDebug MixedAmount
amt)
      (((AccountName, AccountName, Int, MixedAmount)
 -> (AccountName, AccountName, Int, String))
-> [(AccountName, AccountName, Int, MixedAmount)]
-> [(AccountName, AccountName, Int, String)]
forall a b. (a -> b) -> [a] -> [b]
map (AccountName, AccountName, Int, MixedAmount)
-> (AccountName, AccountName, Int, String)
forall a b c. (a, b, c, MixedAmount) -> (a, b, c, String)
showw [(AccountName, AccountName, Int, MixedAmount)]
aitems) [(AccountName, AccountName, Int, String)]
-> [(AccountName, AccountName, Int, String)] -> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?= (((AccountName, AccountName, Int, MixedAmount)
 -> (AccountName, AccountName, Int, String))
-> [(AccountName, AccountName, Int, MixedAmount)]
-> [(AccountName, AccountName, Int, String)]
forall a b. (a -> b) -> [a] -> [b]
map (AccountName, AccountName, Int, MixedAmount)
-> (AccountName, AccountName, Int, String)
forall a b c. (a, b, c, MixedAmount) -> (a, b, c, String)
showw [(AccountName, AccountName, Int, MixedAmount)]
eitems)
      (MixedAmount -> String
showMixedAmountDebug MixedAmount
atotal) String -> String -> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?= (MixedAmount -> String
showMixedAmountDebug MixedAmount
etotal)
  in
    String -> [TestTree] -> TestTree
tests String
"balanceReport" [
     String -> IO () -> TestTree
test String
"no args, null journal" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec, Journal
nulljournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives` ([], MixedAmount
0)
    ,String -> IO () -> TestTree
test String
"no args, sample journal" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
        (AccountName
"assets:bank:checking",AccountName
"assets:bank:checking",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"assets:bank:saving",AccountName
"assets:bank:saving",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"assets:cash",AccountName
"assets:cash",Int
0, String -> MixedAmount
mamountp' String
"$-2.00")
       ,(AccountName
"expenses:food",AccountName
"expenses:food",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"expenses:supplies",AccountName
"expenses:supplies",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"income:gifts",AccountName
"income:gifts",Int
0, String -> MixedAmount
mamountp' String
"$-1.00")
       ,(AccountName
"income:salary",AccountName
"income:salary",Int
0, String -> MixedAmount
mamountp' String
"$-1.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with --tree" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
defreportopts{accountlistmode_ :: AccountListMode
accountlistmode_=AccountListMode
ALTree}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
        (AccountName
"assets",AccountName
"assets",Int
0, String -> MixedAmount
mamountp' String
"$0.00")
       ,(AccountName
"assets:bank",AccountName
"bank",Int
1, String -> MixedAmount
mamountp' String
"$2.00")
       ,(AccountName
"assets:bank:checking",AccountName
"checking",Int
2, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"assets:bank:saving",AccountName
"saving",Int
2, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"assets:cash",AccountName
"cash",Int
1, String -> MixedAmount
mamountp' String
"$-2.00")
       ,(AccountName
"expenses",AccountName
"expenses",Int
0, String -> MixedAmount
mamountp' String
"$2.00")
       ,(AccountName
"expenses:food",AccountName
"food",Int
1, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"expenses:supplies",AccountName
"supplies",Int
1, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"income",AccountName
"income",Int
0, String -> MixedAmount
mamountp' String
"$-2.00")
       ,(AccountName
"income:gifts",AccountName
"gifts",Int
1, String -> MixedAmount
mamountp' String
"$-1.00")
       ,(AccountName
"income:salary",AccountName
"salary",Int
1, String -> MixedAmount
mamountp' String
"$-1.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with --depth=N" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
defreportopts{depth_ :: Maybe Int
depth_=Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
       (AccountName
"expenses",    AccountName
"expenses",    Int
0, String -> MixedAmount
mamountp'  String
"$2.00")
       ,(AccountName
"income",      AccountName
"income",      Int
0, String -> MixedAmount
mamountp' String
"$-2.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with depth:N" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsQuery :: Query
rsQuery=Int -> Query
Depth Int
1}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
       (AccountName
"expenses",    AccountName
"expenses",    Int
0, String -> MixedAmount
mamountp'  String
"$2.00")
       ,(AccountName
"income",      AccountName
"income",      Int
0, String -> MixedAmount
mamountp' String
"$-2.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with date:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsQuery :: Query
rsQuery=DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe Day -> Maybe Day -> DateSpan
DateSpan (Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01) (Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2010 Int
01 Int
01)}, Journal
samplejournal2) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([], MixedAmount
0)
    ,String -> IO () -> TestTree
test String
"with date2:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsQuery :: Query
rsQuery=DateSpan -> Query
Date2 (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe Day -> Maybe Day -> DateSpan
DateSpan (Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01) (Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2010 Int
01 Int
01)}, Journal
samplejournal2) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
        (AccountName
"assets:bank:checking",AccountName
"assets:bank:checking",Int
0,String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"income:salary",AccountName
"income:salary",Int
0,String -> MixedAmount
mamountp' String
"$-1.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with desc:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsQuery :: Query
rsQuery=Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ String -> Regexp
toRegexCI' String
"income"}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
        (AccountName
"assets:bank:checking",AccountName
"assets:bank:checking",Int
0,String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"income:salary",AccountName
"income:salary",Int
0, String -> MixedAmount
mamountp' String
"$-1.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with not:desc:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
     (ReportSpec
defreportspec{rsQuery :: Query
rsQuery=Query -> Query
Not (Query -> Query) -> (Regexp -> Query) -> Regexp -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ String -> Regexp
toRegexCI' String
"income"}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
      ([
        (AccountName
"assets:bank:saving",AccountName
"assets:bank:saving",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"assets:cash",AccountName
"assets:cash",Int
0, String -> MixedAmount
mamountp' String
"$-2.00")
       ,(AccountName
"expenses:food",AccountName
"expenses:food",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"expenses:supplies",AccountName
"expenses:supplies",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
       ,(AccountName
"income:gifts",AccountName
"income:gifts",Int
0, String -> MixedAmount
mamountp' String
"$-1.00")
       ],
       [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
    ,String -> IO () -> TestTree
test String
"with period on a populated period" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
      (ReportSpec
defreportspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
defreportopts{period_ :: Period
period_= Day -> Day -> Period
PeriodBetween (Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
1 Int
1) (Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
1 Int
2)}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
       (
        [
         (AccountName
"assets:bank:checking",AccountName
"assets:bank:checking",Int
0, String -> MixedAmount
mamountp' String
"$1.00")
        ,(AccountName
"income:salary",AccountName
"income:salary",Int
0, String -> MixedAmount
mamountp' String
"$-1.00")
        ],
        [Amount] -> MixedAmount
Mixed [DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0])
     ,String -> IO () -> TestTree
test String
"with period on an unpopulated period" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
      (ReportSpec
defreportspec{rsOpts :: ReportOpts
rsOpts=ReportOpts
defreportopts{period_ :: Period
period_= Day -> Day -> Period
PeriodBetween (Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
1 Int
2) (Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
1 Int
3)}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
       ([], MixedAmount
0)
  
     ]
 ]