separate account types in balancesheet, show totals with consistent layout

This commit is contained in:
Simon Michael 2012-04-16 16:55:30 +00:00
parent 1e2c2bb10c
commit 65a20c6870
2 changed files with 26 additions and 5 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE QuasiQuotes #-}
{-| {-|
The @balancesheet@ command prints a fairly standard balance sheet. The @balancesheet@ command prints a fairly standard balance sheet.
@ -10,7 +11,9 @@ module Hledger.Cli.Balancesheet (
) where ) where
import Data.List import Data.List
import qualified Data.Text.Lazy.IO as LT
import Test.HUnit import Test.HUnit
import Text.Shakespeare.Text
import Hledger import Hledger
import Prelude hiding (putStr) import Prelude hiding (putStr)
@ -22,10 +25,26 @@ import Hledger.Cli.Balance
-- | Print a standard balancesheet. -- | Print a standard balancesheet.
balancesheet :: CliOpts -> Journal -> IO () balancesheet :: CliOpts -> Journal -> IO ()
balancesheet CliOpts{reportopts_=ropts} j = do balancesheet CliOpts{reportopts_=ropts} j = do
let lines = case formatFromOpts ropts of -- let lines = case formatFromOpts ropts of Left err, Right ...
Left err -> [err] d <- getCurrentDay
Right _ -> accountsReportAsText ropts $ accountsReport2 ropts (journalBalanceSheetAccountQuery j) j let m = queryFromOpts ropts d
putStr $ unlines lines assetreport@(_,assets) = accountsReport2 ropts (And [m, journalAssetAccountQuery j]) j
liabilityreport@(_,liabilities) = accountsReport2 ropts (And [m, journalLiabilityAccountQuery j]) j
equityreport@(_,equity) = accountsReport2 ropts (And [m, journalEquityAccountQuery j]) j
total = assets + liabilities + equity
LT.putStr $ [lt|Balance Sheet
Assets:
#{unlines $ accountsReportAsText ropts assetreport}
Liabilities:
#{unlines $ accountsReportAsText ropts liabilityreport}
Equity:
#{unlines $ accountsReportAsText ropts equityreport}
Total:
--------------------
#{padleft 20 $ showMixedAmountWithoutPrice total}
|]
tests_Hledger_Cli_Balancesheet = TestList tests_Hledger_Cli_Balancesheet = TestList
[ [

View File

@ -33,7 +33,9 @@ Revenues:
Expenses: Expenses:
#{unlines $ accountsReportAsText ropts expensereport} #{unlines $ accountsReportAsText ropts expensereport}
Total: #{show total} Total:
--------------------
#{padleft 20 $ showMixedAmountWithoutPrice total}
|] |]
tests_Hledger_Cli_Incomestatement :: Test tests_Hledger_Cli_Incomestatement :: Test