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