mirror of
https://github.com/simonmichael/hledger.git
synced 2024-11-08 07:09:28 +03:00
refactor: try to get these report names under control
This commit is contained in:
parent
0ebdbff17e
commit
ce30cb2cbe
@ -268,8 +268,8 @@ resetTrailAndEnter d scr a = enter d scr (aargs a) $ clearLocs a
|
||||
updateData :: Day -> AppState -> AppState
|
||||
updateData d a@AppState{aopts=opts,ajournal=j} =
|
||||
case screen a of
|
||||
BalanceScreen -> a{abuf=balanceReportAsText opts $ balanceReport opts fspec j}
|
||||
RegisterScreen -> a{abuf=lines $ postingRegisterReportAsText opts $ postingRegisterReport opts fspec j}
|
||||
BalanceScreen -> a{abuf=accountsReportAsText opts $ accountsReport opts fspec j}
|
||||
RegisterScreen -> a{abuf=lines $ postingsReportAsText opts $ postingsReport opts fspec j}
|
||||
PrintScreen -> a{abuf=lines $ showTransactions opts fspec j}
|
||||
where fspec = optsToFilterSpec opts (currentArgs a) d
|
||||
|
||||
|
@ -61,7 +61,7 @@ getJournalR = do
|
||||
where andsubs = if subs then " (and subaccounts)" else ""
|
||||
where
|
||||
filter = if filtering then ", filtered" else ""
|
||||
maincontent = formattedJournalReportAsHtml opts vd $ journalRegisterReport opts j m
|
||||
maincontent = journalTransactionsReportAsHtml opts vd $ journalTransactionsReport opts j m
|
||||
defaultLayout $ do
|
||||
setTitle "hledger-web journal"
|
||||
addHamlet [$hamlet|
|
||||
@ -126,7 +126,7 @@ getJournalRawR = do
|
||||
let
|
||||
sidecontent = sidebar vd
|
||||
title = "Journal entries" ++ if m /= MatchAny then ", filtered" else "" :: String
|
||||
maincontent = rawJournalReportAsHtml opts vd $ journalReport opts nullfilterspec $ filterJournalTransactions2 m j
|
||||
maincontent = rawJournalReportAsHtml opts vd $ rawJournalReport opts nullfilterspec $ filterJournalTransactions2 m j
|
||||
defaultLayout $ do
|
||||
setTitle "hledger-web journal"
|
||||
addHamlet [$hamlet|
|
||||
@ -150,7 +150,7 @@ getJournalOnlyR = do
|
||||
vd@VD{..} <- getViewData
|
||||
defaultLayout $ do
|
||||
setTitle "hledger-web journal only"
|
||||
addHamlet $ rawJournalReportAsHtml opts vd $ journalReport opts nullfilterspec $ filterJournalTransactions2 m j
|
||||
addHamlet $ rawJournalReportAsHtml opts vd $ rawJournalReport opts nullfilterspec $ filterJournalTransactions2 m j
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
@ -166,7 +166,7 @@ getRegisterR = do
|
||||
(a,subs) = fromMaybe ("all accounts",False) $ inAccount qopts
|
||||
andsubs = if subs then " (and subaccounts)" else ""
|
||||
filter = if filtering then ", filtered" else ""
|
||||
maincontent = registerReportHtml opts vd $ accountRegisterReport opts j m $ fromMaybe MatchAny $ inAccountMatcher qopts
|
||||
maincontent = registerReportHtml opts vd $ accountTransactionsReport opts j m $ fromMaybe MatchAny $ inAccountMatcher qopts
|
||||
defaultLayout $ do
|
||||
setTitle "hledger-web register"
|
||||
addHamlet [$hamlet|
|
||||
@ -191,8 +191,8 @@ getRegisterOnlyR = do
|
||||
defaultLayout $ do
|
||||
setTitle "hledger-web register only"
|
||||
addHamlet $
|
||||
case inAccountMatcher qopts of Just m' -> registerReportHtml opts vd $ accountRegisterReport opts j m m'
|
||||
Nothing -> registerReportHtml opts vd $ journalRegisterReport opts j m
|
||||
case inAccountMatcher qopts of Just m' -> registerReportHtml opts vd $ accountTransactionsReport opts j m m'
|
||||
Nothing -> registerReportHtml opts vd $ journalTransactionsReport opts j m
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
@ -204,7 +204,7 @@ getAccountsR = do
|
||||
let j' = filterJournalPostings2 m j
|
||||
html = do
|
||||
setTitle "hledger-web accounts"
|
||||
addHamlet $ balanceReportAsHtml opts vd $ balanceReport2 opts am j'
|
||||
addHamlet $ accountsReportAsHtml opts vd $ accountsReport2 opts am j'
|
||||
json = jsonMap [("accounts", toJSON $ journalAccountNames j')]
|
||||
defaultLayoutJson html json
|
||||
|
||||
@ -220,11 +220,11 @@ getAccountsJsonR = do
|
||||
|
||||
-- | Render the sidebar used on most views.
|
||||
sidebar :: ViewData -> Hamlet AppRoute
|
||||
sidebar vd@VD{..} = balanceReportAsHtml opts vd $ balanceReport2 opts am j
|
||||
sidebar vd@VD{..} = accountsReportAsHtml opts vd $ accountsReport2 opts am j
|
||||
|
||||
-- | Render a "BalanceReport" as HTML.
|
||||
balanceReportAsHtml :: [Opt] -> ViewData -> BalanceReport -> Hamlet AppRoute
|
||||
balanceReportAsHtml _ vd@VD{..} (items',total) =
|
||||
-- | Render a "AccountsReport" as HTML.
|
||||
accountsReportAsHtml :: [Opt] -> ViewData -> AccountsReport -> Hamlet AppRoute
|
||||
accountsReportAsHtml _ vd@VD{..} (items',total) =
|
||||
[$hamlet|
|
||||
<div#accountsheading
|
||||
<a#accounts-toggle-link.togglelink href="#" title="Toggle sidebar">[+]
|
||||
@ -266,7 +266,7 @@ balanceReportAsHtml _ vd@VD{..} (items',total) =
|
||||
inacctmatcher = inAccountMatcher qopts
|
||||
allaccts = isNothing inacctmatcher
|
||||
items = items' -- maybe items' (\m -> filter (matchesAccount m . \(a,_,_,_)->a) items') showacctmatcher
|
||||
itemAsHtml :: ViewData -> BalanceReportItem -> Hamlet AppRoute
|
||||
itemAsHtml :: ViewData -> AccountsReportItem -> Hamlet AppRoute
|
||||
itemAsHtml _ (acct, adisplay, aindent, abal) = [$hamlet|
|
||||
<tr.item.#{inacctclass}
|
||||
<td.account.#{depthclass}
|
||||
@ -303,15 +303,15 @@ accountOnlyQuery a = "inacctonly:" ++ quoteIfSpaced a -- (accountNameToAccountRe
|
||||
-- accountUrl :: AppRoute -> AccountName -> (AppRoute,[(String,ByteString)])
|
||||
accountUrl r a = (r, [("q",pack $ accountQuery a)])
|
||||
|
||||
-- | Render a "JournalReport" as HTML for the raw journal view.
|
||||
rawJournalReportAsHtml :: [Opt] -> ViewData -> JournalReport -> Hamlet AppRoute
|
||||
-- | Render a "RawJournalReport" as HTML for the raw journal view.
|
||||
rawJournalReportAsHtml :: [Opt] -> ViewData -> RawJournalReport -> Hamlet AppRoute
|
||||
rawJournalReportAsHtml _ vd items = [$hamlet|
|
||||
<table.journalreport>
|
||||
$forall i <- numbered items
|
||||
^{itemAsHtml vd i}
|
||||
|]
|
||||
where
|
||||
itemAsHtml :: ViewData -> (Int, JournalReportItem) -> Hamlet AppRoute
|
||||
itemAsHtml :: ViewData -> (Int, RawJournalReportItem) -> Hamlet AppRoute
|
||||
itemAsHtml _ (n, t) = [$hamlet|
|
||||
<tr.item.#{evenodd}>
|
||||
<td.transaction>
|
||||
@ -321,21 +321,21 @@ rawJournalReportAsHtml _ vd items = [$hamlet|
|
||||
evenodd = if even n then "even" else "odd" :: String
|
||||
txn = trimnl $ showTransaction t where trimnl = reverse . dropWhile (=='\n') . reverse
|
||||
|
||||
-- | Render an "AccountRegisterReport" as HTML for the formatted journal view.
|
||||
formattedJournalReportAsHtml :: [Opt] -> ViewData -> AccountRegisterReport -> Hamlet AppRoute
|
||||
formattedJournalReportAsHtml _ vd (_,items) = [$hamlet|
|
||||
-- | Render an "TransactionsReport" as HTML for the formatted journal view.
|
||||
journalTransactionsReportAsHtml :: [Opt] -> ViewData -> TransactionsReport -> Hamlet AppRoute
|
||||
journalTransactionsReportAsHtml _ vd (_,items) = [$hamlet|
|
||||
<table.journalreport
|
||||
<tr.headings
|
||||
<th.date align=left>Date
|
||||
<th.description align=left>Description
|
||||
<th.account align=left>Accounts
|
||||
<th.amount align=right>Amount
|
||||
$forall i <- numberAccountRegisterReportItems items
|
||||
$forall i <- numberTransactionsReportItems items
|
||||
^{itemAsHtml vd i}
|
||||
|]
|
||||
where
|
||||
-- .#{datetransition}
|
||||
itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, AccountRegisterReportItem) -> Hamlet AppRoute
|
||||
itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> Hamlet AppRoute
|
||||
itemAsHtml VD{..} (n, _, _, _, (t, _, split, _, amt, _)) = [$hamlet|
|
||||
<tr.item.#{evenodd}.#{firstposting}
|
||||
<td.date>#{date}
|
||||
@ -360,14 +360,14 @@ $forall p <- tpostings t
|
||||
showamt = not split || not (isZeroMixedAmount amt)
|
||||
|
||||
-- Generate html for an account register, including a balance chart and transaction list.
|
||||
registerReportHtml :: [Opt] -> ViewData -> AccountRegisterReport -> Hamlet AppRoute
|
||||
registerReportHtml :: [Opt] -> ViewData -> TransactionsReport -> Hamlet AppRoute
|
||||
registerReportHtml opts vd r@(_,items) = [$hamlet|
|
||||
^{registerChartHtml items}
|
||||
^{registerItemsHtml opts vd r}
|
||||
|]
|
||||
|
||||
-- Generate html for a transaction list from an "AccountRegisterReport".
|
||||
registerItemsHtml :: [Opt] -> ViewData -> AccountRegisterReport -> Hamlet AppRoute
|
||||
-- Generate html for a transaction list from an "TransactionsReport".
|
||||
registerItemsHtml :: [Opt] -> ViewData -> TransactionsReport -> Hamlet AppRoute
|
||||
registerItemsHtml _ vd (balancelabel,items) = [$hamlet|
|
||||
<table.registerreport
|
||||
<tr.headings
|
||||
@ -379,13 +379,13 @@ registerItemsHtml _ vd (balancelabel,items) = [$hamlet|
|
||||
<th.amount align=right>Amount
|
||||
<th.balance align=right>#{balancelabel}
|
||||
|
||||
$forall i <- numberAccountRegisterReportItems items
|
||||
$forall i <- numberTransactionsReportItems items
|
||||
^{itemAsHtml vd i}
|
||||
|]
|
||||
where
|
||||
-- inacct = inAccount qopts
|
||||
-- filtering = m /= MatchAny
|
||||
itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, AccountRegisterReportItem) -> Hamlet AppRoute
|
||||
itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> Hamlet AppRoute
|
||||
itemAsHtml VD{..} (n, newd, newm, _, (t, _, split, acct, amt, bal)) = [$hamlet|
|
||||
<tr.item.#{evenodd}.#{firstposting}.#{datetransition}
|
||||
<td.date>#{date}
|
||||
@ -419,7 +419,7 @@ $forall p <- tpostings t
|
||||
displayclass = if p then "" else "hidden" :: String
|
||||
|
||||
-- | Generate javascript/html for a register balance line chart based on
|
||||
-- the provided "AccountRegisterReportItem"s.
|
||||
-- the provided "TransactionsReportItem"s.
|
||||
registerChartHtml items = [$hamlet|
|
||||
<script type=text/javascript>
|
||||
$(document).ready(function() {
|
||||
@ -446,11 +446,11 @@ registerChartHtml items = [$hamlet|
|
||||
stringIfLongerThan :: Int -> String -> String
|
||||
stringIfLongerThan n s = if length s > n then s else ""
|
||||
|
||||
numberAccountRegisterReportItems :: [AccountRegisterReportItem] -> [(Int,Bool,Bool,Bool,AccountRegisterReportItem)]
|
||||
numberAccountRegisterReportItems [] = []
|
||||
numberAccountRegisterReportItems is = number 0 nulldate is
|
||||
numberTransactionsReportItems :: [TransactionsReportItem] -> [(Int,Bool,Bool,Bool,TransactionsReportItem)]
|
||||
numberTransactionsReportItems [] = []
|
||||
numberTransactionsReportItems is = number 0 nulldate is
|
||||
where
|
||||
number :: Int -> Day -> [AccountRegisterReportItem] -> [(Int,Bool,Bool,Bool,AccountRegisterReportItem)]
|
||||
number :: Int -> Day -> [TransactionsReportItem] -> [(Int,Bool,Bool,Bool,TransactionsReportItem)]
|
||||
number _ _ [] = []
|
||||
number n prevd (i@(Transaction{tdate=d},_,_,_,_,_):is) = (n+1,newday,newmonth,newyear,i):(number (n+1) d is)
|
||||
where
|
||||
|
@ -111,7 +111,7 @@ tests_Hledger_Cli = TestList
|
||||
let (opts,args) `gives` es = do
|
||||
j <- samplejournal
|
||||
d <- getCurrentDay
|
||||
balanceReportAsText opts (balanceReport opts (optsToFilterSpec opts args d) j) `is` es
|
||||
accountsReportAsText opts (accountsReport opts (optsToFilterSpec opts args d) j) `is` es
|
||||
in TestList
|
||||
[
|
||||
|
||||
@ -247,7 +247,7 @@ tests_Hledger_Cli = TestList
|
||||
," c:d "
|
||||
]) >>= either error' return
|
||||
let j' = journalCanonicaliseAmounts $ journalConvertAmountsToCost j -- enable cost basis adjustment
|
||||
balanceReportAsText [] (balanceReport [] nullfilterspec j') `is`
|
||||
accountsReportAsText [] (accountsReport [] nullfilterspec j') `is`
|
||||
[" $500 a:b"
|
||||
," $-500 c:d"
|
||||
,"--------------------"
|
||||
@ -261,7 +261,7 @@ tests_Hledger_Cli = TestList
|
||||
," test:a 1"
|
||||
," test:b"
|
||||
])
|
||||
balanceReportAsText [] (balanceReport [] nullfilterspec j) `is`
|
||||
accountsReportAsText [] (accountsReport [] nullfilterspec j) `is`
|
||||
[" 1 test:a"
|
||||
," -1 test:b"
|
||||
,"--------------------"
|
||||
@ -338,7 +338,7 @@ tests_Hledger_Cli = TestList
|
||||
"register report with no args" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
(postingRegisterReportAsText [] $ postingRegisterReport [] (optsToFilterSpec [] [] date1) j) `is` unlines
|
||||
(postingsReportAsText [] $ postingsReport [] (optsToFilterSpec [] [] date1) j) `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank:checking $1 $1"
|
||||
@ -356,7 +356,7 @@ tests_Hledger_Cli = TestList
|
||||
do
|
||||
let opts = [Cleared]
|
||||
j <- readJournal' sample_journal_str
|
||||
(postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
(postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
["2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
," assets:cash $-2 0"
|
||||
@ -368,7 +368,7 @@ tests_Hledger_Cli = TestList
|
||||
do
|
||||
let opts = [UnCleared]
|
||||
j <- readJournal' sample_journal_str
|
||||
(postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
(postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank:checking $1 $1"
|
||||
@ -388,19 +388,19 @@ tests_Hledger_Cli = TestList
|
||||
," e 1"
|
||||
," f"
|
||||
]
|
||||
registerdates (postingRegisterReportAsText [] $ postingRegisterReport [] (optsToFilterSpec [] [] date1) j) `is` ["2008/01/01","2008/02/02"]
|
||||
registerdates (postingsReportAsText [] $ postingsReport [] (optsToFilterSpec [] [] date1) j) `is` ["2008/01/01","2008/02/02"]
|
||||
|
||||
,"register report with account pattern" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
(postingRegisterReportAsText [] $ postingRegisterReport [] (optsToFilterSpec [] ["cash"] date1) j) `is` unlines
|
||||
(postingsReportAsText [] $ postingsReport [] (optsToFilterSpec [] ["cash"] date1) j) `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"register report with account pattern, case insensitive" ~:
|
||||
do
|
||||
j <- samplejournal
|
||||
(postingRegisterReportAsText [] $ postingRegisterReport [] (optsToFilterSpec [] ["cAsH"] date1) j) `is` unlines
|
||||
(postingsReportAsText [] $ postingsReport [] (optsToFilterSpec [] ["cAsH"] date1) j) `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
@ -408,7 +408,7 @@ tests_Hledger_Cli = TestList
|
||||
do
|
||||
j <- samplejournal
|
||||
let gives displayexpr =
|
||||
(registerdates (postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is`)
|
||||
(registerdates (postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is`)
|
||||
where opts = [Display displayexpr]
|
||||
"d<[2008/6/2]" `gives` ["2008/01/01","2008/06/01"]
|
||||
"d<=[2008/6/2]" `gives` ["2008/01/01","2008/06/01","2008/06/02"]
|
||||
@ -421,7 +421,7 @@ tests_Hledger_Cli = TestList
|
||||
j <- samplejournal
|
||||
let periodexpr `gives` dates = do
|
||||
j' <- samplejournal
|
||||
registerdates (postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j') `is` dates
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j') `is` dates
|
||||
where opts = [Period periodexpr]
|
||||
"" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
"2008" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
@ -430,7 +430,7 @@ tests_Hledger_Cli = TestList
|
||||
"monthly" `gives` ["2008/01/01","2008/06/01","2008/12/01"]
|
||||
"quarterly" `gives` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
let opts = [Period "yearly"]
|
||||
(postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
(postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
["2008/01/01 - 2008/12/31 assets:bank:saving $1 $1"
|
||||
," assets:cash $-2 $-1"
|
||||
," expenses:food $1 0"
|
||||
@ -440,9 +440,9 @@ tests_Hledger_Cli = TestList
|
||||
," liabilities:debts $1 0"
|
||||
]
|
||||
let opts = [Period "quarterly"]
|
||||
registerdates (postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is` ["2008/01/01","2008/04/01","2008/10/01"]
|
||||
let opts = [Period "quarterly",Empty]
|
||||
registerdates (postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is` ["2008/01/01","2008/04/01","2008/07/01","2008/10/01"]
|
||||
registerdates (postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is` ["2008/01/01","2008/04/01","2008/07/01","2008/10/01"]
|
||||
|
||||
]
|
||||
|
||||
@ -450,7 +450,7 @@ tests_Hledger_Cli = TestList
|
||||
do
|
||||
j <- samplejournal
|
||||
let opts = [Depth "2"]
|
||||
(postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
(postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] date1) j) `is` unlines
|
||||
["2008/01/01 income assets:bank $1 $1"
|
||||
," income:salary $-1 0"
|
||||
,"2008/06/01 gift assets:bank $1 $1"
|
||||
@ -471,7 +471,7 @@ tests_Hledger_Cli = TestList
|
||||
,"unicode in balance layout" ~: do
|
||||
j <- readJournal'
|
||||
"2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n"
|
||||
balanceReportAsText [] (balanceReport [] (optsToFilterSpec [] [] date1) j) `is`
|
||||
accountsReportAsText [] (accountsReport [] (optsToFilterSpec [] [] date1) j) `is`
|
||||
[" -100 актив:наличные"
|
||||
," 100 расходы:покупки"
|
||||
,"--------------------"
|
||||
@ -481,7 +481,7 @@ tests_Hledger_Cli = TestList
|
||||
,"unicode in register layout" ~: do
|
||||
j <- readJournal'
|
||||
"2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n"
|
||||
(postingRegisterReportAsText [] $ postingRegisterReport [] (optsToFilterSpec [] [] date1) j) `is` unlines
|
||||
(postingsReportAsText [] $ postingsReport [] (optsToFilterSpec [] [] date1) j) `is` unlines
|
||||
["2009/01/01 медвежья шкура расходы:покупки 100 100"
|
||||
," актив:наличные -100 0"]
|
||||
|
||||
|
@ -32,7 +32,7 @@ import Hledger
|
||||
import Prelude hiding (putStr, putStrLn, appendFile)
|
||||
import Hledger.Utils.UTF8 (putStr, putStrLn, appendFile)
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Cli.Register (postingRegisterReportAsText)
|
||||
import Hledger.Cli.Register (postingsReportAsText)
|
||||
import Hledger.Cli.Utils
|
||||
import Hledger.Cli.Reports
|
||||
|
||||
@ -219,7 +219,7 @@ registerFromString :: String -> IO String
|
||||
registerFromString s = do
|
||||
d <- getCurrentDay
|
||||
j <- readJournal' s
|
||||
return $ postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts [] d) j
|
||||
return $ postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts [] d) j
|
||||
where opts = [Empty]
|
||||
|
||||
-- | Return a similarity measure, from 0 to 1, for two strings.
|
||||
|
@ -97,7 +97,7 @@ balance report:
|
||||
|
||||
module Hledger.Cli.Balance (
|
||||
balance
|
||||
,balanceReportAsText
|
||||
,accountsReportAsText
|
||||
,tests_Hledger_Cli_Balance
|
||||
) where
|
||||
|
||||
@ -120,14 +120,14 @@ balance opts args j = do
|
||||
d <- getCurrentDay
|
||||
let lines = case parseFormatFromOpts opts of
|
||||
Left err -> [err]
|
||||
Right _ -> balanceReportAsText opts $ balanceReport opts (optsToFilterSpec opts args d) j
|
||||
Right _ -> accountsReportAsText opts $ accountsReport opts (optsToFilterSpec opts args d) j
|
||||
putStr $ unlines lines
|
||||
|
||||
-- | Render a balance report as plain text suitable for console output.
|
||||
balanceReportAsText :: [Opt] -> BalanceReport -> [String]
|
||||
balanceReportAsText opts (items, total) = concat lines ++ t
|
||||
accountsReportAsText :: [Opt] -> AccountsReport -> [String]
|
||||
accountsReportAsText opts (items, total) = concat lines ++ t
|
||||
where
|
||||
lines = map (balanceReportItemAsText opts format) items
|
||||
lines = map (accountsReportItemAsText opts format) items
|
||||
format = formatFromOpts opts
|
||||
t = if NoTotal `elem` opts
|
||||
then []
|
||||
@ -147,21 +147,21 @@ This implementation turned out to be a bit convoluted but implements the followi
|
||||
b USD -1 ; Account 'b' has two amounts. The account name is printed on the last line.
|
||||
-}
|
||||
-- | Render one balance report line item as plain text.
|
||||
balanceReportItemAsText :: [Opt] -> [FormatString] -> BalanceReportItem -> [String]
|
||||
balanceReportItemAsText opts format (_, accountName, depth, Mixed amounts) =
|
||||
accountsReportItemAsText :: [Opt] -> [FormatString] -> AccountsReportItem -> [String]
|
||||
accountsReportItemAsText opts format (_, accountName, depth, Mixed amounts) =
|
||||
case amounts of
|
||||
[] -> []
|
||||
[a] -> [formatBalanceReportItem opts (Just accountName) depth a format]
|
||||
[a] -> [formatAccountsReportItem opts (Just accountName) depth a format]
|
||||
(as) -> asText as
|
||||
where
|
||||
asText :: [Amount] -> [String]
|
||||
asText [] = []
|
||||
asText [a] = [formatBalanceReportItem opts (Just accountName) depth a format]
|
||||
asText (a:as) = (formatBalanceReportItem opts Nothing depth a format) : asText as
|
||||
asText [a] = [formatAccountsReportItem opts (Just accountName) depth a format]
|
||||
asText (a:as) = (formatAccountsReportItem opts Nothing depth a format) : asText as
|
||||
|
||||
formatBalanceReportItem :: [Opt] -> Maybe AccountName -> Int -> Amount -> [FormatString] -> String
|
||||
formatBalanceReportItem _ _ _ _ [] = ""
|
||||
formatBalanceReportItem opts accountName depth amount (f:fs) = s ++ (formatBalanceReportItem opts accountName depth amount fs)
|
||||
formatAccountsReportItem :: [Opt] -> Maybe AccountName -> Int -> Amount -> [FormatString] -> String
|
||||
formatAccountsReportItem _ _ _ _ [] = ""
|
||||
formatAccountsReportItem opts accountName depth amount (f:fs) = s ++ (formatAccountsReportItem opts accountName depth amount fs)
|
||||
where
|
||||
s = case f of
|
||||
FormatLiteral l -> l
|
||||
|
@ -24,9 +24,9 @@ print' opts args j = do
|
||||
putStr $ showTransactions opts (optsToFilterSpec opts args d) j
|
||||
|
||||
showTransactions :: [Opt] -> FilterSpec -> Journal -> String
|
||||
showTransactions opts fspec j = journalReportAsText opts fspec $ journalReport opts fspec j
|
||||
showTransactions opts fspec j = rawJournalReportAsText opts fspec $ rawJournalReport opts fspec j
|
||||
|
||||
journalReportAsText :: [Opt] -> FilterSpec -> JournalReport -> String
|
||||
journalReportAsText opts _ items = concatMap (showTransactionForPrint effective) items
|
||||
rawJournalReportAsText :: [Opt] -> FilterSpec -> RawJournalReport -> String
|
||||
rawJournalReportAsText opts _ items = concatMap (showTransactionForPrint effective) items
|
||||
where effective = Effective `elem` opts
|
||||
|
||||
|
@ -7,7 +7,7 @@ A ledger-compatible @register@ command.
|
||||
|
||||
module Hledger.Cli.Register (
|
||||
register
|
||||
,postingRegisterReportAsText
|
||||
,postingsReportAsText
|
||||
,showPostingWithBalanceForVty
|
||||
,tests_Hledger_Cli_Register
|
||||
) where
|
||||
@ -28,11 +28,11 @@ import Hledger.Cli.Reports
|
||||
register :: [Opt] -> [String] -> Journal -> IO ()
|
||||
register opts args j = do
|
||||
d <- getCurrentDay
|
||||
putStr $ postingRegisterReportAsText opts $ postingRegisterReport opts (optsToFilterSpec opts args d) j
|
||||
putStr $ postingsReportAsText opts $ postingsReport opts (optsToFilterSpec opts args d) j
|
||||
|
||||
-- | Render a register report as plain text suitable for console output.
|
||||
postingRegisterReportAsText :: [Opt] -> PostingRegisterReport -> String
|
||||
postingRegisterReportAsText opts = unlines . map (postingRegisterReportItemAsText opts) . snd
|
||||
postingsReportAsText :: [Opt] -> PostingsReport -> String
|
||||
postingsReportAsText opts = unlines . map (postingsReportItemAsText opts) . snd
|
||||
|
||||
-- | Render one register report line item as plain text. Eg:
|
||||
-- @
|
||||
@ -41,8 +41,8 @@ postingRegisterReportAsText opts = unlines . map (postingRegisterReportItemAsTex
|
||||
-- ^ displayed for first postings^
|
||||
-- only, otherwise blank
|
||||
-- @
|
||||
postingRegisterReportItemAsText :: [Opt] -> PostingRegisterReportItem -> String
|
||||
postingRegisterReportItemAsText _ (dd, p, b) = concatTopPadded [datedesc, pstr, " ", bal]
|
||||
postingsReportItemAsText :: [Opt] -> PostingsReportItem -> String
|
||||
postingsReportItemAsText _ (dd, p, b) = concatTopPadded [datedesc, pstr, " ", bal]
|
||||
where
|
||||
datedesc = case dd of Nothing -> replicate datedescwidth ' '
|
||||
Just (da, de) -> printf "%s %s " date desc
|
||||
@ -57,7 +57,7 @@ postingRegisterReportItemAsText _ (dd, p, b) = concatTopPadded [datedesc, pstr,
|
||||
bal = padleft 12 (showMixedAmountOrZeroWithoutPrice b)
|
||||
|
||||
-- XXX
|
||||
showPostingWithBalanceForVty showtxninfo p b = postingRegisterReportItemAsText [] $ mkpostingRegisterItem showtxninfo p b
|
||||
showPostingWithBalanceForVty showtxninfo p b = postingsReportItemAsText [] $ mkpostingsReportItem showtxninfo p b
|
||||
|
||||
tests_Hledger_Cli_Register :: Test
|
||||
tests_Hledger_Cli_Register = TestList
|
||||
|
@ -9,27 +9,27 @@ on the command-line options, should move to hledger-lib later.
|
||||
-}
|
||||
|
||||
module Hledger.Cli.Reports (
|
||||
-- * Journal report
|
||||
JournalReport,
|
||||
JournalReportItem,
|
||||
journalReport,
|
||||
-- * Posting register report
|
||||
PostingRegisterReport,
|
||||
PostingRegisterReportItem,
|
||||
postingRegisterReport,
|
||||
mkpostingRegisterItem, -- for silly showPostingWithBalanceForVty in Hledger.Cli.Register
|
||||
journalRegisterReport,
|
||||
-- * Account register report
|
||||
AccountRegisterReport,
|
||||
AccountRegisterReportItem,
|
||||
-- * Raw journal report
|
||||
RawJournalReport,
|
||||
RawJournalReportItem,
|
||||
rawJournalReport,
|
||||
-- * Postings report
|
||||
PostingsReport,
|
||||
PostingsReportItem,
|
||||
postingsReport,
|
||||
mkpostingsReportItem, -- XXX for showPostingWithBalanceForVty in Hledger.Cli.Register
|
||||
-- * Transactions report
|
||||
TransactionsReport,
|
||||
TransactionsReportItem,
|
||||
ariDate,
|
||||
ariBalance,
|
||||
accountRegisterReport,
|
||||
-- * Balance report
|
||||
BalanceReport,
|
||||
BalanceReportItem,
|
||||
balanceReport,
|
||||
balanceReport2,
|
||||
journalTransactionsReport,
|
||||
accountTransactionsReport,
|
||||
-- * Accounts report
|
||||
AccountsReport,
|
||||
AccountsReportItem,
|
||||
accountsReport,
|
||||
accountsReport2,
|
||||
-- * Tests
|
||||
tests_Hledger_Cli_Reports
|
||||
)
|
||||
@ -53,35 +53,33 @@ import Hledger.Cli.Utils
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- | A "journal report" is just a list of transactions.
|
||||
type JournalReport = [JournalReportItem]
|
||||
-- | A raw journal report is a list of transactions used to generate a raw journal view.
|
||||
-- Used by eg hledger's print command.
|
||||
type RawJournalReport = [RawJournalReportItem]
|
||||
type RawJournalReportItem = Transaction
|
||||
|
||||
type JournalReportItem = Transaction
|
||||
|
||||
-- | Select transactions, as in the print command.
|
||||
journalReport :: [Opt] -> FilterSpec -> Journal -> JournalReport
|
||||
journalReport opts fspec j = sortBy (comparing tdate) $ jtxns $ filterJournalTransactions fspec j'
|
||||
-- | Select transactions for a raw journal report.
|
||||
rawJournalReport :: [Opt] -> FilterSpec -> Journal -> RawJournalReport
|
||||
rawJournalReport opts fspec j = sortBy (comparing tdate) $ jtxns $ filterJournalTransactions fspec j'
|
||||
where
|
||||
j' = journalSelectingDateFromOpts opts $ journalSelectingAmountFromOpts opts j
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- | A posting register report lists postings to one or more accounts,
|
||||
-- with a running total. Postings may be actual postings, or aggregate
|
||||
-- postings corresponding to a reporting interval.
|
||||
type PostingRegisterReport = (String -- label for the running balance column XXX remove
|
||||
,[PostingRegisterReportItem] -- line items, one per posting
|
||||
)
|
||||
|
||||
type PostingRegisterReportItem = (Maybe (Day, String) -- transaction date and description if this is the first posting
|
||||
,Posting -- the posting
|
||||
,MixedAmount -- the running total after this posting
|
||||
-- | A postings report is a list of postings with a running total, a label
|
||||
-- for the total field, and a little extra transaction info to help with rendering.
|
||||
type PostingsReport = (String -- label for the running balance column XXX remove
|
||||
,[PostingsReportItem] -- line items, one per posting
|
||||
)
|
||||
type PostingsReportItem = (Maybe (Day, String) -- transaction date and description if this is the first posting
|
||||
,Posting -- the posting
|
||||
,MixedAmount -- the running total after this posting
|
||||
)
|
||||
|
||||
-- | Select postings from the journal and get their running balance, as in
|
||||
-- the register command.
|
||||
postingRegisterReport :: [Opt] -> FilterSpec -> Journal -> PostingRegisterReport
|
||||
postingRegisterReport opts fspec j = (totallabel, postingRegisterItems ps nullposting startbal (+))
|
||||
-- | Select postings from the journal and add running balance and other
|
||||
-- information to make a postings report. Used by eg hledger's register command.
|
||||
postingsReport :: [Opt] -> FilterSpec -> Journal -> PostingsReport
|
||||
postingsReport opts fspec j = (totallabel, postingsReportItems ps nullposting startbal (+))
|
||||
where
|
||||
ps | interval == NoInterval = displayableps
|
||||
| otherwise = summarisePostingsByInterval interval depth empty filterspan displayableps
|
||||
@ -99,21 +97,21 @@ postingRegisterReport opts fspec j = (totallabel, postingRegisterItems ps nullpo
|
||||
totallabel = "Total"
|
||||
balancelabel = "Balance"
|
||||
|
||||
-- | Generate posting register report line items.
|
||||
postingRegisterItems :: [Posting] -> Posting -> MixedAmount -> (MixedAmount -> MixedAmount -> MixedAmount) -> [PostingRegisterReportItem]
|
||||
postingRegisterItems [] _ _ _ = []
|
||||
postingRegisterItems (p:ps) pprev b sumfn = i:(postingRegisterItems ps p b' sumfn)
|
||||
-- | Generate postings report line items.
|
||||
postingsReportItems :: [Posting] -> Posting -> MixedAmount -> (MixedAmount -> MixedAmount -> MixedAmount) -> [PostingsReportItem]
|
||||
postingsReportItems [] _ _ _ = []
|
||||
postingsReportItems (p:ps) pprev b sumfn = i:(postingsReportItems ps p b' sumfn)
|
||||
where
|
||||
i = mkpostingRegisterItem isfirst p b'
|
||||
i = mkpostingsReportItem isfirst p b'
|
||||
isfirst = ptransaction p /= ptransaction pprev
|
||||
b' = b `sumfn` pamount p
|
||||
|
||||
-- | Generate one register report line item, from a flag indicating
|
||||
-- | Generate one postings report line item, from a flag indicating
|
||||
-- whether to include transaction info, a posting, and the current running
|
||||
-- balance.
|
||||
mkpostingRegisterItem :: Bool -> Posting -> MixedAmount -> PostingRegisterReportItem
|
||||
mkpostingRegisterItem False p b = (Nothing, p, b)
|
||||
mkpostingRegisterItem True p b = (ds, p, b)
|
||||
mkpostingsReportItem :: Bool -> Posting -> MixedAmount -> PostingsReportItem
|
||||
mkpostingsReportItem False p b = (Nothing, p, b)
|
||||
mkpostingsReportItem True p b = (ds, p, b)
|
||||
where ds = case ptransaction p of Just (Transaction{tdate=da,tdescription=de}) -> Just (da,de)
|
||||
Nothing -> Just (nulldate,"")
|
||||
|
||||
@ -214,57 +212,56 @@ summarisePostingsInDateSpan (DateSpan b e) depth showempty ps
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- | Select postings from the whole journal and get their running balance.
|
||||
-- Similar to "postingRegisterReport" except it uses matchers and
|
||||
-- per-transaction report items like "accountRegisterReport".
|
||||
journalRegisterReport :: [Opt] -> Journal -> Matcher -> AccountRegisterReport
|
||||
journalRegisterReport _ Journal{jtxns=ts} m = (totallabel, items)
|
||||
where
|
||||
ts' = sortBy (comparing tdate) $ filter (not . null . tpostings) $ map (filterTransactionPostings m) ts
|
||||
items = reverse $ accountRegisterReportItems m Nothing nullmixedamt id ts'
|
||||
-- XXX items' first element should be the full transaction with all postings
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- | An account register report lists transactions to a single account (or
|
||||
-- possibly subs as well), with the accurate running account balance when
|
||||
-- possible (otherwise, a running total.)
|
||||
type AccountRegisterReport = (String -- label for the balance column, eg "balance" or "total"
|
||||
,[AccountRegisterReportItem] -- line items, one per transaction
|
||||
)
|
||||
|
||||
type AccountRegisterReportItem = (Transaction -- the corresponding transaction
|
||||
,Transaction -- the transaction with postings to the focussed account removed
|
||||
,Bool -- is this a split (more than one other-account posting) ?
|
||||
,String -- the (possibly aggregated) account info to display
|
||||
,MixedAmount -- the (possibly aggregated) amount to display (sum of the other-account postings)
|
||||
,MixedAmount -- the running balance for the focussed account after this transaction
|
||||
)
|
||||
-- | A transactions report includes a list of transactions
|
||||
-- (posting-filtered and unfiltered variants), a running balance, and some
|
||||
-- other information helpful for rendering a register view (a flag
|
||||
-- indicating multiple other accounts and a display string describing
|
||||
-- them) with or without a notion of current account(s).
|
||||
type TransactionsReport = (String -- label for the balance column, eg "balance" or "total"
|
||||
,[TransactionsReportItem] -- line items, one per transaction
|
||||
)
|
||||
type TransactionsReportItem = (Transaction -- the corresponding transaction
|
||||
,Transaction -- the transaction with postings to the current account(s) removed
|
||||
,Bool -- is this a split, ie more than one other account posting
|
||||
,String -- a display string describing the other account(s), if any
|
||||
,MixedAmount -- the amount posted to the current account(s) (or total amount posted)
|
||||
,MixedAmount -- the running balance for the current account(s) after this transaction
|
||||
)
|
||||
|
||||
ariDate (t,_,_,_,_,_) = tdate t
|
||||
ariBalance (_,_,_,_,_,Mixed a) = case a of [] -> "0"
|
||||
(Amount{quantity=q}):_ -> show q
|
||||
|
||||
-- | Select transactions within one (or more) specified accounts, and get
|
||||
-- their running balance within that (those) account(s). Used for a
|
||||
-- conventional quicker/gnucash/bank-style account register. Specifically,
|
||||
-- this differs from "postingRegisterReport" as follows:
|
||||
-- | Select transactions from the whole journal for a transactions report,
|
||||
-- with no \"current\" account. The end result is similar to
|
||||
-- "postingsReport" except it uses matchers and transaction-based report
|
||||
-- items and the items are most recent first. Used by eg hledger-web's
|
||||
-- journal view.
|
||||
journalTransactionsReport :: [Opt] -> Journal -> Matcher -> TransactionsReport
|
||||
journalTransactionsReport _ Journal{jtxns=ts} m = (totallabel, items)
|
||||
where
|
||||
ts' = sortBy (comparing tdate) $ filter (not . null . tpostings) $ map (filterTransactionPostings m) ts
|
||||
items = reverse $ accountTransactionsReportItems m Nothing nullmixedamt id ts'
|
||||
-- XXX items' first element should be the full transaction with all postings
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- | Select transactions within one or more \"current\" accounts, and make a
|
||||
-- transactions report relative to those account(s). This means:
|
||||
--
|
||||
-- 1. it shows transactions, from the point of view of the focussed
|
||||
-- account. The other account's name and posted amount is displayed,
|
||||
-- aggregated if there is more than one other account posting.
|
||||
-- 1. it shows transactions from the point of view of the current account(s).
|
||||
-- The transaction amount is the amount posted to the current account(s).
|
||||
-- The other accounts' names are provided.
|
||||
--
|
||||
-- 2. With no transaction filtering in effect other than a start date, it
|
||||
-- shows the accurate historical running balance for this
|
||||
-- account. Otherwise it shows a running total starting at 0 like the
|
||||
-- posting register report.
|
||||
-- shows the accurate historical running balance for the current account(s).
|
||||
-- Otherwise it shows a running total starting at 0.
|
||||
--
|
||||
-- 3. It currently does not handle reporting intervals.
|
||||
-- Currently, reporting intervals are not supported, and report items are
|
||||
-- most recent first. Used by eg hledger-web's account register view.
|
||||
--
|
||||
-- 4. Report items are most recent first.
|
||||
--
|
||||
accountRegisterReport :: [Opt] -> Journal -> Matcher -> Matcher -> AccountRegisterReport
|
||||
accountRegisterReport opts j m thisacctmatcher = (label, items)
|
||||
accountTransactionsReport :: [Opt] -> Journal -> Matcher -> Matcher -> TransactionsReport
|
||||
accountTransactionsReport opts j m thisacctmatcher = (label, items)
|
||||
where
|
||||
-- transactions affecting this account, in date order
|
||||
ts = sortBy (comparing tdate) $ filter (matchesTransaction thisacctmatcher) $ jtxns j
|
||||
@ -282,17 +279,16 @@ accountRegisterReport opts j m thisacctmatcher = (label, items)
|
||||
tostartdatematcher = MatchDate True (DateSpan Nothing startdate)
|
||||
startdate = matcherStartDate effective m
|
||||
effective = Effective `elem` opts
|
||||
items = reverse $ accountRegisterReportItems m (Just thisacctmatcher) startbal negate ts
|
||||
items = reverse $ accountTransactionsReportItems m (Just thisacctmatcher) startbal negate ts
|
||||
|
||||
-- | Generate account register line items from a list of transactions,
|
||||
-- using the provided query and "this account" matchers, starting balance,
|
||||
-- | Generate transactions report items from a list of transactions,
|
||||
-- using the provided query and current account matchers, starting balance,
|
||||
-- sign-setting function and balance-summing function.
|
||||
|
||||
-- This is used for both accountRegisterReport and journalRegisterReport,
|
||||
-- which makes it a bit overcomplicated.
|
||||
accountRegisterReportItems :: Matcher -> Maybe Matcher -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [AccountRegisterReportItem]
|
||||
accountRegisterReportItems _ _ _ _ [] = []
|
||||
accountRegisterReportItems matcher thisacctmatcher bal signfn (t:ts) =
|
||||
accountTransactionsReportItems :: Matcher -> Maybe Matcher -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [TransactionsReportItem]
|
||||
accountTransactionsReportItems _ _ _ _ [] = []
|
||||
accountTransactionsReportItems matcher thisacctmatcher bal signfn (t:ts) =
|
||||
-- This is used for both accountTransactionsReport and journalTransactionsReport,
|
||||
-- which makes it a bit overcomplicated
|
||||
case i of Just i' -> i':is
|
||||
Nothing -> is
|
||||
where
|
||||
@ -311,7 +307,7 @@ accountRegisterReportItems matcher thisacctmatcher bal signfn (t:ts) =
|
||||
where
|
||||
a = signfn amt
|
||||
b = bal + a
|
||||
is = accountRegisterReportItems matcher thisacctmatcher bal' signfn ts
|
||||
is = accountTransactionsReportItems matcher thisacctmatcher bal' signfn ts
|
||||
|
||||
-- | Generate a short readable summary of some postings, like
|
||||
-- "from (negatives) to (positives)".
|
||||
@ -333,30 +329,33 @@ filterTransactionPostings m t@Transaction{tpostings=ps} = t{tpostings=filter (m
|
||||
|
||||
-------------------------------------------------------------------------------
|
||||
|
||||
-- | A balance report is a chart of accounts with balances, and their grand total.
|
||||
type BalanceReport = ([BalanceReportItem] -- line items, one per account
|
||||
,MixedAmount -- total balance of all accounts
|
||||
)
|
||||
|
||||
type BalanceReportItem = (AccountName -- full account name
|
||||
,AccountName -- account name elided for display: the leaf name,
|
||||
-- prefixed by any boring parents immediately above
|
||||
,Int -- how many steps to indent this account (0-based account depth excluding boring parents)
|
||||
,MixedAmount) -- account balance, includes subs unless --flat is present
|
||||
-- | An accounts report is a list of account names (full and short
|
||||
-- variants) with their balances, appropriate indentation for rendering as
|
||||
-- a hierarchy tree, and grand total.
|
||||
type AccountsReport = ([AccountsReportItem] -- line items, one per account
|
||||
,MixedAmount -- total balance of all accounts
|
||||
)
|
||||
type AccountsReportItem = (AccountName -- full account name
|
||||
,AccountName -- short account name for display (the leaf name, prefixed by any boring parents immediately above)
|
||||
,Int -- how many steps to indent this account (0-based account depth excluding boring parents)
|
||||
,MixedAmount) -- account balance, includes subs unless --flat is present
|
||||
|
||||
-- | Select accounts, and get their balances at the end of the selected
|
||||
-- period, as in the balance command.
|
||||
balanceReport :: [Opt] -> FilterSpec -> Journal -> BalanceReport
|
||||
balanceReport opts filterspec j = balanceReport' opts j (journalToLedger filterspec)
|
||||
-- period, and misc. display information, for an accounts report. Used by
|
||||
-- eg hledger's balance command.
|
||||
accountsReport :: [Opt] -> FilterSpec -> Journal -> AccountsReport
|
||||
accountsReport opts filterspec j = accountsReport' opts j (journalToLedger filterspec)
|
||||
|
||||
-- | Select accounts, and get their balances at the end of the selected
|
||||
-- period. Like "balanceReport" but uses the new matchers.
|
||||
balanceReport2 :: [Opt] -> Matcher -> Journal -> BalanceReport
|
||||
balanceReport2 opts matcher j = balanceReport' opts j (journalToLedger2 matcher)
|
||||
-- period, and misc. display information, for an accounts report. Like
|
||||
-- "accountsReport" but uses the new matchers. Used by eg hledger-web's
|
||||
-- accounts sidebar.
|
||||
accountsReport2 :: [Opt] -> Matcher -> Journal -> AccountsReport
|
||||
accountsReport2 opts matcher j = accountsReport' opts j (journalToLedger2 matcher)
|
||||
|
||||
-- Balance report helper.
|
||||
balanceReport' :: [Opt] -> Journal -> (Journal -> Ledger) -> BalanceReport
|
||||
balanceReport' opts j jtol = (items, total)
|
||||
-- Accounts report helper.
|
||||
accountsReport' :: [Opt] -> Journal -> (Journal -> Ledger) -> AccountsReport
|
||||
accountsReport' opts j jtol = (items, total)
|
||||
where
|
||||
items = map mkitem interestingaccts
|
||||
interestingaccts | NoElide `elem` opts = acctnames
|
||||
@ -367,7 +366,7 @@ balanceReport' opts j jtol = (items, total)
|
||||
l = jtol $ journalSelectingDateFromOpts opts $ journalSelectingAmountFromOpts opts j
|
||||
|
||||
-- | Get data for one balance report line item.
|
||||
mkitem :: AccountName -> BalanceReportItem
|
||||
mkitem :: AccountName -> AccountsReportItem
|
||||
mkitem a = (a, adisplay, indent, abal)
|
||||
where
|
||||
adisplay | Flat `elem` opts = a
|
||||
@ -384,8 +383,8 @@ balanceReport' opts j jtol = (items, total)
|
||||
exclusiveBalance :: Account -> MixedAmount
|
||||
exclusiveBalance = sumPostings . apostings
|
||||
|
||||
-- | Is the named account considered interesting for this ledger's balance report ?
|
||||
-- We follow the style of ledger's balance command.
|
||||
-- | Is the named account considered interesting for this ledger's accounts report,
|
||||
-- following the eliding style of ledger's balance command ?
|
||||
isInteresting :: [Opt] -> Ledger -> AccountName -> Bool
|
||||
isInteresting opts l a | Flat `elem` opts = isInterestingFlat opts l a
|
||||
| otherwise = isInterestingIndented opts l a
|
||||
|
Loading…
Reference in New Issue
Block a user