documentation and cleanup for BalanceView
This commit is contained in:
parent
9d817e2d47
commit
b41d11c6e9
@ -1,4 +1,12 @@
|
|||||||
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
|
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
|
||||||
|
{-|
|
||||||
|
|
||||||
|
This module is used by the 'balancesheet', 'incomestatement', and
|
||||||
|
'cashflow' commands to print out acocunt balances based on a specific
|
||||||
|
"view", which consists of a title and multiple named queries that are
|
||||||
|
aggregated and totaled.
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
module Hledger.Cli.BalanceView (
|
module Hledger.Cli.BalanceView (
|
||||||
BalanceView(..)
|
BalanceView(..)
|
||||||
@ -16,15 +24,18 @@ import Hledger
|
|||||||
import Hledger.Cli.Balance
|
import Hledger.Cli.Balance
|
||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
|
|
||||||
data BalanceView = BV { bvmode :: String
|
-- | Describes a view for the balance, which can consist of multiple
|
||||||
, bvaliases :: [String]
|
-- separate named queries that are aggregated and totaled.
|
||||||
, bvhelp :: String
|
data BalanceView = BalanceView {
|
||||||
, bvname :: String
|
bvmode :: String, -- ^ command line mode of the view
|
||||||
, bvqueries :: [(String, Journal -> Query)]
|
bvaliases :: [String], -- ^ command line aliases
|
||||||
}
|
bvhelp :: String, -- ^ command line help message
|
||||||
|
bvtitle :: String, -- ^ title of the view
|
||||||
|
bvqueries :: [(String, Journal -> Query)] -- ^ named queries that make up the view
|
||||||
|
}
|
||||||
|
|
||||||
balanceviewmode :: BalanceView -> Mode RawOpts
|
balanceviewmode :: BalanceView -> Mode RawOpts
|
||||||
balanceviewmode bv@BV{..} = (defCommandMode $ bvmode : bvaliases) {
|
balanceviewmode BalanceView{..} = (defCommandMode $ bvmode : bvaliases) {
|
||||||
modeHelp = bvhelp `withAliases` bvaliases
|
modeHelp = bvhelp `withAliases` bvaliases
|
||||||
,modeGroupFlags = Group {
|
,modeGroupFlags = Group {
|
||||||
groupUnnamed = [
|
groupUnnamed = [
|
||||||
@ -42,25 +53,24 @@ balanceviewmode bv@BV{..} = (defCommandMode $ bvmode : bvaliases) {
|
|||||||
balanceviewQueryReport
|
balanceviewQueryReport
|
||||||
:: ReportOpts
|
:: ReportOpts
|
||||||
-> Day
|
-> Day
|
||||||
-> Maybe Day
|
|
||||||
-> Journal
|
-> Journal
|
||||||
-> String
|
-> String
|
||||||
-> (Journal -> Query)
|
-> (Journal -> Query)
|
||||||
-> ([String], Sum MixedAmount)
|
-> ([String], Sum MixedAmount)
|
||||||
balanceviewQueryReport ropts currDay reportEnd j t q = ([view], Sum amt)
|
balanceviewQueryReport ropts currDay j t q = ([view], Sum amt)
|
||||||
where
|
where
|
||||||
q' = And [queryFromOpts currDay (withoutBeginDate ropts), q j]
|
q' = And [queryFromOpts currDay (withoutBeginDate ropts), q j]
|
||||||
rep@(_ , amt) = balanceReport ropts q' j
|
rep@(_ , amt) = balanceReport ropts q' j
|
||||||
view = intercalate "\n" [t <> ":", balanceReportAsText ropts rep]
|
view = intercalate "\n" [t <> ":", balanceReportAsText ropts rep]
|
||||||
|
|
||||||
|
-- | Prints out a balance report according to a given view
|
||||||
balanceviewReport :: BalanceView -> CliOpts -> Journal -> IO ()
|
balanceviewReport :: BalanceView -> CliOpts -> Journal -> IO ()
|
||||||
balanceviewReport BV{..} CliOpts{reportopts_=ropts} j = do
|
balanceviewReport BalanceView{..} CliOpts{reportopts_=ropts} j = do
|
||||||
currDay <- getCurrentDay
|
currDay <- getCurrentDay
|
||||||
reportEnd <- reportEndDate j ropts
|
|
||||||
let (views, amt) =
|
let (views, amt) =
|
||||||
foldMap (uncurry (balanceviewQueryReport ropts currDay reportEnd j))
|
foldMap (uncurry (balanceviewQueryReport ropts currDay j))
|
||||||
bvqueries
|
bvqueries
|
||||||
mapM_ putStrLn (bvname : "" : views)
|
mapM_ putStrLn (bvtitle : "" : views)
|
||||||
|
|
||||||
unless (no_total_ ropts) . mapM_ putStrLn $
|
unless (no_total_ ropts) . mapM_ putStrLn $
|
||||||
[ "Total:"
|
[ "Total:"
|
||||||
|
|||||||
@ -18,13 +18,15 @@ import Hledger
|
|||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
import Hledger.Cli.BalanceView
|
import Hledger.Cli.BalanceView
|
||||||
|
|
||||||
bsBV = BV "balancesheet"
|
bsBV = BalanceView {
|
||||||
["bs"]
|
bvmode = "balancesheet",
|
||||||
"show a balance sheet"
|
bvaliases = ["bs"],
|
||||||
"Balance Sheet"
|
bvhelp = "show a balance sheet",
|
||||||
[ ("Assets", journalAssetAccountQuery)
|
bvtitle = "Balance Sheet",
|
||||||
, ("Liabilities", journalLiabilityAccountQuery)
|
bvqueries = [ ("Assets" , journalAssetAccountQuery),
|
||||||
]
|
("Liabilities", journalLiabilityAccountQuery)
|
||||||
|
]
|
||||||
|
}
|
||||||
|
|
||||||
balancesheetmode :: Mode RawOpts
|
balancesheetmode :: Mode RawOpts
|
||||||
balancesheetmode = balanceviewmode bsBV
|
balancesheetmode = balanceviewmode bsBV
|
||||||
|
|||||||
@ -21,12 +21,13 @@ import Hledger
|
|||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
import Hledger.Cli.BalanceView
|
import Hledger.Cli.BalanceView
|
||||||
|
|
||||||
cfBV = BV "cashflow"
|
cfBV = BalanceView {
|
||||||
["cf"]
|
bvmode = "cashflow",
|
||||||
"show a cashflow statement statement"
|
bvaliases = ["cf"],
|
||||||
"Cashflow Statement"
|
bvhelp = "show a cashflow statement",
|
||||||
[ ("Cash flows", journalCashAccountQuery)
|
bvtitle = "Cashflow Statement",
|
||||||
]
|
bvqueries = [("Cash flows", journalCashAccountQuery)]
|
||||||
|
}
|
||||||
|
|
||||||
cashflowmode :: Mode RawOpts
|
cashflowmode :: Mode RawOpts
|
||||||
cashflowmode = balanceviewmode cfBV
|
cashflowmode = balanceviewmode cfBV
|
||||||
|
|||||||
@ -18,13 +18,15 @@ import Hledger
|
|||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
import Hledger.Cli.BalanceView
|
import Hledger.Cli.BalanceView
|
||||||
|
|
||||||
isBV = BV "incomestatement"
|
isBV = BalanceView {
|
||||||
["is"]
|
bvmode = "incomestatement",
|
||||||
"show an income statement"
|
bvaliases = ["is"],
|
||||||
"Income Statement"
|
bvhelp = "show an income statement",
|
||||||
[ ("Revenues", journalIncomeAccountQuery)
|
bvtitle = "Income Statement",
|
||||||
, ("Expenses", journalExpenseAccountQuery)
|
bvqueries = [ ("Revenues", journalIncomeAccountQuery),
|
||||||
]
|
("Expenses", journalExpenseAccountQuery)
|
||||||
|
]
|
||||||
|
}
|
||||||
|
|
||||||
incomestatementmode :: Mode RawOpts
|
incomestatementmode :: Mode RawOpts
|
||||||
incomestatementmode = balanceviewmode isBV
|
incomestatementmode = balanceviewmode isBV
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user