imp: balance: Implement multi-line display for multicommodity balance reports.
This allows more control over how multicommodity amounts are displayed. In addition to the default single-line display, and the recent commodity column display, we now have multi-line display. This is controlled by the --layout option, which has possible values "wide", "tall", and "bare". The --commodity-column option has been hidden, but is equivalent to --layout=bare. squash
This commit is contained in:
parent
3dce61ea09
commit
7e21f05a83
@ -913,12 +913,9 @@ showMixedAmountOneLineB opts@AmountDisplayOpts{displayMaxWidth=mmax,displayMinWi
|
|||||||
withElided = zipWith (\num amt -> (amt, elisionDisplay Nothing (wbWidth sep) num amt)) [n-1,n-2..0]
|
withElided = zipWith (\num amt -> (amt, elisionDisplay Nothing (wbWidth sep) num amt)) [n-1,n-2..0]
|
||||||
|
|
||||||
orderedAmounts :: AmountDisplayOpts -> MixedAmount -> [Amount]
|
orderedAmounts :: AmountDisplayOpts -> MixedAmount -> [Amount]
|
||||||
orderedAmounts AmountDisplayOpts{displayOrder=ord} ma
|
orderedAmounts dopts = maybe id (mapM pad) (displayOrder dopts) . amounts
|
||||||
| Just cs <- ord = fmap pad cs
|
|
||||||
| otherwise = as
|
|
||||||
where
|
where
|
||||||
as = amounts ma
|
pad c = fromMaybe (amountWithCommodity c nullamt) . find ((c==) . acommodity)
|
||||||
pad c = fromMaybe (amountWithCommodity c nullamt) . find ((==) c . acommodity) $ as
|
|
||||||
|
|
||||||
|
|
||||||
data AmountDisplay = AmountDisplay
|
data AmountDisplay = AmountDisplay
|
||||||
|
|||||||
@ -38,7 +38,7 @@ import qualified Data.Text.Lazy as TL
|
|||||||
import qualified Data.Text.Lazy.Builder as TB
|
import qualified Data.Text.Lazy.Builder as TB
|
||||||
--import System.Console.CmdArgs.Explicit as C
|
--import System.Console.CmdArgs.Explicit as C
|
||||||
--import Lucid as L
|
--import Lucid as L
|
||||||
import Text.Tabular.AsciiWide as Tab
|
import qualified Text.Tabular.AsciiWide as Tab
|
||||||
|
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Utils
|
import Hledger.Utils
|
||||||
@ -230,18 +230,18 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $
|
|||||||
<> ":"
|
<> ":"
|
||||||
|
|
||||||
-- | Build a 'Table' from a multi-column balance report.
|
-- | Build a 'Table' from a multi-column balance report.
|
||||||
budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text WideBuilder
|
budgetReportAsTable :: ReportOpts -> BudgetReport -> Tab.Table Text Text WideBuilder
|
||||||
budgetReportAsTable
|
budgetReportAsTable
|
||||||
ReportOpts{..}
|
ReportOpts{..}
|
||||||
(PeriodicReport spans items tr) =
|
(PeriodicReport spans items tr) =
|
||||||
maybetransposetable $
|
maybetransposetable $
|
||||||
addtotalrow $
|
addtotalrow $
|
||||||
Table
|
Tab.Table
|
||||||
(Tab.Group NoLine $ map Header accts)
|
(Tab.Group Tab.NoLine $ map Tab.Header accts)
|
||||||
(Tab.Group NoLine $ map Header colheadings)
|
(Tab.Group Tab.NoLine $ map Tab.Header colheadings)
|
||||||
rows
|
rows
|
||||||
where
|
where
|
||||||
colheadings = ["Commodity" | commodity_column_]
|
colheadings = ["Commodity" | commodity_layout_ == CommodityColumn]
|
||||||
++ map (reportPeriodName balanceaccum_ spans) spans
|
++ map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | row_total_]
|
++ [" Total" | row_total_]
|
||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
@ -255,16 +255,16 @@ budgetReportAsTable
|
|||||||
|
|
||||||
addtotalrow
|
addtotalrow
|
||||||
| no_total_ = id
|
| no_total_ = id
|
||||||
| otherwise = let rh = Tab.Group NoLine . replicate (length totalrows) $ Header ""
|
| otherwise = let rh = Tab.Group Tab.NoLine . replicate (length totalrows) $ Tab.Header ""
|
||||||
ch = Header [] -- ignored
|
ch = Tab.Header [] -- ignored
|
||||||
in (flip (concatTables SingleLine) $ Table rh ch totalrows)
|
in (flip (Tab.concatTables Tab.SingleLine) $ Tab.Table rh ch totalrows)
|
||||||
|
|
||||||
maybetranspose
|
maybetranspose
|
||||||
| transpose_ = transpose
|
| transpose_ = transpose
|
||||||
| otherwise = id
|
| otherwise = id
|
||||||
|
|
||||||
maybetransposetable
|
maybetransposetable
|
||||||
| transpose_ = \(Table rh ch vals) -> Table ch rh (transpose vals)
|
| transpose_ = \(Tab.Table rh ch vals) -> Tab.Table ch rh (transpose vals)
|
||||||
| otherwise = id
|
| otherwise = id
|
||||||
|
|
||||||
(accts, rows, totalrows) = (accts, prependcs itemscs (padcells texts), prependcs trcs (padtr trtexts))
|
(accts, rows, totalrows) = (accts, prependcs itemscs (padcells texts), prependcs trcs (padtr trtexts))
|
||||||
@ -283,19 +283,19 @@ budgetReportAsTable
|
|||||||
padcells = maybetranspose . fmap (fmap (uncurry paddisplaycell) . zip widths) . maybetranspose
|
padcells = maybetranspose . fmap (fmap (uncurry paddisplaycell) . zip widths) . maybetranspose
|
||||||
padtr = maybetranspose . fmap (fmap (uncurry paddisplaycell) . zip trwidths) . maybetranspose
|
padtr = maybetranspose . fmap (fmap (uncurry paddisplaycell) . zip trwidths) . maybetranspose
|
||||||
|
|
||||||
-- commodities are shown with the amounts without `commodity-column`
|
-- commodities are shown with the amounts without `commodity-layout_ == CommodityColumn`
|
||||||
prependcs cs
|
prependcs cs
|
||||||
| commodity_column_ = zipWith (:) cs
|
| commodity_layout_ /= CommodityColumn = id
|
||||||
| otherwise = id
|
| otherwise = zipWith (:) cs
|
||||||
|
|
||||||
rowToBudgetCells (PeriodicReportRow _ as rowtot rowavg) = as
|
rowToBudgetCells (PeriodicReportRow _ as rowtot rowavg) = as
|
||||||
++ [rowtot | row_total_ && not (null as)]
|
++ [rowtot | row_total_ && not (null as)]
|
||||||
++ [rowavg | average_ && not (null as)]
|
++ [rowavg | average_ && not (null as)]
|
||||||
|
|
||||||
-- functions for displaying budget cells depending on `commodity-column` flag
|
-- functions for displaying budget cells depending on `commodity-layout_` option
|
||||||
rowfuncs :: [CommoditySymbol] -> (BudgetShowMixed, BudgetPercBudget)
|
rowfuncs :: [CommoditySymbol] -> (BudgetShowMixed, BudgetPercBudget)
|
||||||
rowfuncs cs
|
rowfuncs cs
|
||||||
| not commodity_column_ =
|
| commodity_layout_ == CommodityOneLine =
|
||||||
( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=Just 32}
|
( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=Just 32}
|
||||||
, \a -> pure . percentage a)
|
, \a -> pure . percentage a)
|
||||||
| otherwise =
|
| otherwise =
|
||||||
@ -408,7 +408,7 @@ budgetReportAsCsv
|
|||||||
|
|
||||||
-- heading row
|
-- heading row
|
||||||
("Account" :
|
("Account" :
|
||||||
["Commodity" | commodity_column_ ]
|
["Commodity" | commodity_layout_ == CommodityColumn ]
|
||||||
++ concatMap (\span -> [showDateSpan span, "budget"]) colspans
|
++ concatMap (\span -> [showDateSpan span, "budget"]) colspans
|
||||||
++ concat [["Total" ,"budget"] | row_total_]
|
++ concat [["Total" ,"budget"] | row_total_]
|
||||||
++ concat [["Average","budget"] | average_]
|
++ concat [["Average","budget"] | average_]
|
||||||
@ -428,7 +428,7 @@ budgetReportAsCsv
|
|||||||
-> PeriodicReportRow a BudgetCell
|
-> PeriodicReportRow a BudgetCell
|
||||||
-> [[Text]]
|
-> [[Text]]
|
||||||
rowAsTexts render row@(PeriodicReportRow _ as (rowtot,budgettot) (rowavg, budgetavg))
|
rowAsTexts render row@(PeriodicReportRow _ as (rowtot,budgettot) (rowavg, budgetavg))
|
||||||
| not commodity_column_ = [render row : fmap showNorm all]
|
| commodity_layout_ /= CommodityColumn = [render row : fmap showNorm all]
|
||||||
| otherwise =
|
| otherwise =
|
||||||
joinNames . zipWith (:) cs -- add symbols and names
|
joinNames . zipWith (:) cs -- add symbols and names
|
||||||
. transpose -- each row becomes a list of Text quantities
|
. transpose -- each row becomes a list of Text quantities
|
||||||
|
|||||||
@ -568,16 +568,17 @@ balanceReportTableAsText ReportOpts{..} =
|
|||||||
Tab.renderTableByRowsB def{Tab.tableBorders=False, Tab.prettyTable=pretty_} renderCh renderRow
|
Tab.renderTableByRowsB def{Tab.tableBorders=False, Tab.prettyTable=pretty_} renderCh renderRow
|
||||||
where
|
where
|
||||||
renderCh
|
renderCh
|
||||||
| not commodity_column_ || transpose_ = fmap (Tab.textCell Tab.TopRight)
|
| commodity_layout_ /= CommodityColumn || transpose_ = fmap (Tab.textCell Tab.TopRight)
|
||||||
| otherwise = zipWith ($) (Tab.textCell Tab.TopLeft : repeat (Tab.textCell Tab.TopRight))
|
| otherwise = zipWith ($) (Tab.textCell Tab.TopLeft : repeat (Tab.textCell Tab.TopRight))
|
||||||
|
|
||||||
renderRow (rh, row)
|
renderRow (rh, row)
|
||||||
| not commodity_column_ || transpose_ =
|
| commodity_layout_ /= CommodityColumn || transpose_ =
|
||||||
(Tab.textCell Tab.TopLeft rh, fmap (Tab.Cell Tab.TopRight . pure) row)
|
(Tab.textCell Tab.TopLeft rh, fmap (Tab.Cell Tab.TopRight . pure) row)
|
||||||
| otherwise =
|
| otherwise =
|
||||||
(Tab.textCell Tab.TopLeft rh, zipWith ($) (Tab.Cell Tab.TopLeft : repeat (Tab.Cell Tab.TopRight)) (fmap pure row))
|
(Tab.textCell Tab.TopLeft rh, zipWith ($) (Tab.Cell Tab.TopLeft : repeat (Tab.Cell Tab.TopRight)) (fmap pure row))
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|
||||||
tests_MultiBalanceReport = testGroup "MultiBalanceReport" [
|
tests_MultiBalanceReport = testGroup "MultiBalanceReport" [
|
||||||
|
|||||||
@ -26,6 +26,7 @@ module Hledger.Reports.ReportOptions (
|
|||||||
BalanceAccumulation(..),
|
BalanceAccumulation(..),
|
||||||
AccountListMode(..),
|
AccountListMode(..),
|
||||||
ValuationType(..),
|
ValuationType(..),
|
||||||
|
CommodityLayout(..),
|
||||||
defreportopts,
|
defreportopts,
|
||||||
rawOptsToReportOpts,
|
rawOptsToReportOpts,
|
||||||
defreportspec,
|
defreportspec,
|
||||||
@ -62,7 +63,8 @@ module Hledger.Reports.ReportOptions (
|
|||||||
where
|
where
|
||||||
|
|
||||||
import Control.Applicative (Const(..), (<|>), liftA2)
|
import Control.Applicative (Const(..), (<|>), liftA2)
|
||||||
import Control.Monad ((<=<), join)
|
import Control.Monad ((<=<), guard, join)
|
||||||
|
import Data.Char (toLower)
|
||||||
import Data.Either (fromRight)
|
import Data.Either (fromRight)
|
||||||
import Data.Either.Extra (eitherToMaybe)
|
import Data.Either.Extra (eitherToMaybe)
|
||||||
import Data.Functor.Identity (Identity(..))
|
import Data.Functor.Identity (Identity(..))
|
||||||
@ -71,7 +73,7 @@ import Data.Maybe (fromMaybe, mapMaybe)
|
|||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Time.Calendar (Day, addDays)
|
import Data.Time.Calendar (Day, addDays)
|
||||||
import Data.Default (Default(..))
|
import Data.Default (Default(..))
|
||||||
import Safe (headMay, lastDef, lastMay, maximumMay)
|
import Safe (headDef, headMay, lastDef, lastMay, maximumMay)
|
||||||
|
|
||||||
import Text.Megaparsec.Custom
|
import Text.Megaparsec.Custom
|
||||||
|
|
||||||
@ -107,47 +109,49 @@ data AccountListMode = ALFlat | ALTree deriving (Eq, Show)
|
|||||||
|
|
||||||
instance Default AccountListMode where def = ALFlat
|
instance Default AccountListMode where def = ALFlat
|
||||||
|
|
||||||
|
data CommodityLayout = CommodityOneLine | CommodityMultiLine | CommodityColumn deriving (Eq, Show)
|
||||||
|
|
||||||
-- | Standard options for customising report filtering and output.
|
-- | Standard options for customising report filtering and output.
|
||||||
-- Most of these correspond to standard hledger command-line options
|
-- Most of these correspond to standard hledger command-line options
|
||||||
-- or query arguments, but not all. Some are used only by certain
|
-- or query arguments, but not all. Some are used only by certain
|
||||||
-- commands, as noted below.
|
-- commands, as noted below.
|
||||||
data ReportOpts = ReportOpts {
|
data ReportOpts = ReportOpts {
|
||||||
-- for most reports:
|
-- for most reports:
|
||||||
period_ :: Period
|
period_ :: Period
|
||||||
,interval_ :: Interval
|
,interval_ :: Interval
|
||||||
,statuses_ :: [Status] -- ^ Zero, one, or two statuses to be matched
|
,statuses_ :: [Status] -- ^ Zero, one, or two statuses to be matched
|
||||||
,cost_ :: Costing -- ^ Should we convert amounts to cost, when present?
|
,cost_ :: Costing -- ^ Should we convert amounts to cost, when present?
|
||||||
,value_ :: Maybe ValuationType -- ^ What value should amounts be converted to ?
|
,value_ :: Maybe ValuationType -- ^ What value should amounts be converted to ?
|
||||||
,infer_prices_ :: Bool -- ^ Infer market prices from transactions ?
|
,infer_prices_ :: Bool -- ^ Infer market prices from transactions ?
|
||||||
,depth_ :: Maybe Int
|
,depth_ :: Maybe Int
|
||||||
,date2_ :: Bool
|
,date2_ :: Bool
|
||||||
,empty_ :: Bool
|
,empty_ :: Bool
|
||||||
,no_elide_ :: Bool
|
,no_elide_ :: Bool
|
||||||
,real_ :: Bool
|
,real_ :: Bool
|
||||||
,format_ :: StringFormat
|
,format_ :: StringFormat
|
||||||
,pretty_ :: Bool
|
,pretty_ :: Bool
|
||||||
,querystring_ :: [T.Text]
|
,querystring_ :: [T.Text]
|
||||||
--
|
--
|
||||||
,average_ :: Bool
|
,average_ :: Bool
|
||||||
-- for posting reports (register)
|
-- for posting reports (register)
|
||||||
,related_ :: Bool
|
,related_ :: Bool
|
||||||
-- for account transactions reports (aregister)
|
-- for account transactions reports (aregister)
|
||||||
,txn_dates_ :: Bool
|
,txn_dates_ :: Bool
|
||||||
-- for balance reports (bal, bs, cf, is)
|
-- for balance reports (bal, bs, cf, is)
|
||||||
,balancecalc_ :: BalanceCalculation -- ^ What to calculate in balance report cells
|
,balancecalc_ :: BalanceCalculation -- ^ What to calculate in balance report cells
|
||||||
,balanceaccum_ :: BalanceAccumulation -- ^ How to accumulate balance report values over time
|
,balanceaccum_ :: BalanceAccumulation -- ^ How to accumulate balance report values over time
|
||||||
,budgetpat_ :: Maybe T.Text -- ^ A case-insensitive description substring
|
,budgetpat_ :: Maybe T.Text -- ^ A case-insensitive description substring
|
||||||
-- to select periodic transactions for budget reports.
|
-- to select periodic transactions for budget reports.
|
||||||
-- (Not a regexp, nor a full hledger query, for now.)
|
-- (Not a regexp, nor a full hledger query, for now.)
|
||||||
,accountlistmode_ :: AccountListMode
|
,accountlistmode_ :: AccountListMode
|
||||||
,drop_ :: Int
|
,drop_ :: Int
|
||||||
,row_total_ :: Bool
|
,row_total_ :: Bool
|
||||||
,no_total_ :: Bool
|
,no_total_ :: Bool
|
||||||
,show_costs_ :: Bool -- ^ Whether to show costs for reports which normally don't show them
|
,show_costs_ :: Bool -- ^ Whether to show costs for reports which normally don't show them
|
||||||
,sort_amount_ :: Bool
|
,sort_amount_ :: Bool
|
||||||
,percent_ :: Bool
|
,percent_ :: Bool
|
||||||
,invert_ :: Bool -- ^ if true, flip all amount signs in reports
|
,invert_ :: Bool -- ^ if true, flip all amount signs in reports
|
||||||
,normalbalance_ :: Maybe NormalSign
|
,normalbalance_ :: Maybe NormalSign
|
||||||
-- ^ This can be set when running balance reports on a set of accounts
|
-- ^ This can be set when running balance reports on a set of accounts
|
||||||
-- with the same normal balance type (eg all assets, or all incomes).
|
-- with the same normal balance type (eg all assets, or all incomes).
|
||||||
-- - It helps --sort-amount know how to sort negative numbers
|
-- - It helps --sort-amount know how to sort negative numbers
|
||||||
@ -155,51 +159,51 @@ data ReportOpts = ReportOpts {
|
|||||||
-- - It helps compound balance report commands (is, bs etc.) do
|
-- - It helps compound balance report commands (is, bs etc.) do
|
||||||
-- sign normalisation, converting normally negative subreports to
|
-- sign normalisation, converting normally negative subreports to
|
||||||
-- normally positive for a more conventional display.
|
-- normally positive for a more conventional display.
|
||||||
,color_ :: Bool
|
,color_ :: Bool
|
||||||
-- ^ Whether to use ANSI color codes in text output.
|
-- ^ Whether to use ANSI color codes in text output.
|
||||||
-- Influenced by the --color/colour flag (cf CliOptions),
|
-- Influenced by the --color/colour flag (cf CliOptions),
|
||||||
-- whether stdout is an interactive terminal, and the value of
|
-- whether stdout is an interactive terminal, and the value of
|
||||||
-- TERM and existence of NO_COLOR environment variables.
|
-- TERM and existence of NO_COLOR environment variables.
|
||||||
,transpose_ :: Bool
|
,transpose_ :: Bool
|
||||||
,commodity_column_:: Bool
|
,commodity_layout_ :: CommodityLayout
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
||||||
instance Default ReportOpts where def = defreportopts
|
instance Default ReportOpts where def = defreportopts
|
||||||
|
|
||||||
defreportopts :: ReportOpts
|
defreportopts :: ReportOpts
|
||||||
defreportopts = ReportOpts
|
defreportopts = ReportOpts
|
||||||
{ period_ = PeriodAll
|
{ period_ = PeriodAll
|
||||||
, interval_ = NoInterval
|
, interval_ = NoInterval
|
||||||
, statuses_ = []
|
, statuses_ = []
|
||||||
, cost_ = NoCost
|
, cost_ = NoCost
|
||||||
, value_ = Nothing
|
, value_ = Nothing
|
||||||
, infer_prices_ = False
|
, infer_prices_ = False
|
||||||
, depth_ = Nothing
|
, depth_ = Nothing
|
||||||
, date2_ = False
|
, date2_ = False
|
||||||
, empty_ = False
|
, empty_ = False
|
||||||
, no_elide_ = False
|
, no_elide_ = False
|
||||||
, real_ = False
|
, real_ = False
|
||||||
, format_ = def
|
, format_ = def
|
||||||
, pretty_ = False
|
, pretty_ = False
|
||||||
, querystring_ = []
|
, querystring_ = []
|
||||||
, average_ = False
|
, average_ = False
|
||||||
, related_ = False
|
, related_ = False
|
||||||
, txn_dates_ = False
|
, txn_dates_ = False
|
||||||
, balancecalc_ = def
|
, balancecalc_ = def
|
||||||
, balanceaccum_ = def
|
, balanceaccum_ = def
|
||||||
, budgetpat_ = Nothing
|
, budgetpat_ = Nothing
|
||||||
, accountlistmode_ = ALFlat
|
, accountlistmode_ = ALFlat
|
||||||
, drop_ = 0
|
, drop_ = 0
|
||||||
, row_total_ = False
|
, row_total_ = False
|
||||||
, no_total_ = False
|
, no_total_ = False
|
||||||
, show_costs_ = False
|
, show_costs_ = False
|
||||||
, sort_amount_ = False
|
, sort_amount_ = False
|
||||||
, percent_ = False
|
, percent_ = False
|
||||||
, invert_ = False
|
, invert_ = False
|
||||||
, normalbalance_ = Nothing
|
, normalbalance_ = Nothing
|
||||||
, color_ = False
|
, color_ = False
|
||||||
, transpose_ = False
|
, transpose_ = False
|
||||||
, commodity_column_ = False
|
, commodity_layout_ = CommodityOneLine
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Generate a ReportOpts from raw command-line input, given a day.
|
-- | Generate a ReportOpts from raw command-line input, given a day.
|
||||||
@ -222,37 +226,37 @@ rawOptsToReportOpts d rawopts =
|
|||||||
Just (Left err) -> usageError $ "could not parse format option: " ++ err
|
Just (Left err) -> usageError $ "could not parse format option: " ++ err
|
||||||
|
|
||||||
in defreportopts
|
in defreportopts
|
||||||
{period_ = periodFromRawOpts d rawopts
|
{period_ = periodFromRawOpts d rawopts
|
||||||
,interval_ = intervalFromRawOpts rawopts
|
,interval_ = intervalFromRawOpts rawopts
|
||||||
,statuses_ = statusesFromRawOpts rawopts
|
,statuses_ = statusesFromRawOpts rawopts
|
||||||
,cost_ = costing
|
,cost_ = costing
|
||||||
,value_ = valuation
|
,value_ = valuation
|
||||||
,infer_prices_ = boolopt "infer-market-prices" rawopts
|
,infer_prices_ = boolopt "infer-market-prices" rawopts
|
||||||
,depth_ = maybeposintopt "depth" rawopts
|
,depth_ = maybeposintopt "depth" rawopts
|
||||||
,date2_ = boolopt "date2" rawopts
|
,date2_ = boolopt "date2" rawopts
|
||||||
,empty_ = boolopt "empty" rawopts
|
,empty_ = boolopt "empty" rawopts
|
||||||
,no_elide_ = boolopt "no-elide" rawopts
|
,no_elide_ = boolopt "no-elide" rawopts
|
||||||
,real_ = boolopt "real" rawopts
|
,real_ = boolopt "real" rawopts
|
||||||
,format_ = format
|
,format_ = format
|
||||||
,querystring_ = querystring
|
,querystring_ = querystring
|
||||||
,average_ = boolopt "average" rawopts
|
,average_ = boolopt "average" rawopts
|
||||||
,related_ = boolopt "related" rawopts
|
,related_ = boolopt "related" rawopts
|
||||||
,txn_dates_ = boolopt "txn-dates" rawopts
|
,txn_dates_ = boolopt "txn-dates" rawopts
|
||||||
,balancecalc_ = balancecalcopt rawopts
|
,balancecalc_ = balancecalcopt rawopts
|
||||||
,balanceaccum_ = balanceaccumopt rawopts
|
,balanceaccum_ = balanceaccumopt rawopts
|
||||||
,budgetpat_ = maybebudgetpatternopt rawopts
|
,budgetpat_ = maybebudgetpatternopt rawopts
|
||||||
,accountlistmode_ = accountlistmodeopt rawopts
|
,accountlistmode_ = accountlistmodeopt rawopts
|
||||||
,drop_ = posintopt "drop" rawopts
|
,drop_ = posintopt "drop" rawopts
|
||||||
,row_total_ = boolopt "row-total" rawopts
|
,row_total_ = boolopt "row-total" rawopts
|
||||||
,no_total_ = boolopt "no-total" rawopts
|
,no_total_ = boolopt "no-total" rawopts
|
||||||
,show_costs_ = boolopt "show-costs" rawopts
|
,show_costs_ = boolopt "show-costs" rawopts
|
||||||
,sort_amount_ = boolopt "sort-amount" rawopts
|
,sort_amount_ = boolopt "sort-amount" rawopts
|
||||||
,percent_ = boolopt "percent" rawopts
|
,percent_ = boolopt "percent" rawopts
|
||||||
,invert_ = boolopt "invert" rawopts
|
,invert_ = boolopt "invert" rawopts
|
||||||
,pretty_ = pretty
|
,pretty_ = pretty
|
||||||
,color_ = useColorOnStdout -- a lower-level helper
|
,color_ = useColorOnStdout -- a lower-level helper
|
||||||
,transpose_ = boolopt "transpose" rawopts
|
,transpose_ = boolopt "transpose" rawopts
|
||||||
,commodity_column_= boolopt "commodity-column" rawopts
|
,commodity_layout_ = commoditylayoutopt rawopts
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | The result of successfully parsing a ReportOpts on a particular
|
-- | The result of successfully parsing a ReportOpts on a particular
|
||||||
@ -327,6 +331,18 @@ balanceAccumulationOverride rawopts = choiceopt parse rawopts <|> reportbal
|
|||||||
CalcValueChange -> Just PerPeriod
|
CalcValueChange -> Just PerPeriod
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
|
commoditylayoutopt :: RawOpts -> CommodityLayout
|
||||||
|
commoditylayoutopt rawopts = fromMaybe CommodityOneLine $ layout <|> column
|
||||||
|
where
|
||||||
|
layout = parse <$> maybestringopt "commodity-layout" rawopts
|
||||||
|
column = CommodityColumn <$ guard (boolopt "commodity-column" rawopts)
|
||||||
|
|
||||||
|
parse opt = case toLower $ headDef 'x' opt of
|
||||||
|
'o' -> CommodityOneLine -- "oneline" and abbreviations
|
||||||
|
'm' -> CommodityMultiLine -- "multiline" and abbreviations
|
||||||
|
'c' -> CommodityColumn -- "column" and abbreviations
|
||||||
|
_ -> usageError "--commodity-layout's argument should be \"oneline\", \"multiline\", or \"column\""
|
||||||
|
|
||||||
-- Get the period specified by any -b/--begin, -e/--end and/or -p/--period
|
-- Get the period specified by any -b/--begin, -e/--end and/or -p/--period
|
||||||
-- options appearing in the command line.
|
-- options appearing in the command line.
|
||||||
-- Its bounds are the rightmost begin date specified by a -b or -p, and
|
-- Its bounds are the rightmost begin date specified by a -b or -p, and
|
||||||
|
|||||||
@ -270,7 +270,10 @@ import Data.Time (fromGregorian)
|
|||||||
import System.Console.CmdArgs.Explicit as C
|
import System.Console.CmdArgs.Explicit as C
|
||||||
import Lucid as L
|
import Lucid as L
|
||||||
import Safe (headMay, maximumMay)
|
import Safe (headMay, maximumMay)
|
||||||
import Text.Tabular.AsciiWide as Tab
|
import Text.Tabular.AsciiWide
|
||||||
|
(Align(..), Cell(..), Table(..), TableOpts(..), cellWidth, concatTables,
|
||||||
|
renderColumns, renderRowB, textCell)
|
||||||
|
import qualified Text.Tabular.AsciiWide as Tab
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
@ -315,14 +318,22 @@ balancemode = hledgerCommandMode
|
|||||||
,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total"
|
,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total"
|
||||||
,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign"
|
,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign"
|
||||||
,flagNone ["transpose"] (setboolopt "transpose") "transpose rows and columns"
|
,flagNone ["transpose"] (setboolopt "transpose") "transpose rows and columns"
|
||||||
,flagNone ["commodity-column"] (setboolopt "commodity-column")
|
,flagReq ["commodity-layout"] (\s opts -> Right $ setopt "commodity-layout" s opts) "ARG"
|
||||||
"show commodity symbols in a separate column, amounts as bare numbers, one row per commodity"
|
(unlines
|
||||||
|
["show multicommodity amounts in the given ARG. ARG can be:"
|
||||||
|
,"'oneline': show all commodities on a single line"
|
||||||
|
,"'multiline': show each commodity on a new line"
|
||||||
|
,"'column': show commodity symbols in a separate column and amounts as bare numbers"
|
||||||
|
])
|
||||||
,outputFormatFlag ["txt","html","csv","json"]
|
,outputFormatFlag ["txt","html","csv","json"]
|
||||||
,outputFileFlag
|
,outputFileFlag
|
||||||
]
|
]
|
||||||
)
|
)
|
||||||
[generalflagsgroup1]
|
[generalflagsgroup1]
|
||||||
hiddenflags
|
(hiddenflags ++
|
||||||
|
[ flagNone ["commodity-column"] (setboolopt "commodity-column")
|
||||||
|
"show commodity symbols in a separate column, amounts as bare numbers, one row per commodity"
|
||||||
|
])
|
||||||
([], Just $ argsFlag "[QUERY]")
|
([], Just $ argsFlag "[QUERY]")
|
||||||
|
|
||||||
-- | The balance command, prints a balance report.
|
-- | The balance command, prints a balance report.
|
||||||
@ -396,31 +407,29 @@ balance opts@CliOpts{reportspec_=rspec} j = case balancecalc_ of
|
|||||||
-- | Render a single-column balance report as CSV.
|
-- | Render a single-column balance report as CSV.
|
||||||
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
|
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
|
||||||
balanceReportAsCsv opts (items, total) =
|
balanceReportAsCsv opts (items, total) =
|
||||||
("account" : ((if commodity_column_ opts then (:) "commodity" else id) $ ["balance"]))
|
("account" : ((if commodity_layout_ opts == CommodityColumn then (:) "commodity" else id) $ ["balance"]))
|
||||||
: (concatMap (\(a, _, _, b) -> rows a b) items)
|
: (concatMap (\(a, _, _, b) -> rows a b) items)
|
||||||
++ if no_total_ opts then [] else rows "total" total
|
++ if no_total_ opts then [] else rows "total" total
|
||||||
where
|
where
|
||||||
rows :: AccountName -> MixedAmount -> [[T.Text]]
|
rows :: AccountName -> MixedAmount -> [[T.Text]]
|
||||||
rows name ma
|
rows name ma = case commodity_layout_ opts of
|
||||||
| commodity_column_ opts =
|
CommodityColumn ->
|
||||||
fmap (\(k, a) -> [showName name, k, renderAmount . mixedAmount . amountStripPrices $ a])
|
fmap (\(k, a) -> [showName name, k, renderAmount . mixedAmount . amountStripPrices $ a])
|
||||||
. M.toList . foldl' sumAmounts mempty . amounts $ ma
|
. M.toList . foldl' sumAmounts mempty . amounts $ ma
|
||||||
| otherwise = [[showName name, renderAmount ma]]
|
_ -> [[showName name, renderAmount ma]]
|
||||||
|
|
||||||
showName = accountNameDrop (drop_ opts)
|
showName = accountNameDrop (drop_ opts)
|
||||||
renderAmount amt = wbToText $ showMixedAmountB bopts amt
|
renderAmount amt = wbToText $ showMixedAmountB bopts amt
|
||||||
where bopts = (balanceOpts False opts){displayOrder = order}
|
where bopts = (balanceOpts False opts){displayOrder = order}
|
||||||
order = if commodity_column_ opts then Just (S.toList $ maCommodities amt) else Nothing
|
order = if commodity_layout_ opts == CommodityColumn then Just (S.toList $ maCommodities amt) else Nothing
|
||||||
sumAmounts mp am = M.insertWith (+) (acommodity am) am mp
|
sumAmounts mp am = M.insertWith (+) (acommodity am) am mp
|
||||||
|
|
||||||
-- | Render a single-column balance report as plain text.
|
-- | Render a single-column balance report as plain text.
|
||||||
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
|
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
|
||||||
balanceReportAsText opts ((items, total))
|
balanceReportAsText opts ((items, total)) = case commodity_layout_ opts of
|
||||||
| not (commodity_column_ opts) =
|
CommodityColumn | iscustom -> error' "Custom format not supported with commodity columns" -- PARTIAL:
|
||||||
unlinesB lines
|
CommodityColumn -> balanceReportAsText' opts ((items, total))
|
||||||
<> unlinesB (if no_total_ opts then [] else [overline, totalLines])
|
_ -> unlinesB lines <> unlinesB (if no_total_ opts then [] else [overline, totalLines])
|
||||||
| iscustom = error' "Custom format not supported with --commodity-column" -- PARTIAL:
|
|
||||||
| otherwise = balanceReportAsText' opts ((items, total))
|
|
||||||
where
|
where
|
||||||
(lines, sizes) = unzip $ map (balanceReportItemAsText opts) items
|
(lines, sizes) = unzip $ map (balanceReportItemAsText opts) items
|
||||||
-- abuse renderBalanceReportItem to render the total with similar format
|
-- abuse renderBalanceReportItem to render the total with similar format
|
||||||
@ -438,7 +447,7 @@ balanceReportAsText opts ((items, total))
|
|||||||
-- | Render a single-column balance report as plain text in commodity-column mode
|
-- | Render a single-column balance report as plain text in commodity-column mode
|
||||||
balanceReportAsText' :: ReportOpts -> BalanceReport -> TB.Builder
|
balanceReportAsText' :: ReportOpts -> BalanceReport -> TB.Builder
|
||||||
balanceReportAsText' opts ((items, total)) =
|
balanceReportAsText' opts ((items, total)) =
|
||||||
unlinesB . fmap (renderColumns def{tableBorders=False} sizes . Tab.Group NoLine . fmap Header) $
|
unlinesB . fmap (renderColumns def{tableBorders=False} sizes . Tab.Group Tab.NoLine . fmap Tab.Header) $
|
||||||
lines ++ concat [[[overline], totalline] | not (no_total_ opts)]
|
lines ++ concat [[[overline], totalline] | not (no_total_ opts)]
|
||||||
where
|
where
|
||||||
render (_, acctname, depth, amt) =
|
render (_, acctname, depth, amt) =
|
||||||
@ -483,7 +492,7 @@ renderBalanceReportItem opts (acctname, depth, total) =
|
|||||||
BottomAligned comps -> renderRow' $ render False False comps
|
BottomAligned comps -> renderRow' $ render False False comps
|
||||||
where
|
where
|
||||||
renderRow' is = ( renderRowB def{tableBorders=False, borderSpaces=False}
|
renderRow' is = ( renderRowB def{tableBorders=False, borderSpaces=False}
|
||||||
. Tab.Group NoLine $ map Header is
|
. Tab.Group Tab.NoLine $ map Tab.Header is
|
||||||
, map cellWidth is )
|
, map cellWidth is )
|
||||||
|
|
||||||
render topaligned oneline = map (renderComponent topaligned oneline opts (acctname, depth, total))
|
render topaligned oneline = map (renderComponent topaligned oneline opts (acctname, depth, total))
|
||||||
@ -515,7 +524,7 @@ multiBalanceReportAsCsv opts@ReportOpts{..} =
|
|||||||
|
|
||||||
multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV)
|
multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV)
|
||||||
multiBalanceReportAsCsv' opts@ReportOpts{..} (PeriodicReport colspans items tr) =
|
multiBalanceReportAsCsv' opts@ReportOpts{..} (PeriodicReport colspans items tr) =
|
||||||
( ("account" : ["commodity" | commodity_column_] ++ map showDateSpan colspans
|
( ("account" : ["commodity" | commodity_layout_ == CommodityColumn] ++ map showDateSpan colspans
|
||||||
++ ["total" | row_total_]
|
++ ["total" | row_total_]
|
||||||
++ ["average" | average_]
|
++ ["average" | average_]
|
||||||
) : concatMap (fullRowAsTexts (accountNameDrop drop_ . prrFullName)) items
|
) : concatMap (fullRowAsTexts (accountNameDrop drop_ . prrFullName)) items
|
||||||
@ -657,12 +666,12 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
|||||||
maybetranspose $
|
maybetranspose $
|
||||||
addtotalrow $
|
addtotalrow $
|
||||||
Table
|
Table
|
||||||
(Tab.Group NoLine $ map Header (concat accts))
|
(Tab.Group Tab.NoLine $ map Tab.Header (concat accts))
|
||||||
(Tab.Group NoLine $ map Header colheadings)
|
(Tab.Group Tab.NoLine $ map Tab.Header colheadings)
|
||||||
(concat rows)
|
(concat rows)
|
||||||
where
|
where
|
||||||
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
||||||
colheadings = ["Commodity" | commodity_column_ opts]
|
colheadings = ["Commodity" | commodity_layout_ opts == CommodityColumn]
|
||||||
++ map (reportPeriodName balanceaccum_ spans) spans
|
++ map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | totalscolumn]
|
++ [" Total" | totalscolumn]
|
||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
@ -676,20 +685,23 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
|||||||
| no_total_ opts = id
|
| no_total_ opts = id
|
||||||
| otherwise =
|
| otherwise =
|
||||||
let totalrows = multiBalanceRowAsTableText opts tr
|
let totalrows = multiBalanceRowAsTableText opts tr
|
||||||
rh = Tab.Group NoLine . replicate (length totalrows) $ Header ""
|
rh = Tab.Group Tab.NoLine . replicate (length totalrows) $ Tab.Header ""
|
||||||
ch = Header [] -- ignored
|
ch = Tab.Header [] -- ignored
|
||||||
in (flip (concatTables SingleLine) $ Table rh ch totalrows)
|
in (flip (concatTables Tab.SingleLine) $ Table rh ch totalrows)
|
||||||
maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals)
|
maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals)
|
||||||
| otherwise = id
|
| otherwise = id
|
||||||
|
|
||||||
multiBalanceRowAsWbs :: AmountDisplayOpts -> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
|
multiBalanceRowAsWbs :: AmountDisplayOpts -> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]]
|
||||||
multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg)
|
multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg) =
|
||||||
| not commodity_column_ = [fmap (showMixedAmountB bopts) all]
|
case commodity_layout_ of
|
||||||
| otherwise =
|
CommodityOneLine -> [fmap (showMixedAmountB bopts) all]
|
||||||
zipWith (:) (fmap wbFromText cs) -- add symbols
|
CommodityMultiLine -> paddedTranspose mempty
|
||||||
. transpose -- each row becomes a list of Text quantities
|
. fmap (showMixedAmountLinesB bopts{displayMaxWidth=Nothing})
|
||||||
. fmap (showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing})
|
$ all
|
||||||
$ all
|
CommodityColumn -> zipWith (:) (fmap wbFromText cs) -- add symbols
|
||||||
|
. transpose -- each row becomes a list of Text quantities
|
||||||
|
. fmap (showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing})
|
||||||
|
$ all
|
||||||
where
|
where
|
||||||
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
||||||
cs = S.toList . foldl' S.union mempty $ fmap maCommodities all
|
cs = S.toList . foldl' S.union mempty $ fmap maCommodities all
|
||||||
@ -697,6 +709,20 @@ multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg)
|
|||||||
++ [rowtot | totalscolumn && not (null as)]
|
++ [rowtot | totalscolumn && not (null as)]
|
||||||
++ [rowavg | average_ && not (null as)]
|
++ [rowavg | average_ && not (null as)]
|
||||||
|
|
||||||
|
paddedTranspose :: a -> [[a]] -> [[a]]
|
||||||
|
paddedTranspose _ [] = [[]]
|
||||||
|
paddedTranspose n as = take (maximum . map length $ as) . trans $ as
|
||||||
|
where
|
||||||
|
trans ([] : xss) = (n : map h xss) : trans ([n] : map t xss)
|
||||||
|
trans ((x : xs) : xss) = (x : map h xss) : trans (m xs : map t xss)
|
||||||
|
trans [] = []
|
||||||
|
h (x:_) = x
|
||||||
|
h [] = n
|
||||||
|
t (_:xs) = xs
|
||||||
|
t [] = [n]
|
||||||
|
m (x:xs) = x:xs
|
||||||
|
m [] = [n]
|
||||||
|
|
||||||
multiBalanceRowAsCsvText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[T.Text]]
|
multiBalanceRowAsCsvText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[T.Text]]
|
||||||
multiBalanceRowAsCsvText opts = fmap (fmap wbToText) . multiBalanceRowAsWbs (balanceOpts False opts) opts
|
multiBalanceRowAsCsvText opts = fmap (fmap wbToText) . multiBalanceRowAsWbs (balanceOpts False opts) opts
|
||||||
|
|
||||||
|
|||||||
@ -150,11 +150,11 @@ roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{_rsReportOpts=ReportO
|
|||||||
, T.pack $ printf "%0.2f%%" $ smallIsZero twr ]
|
, T.pack $ printf "%0.2f%%" $ smallIsZero twr ]
|
||||||
|
|
||||||
let table = Table
|
let table = Table
|
||||||
(Tab.Group NoLine (map (Header . T.pack . show) (take (length tableBody) [1..])))
|
(Tab.Group Tab.NoLine (map (Header . T.pack . show) (take (length tableBody) [1..])))
|
||||||
(Tab.Group DoubleLine
|
(Tab.Group Tab.DoubleLine
|
||||||
[ Tab.Group SingleLine [Header "Begin", Header "End"]
|
[ Tab.Group Tab.SingleLine [Header "Begin", Header "End"]
|
||||||
, Tab.Group SingleLine [Header "Value (begin)", Header "Cashflow", Header "Value (end)", Header "PnL"]
|
, Tab.Group Tab.SingleLine [Header "Value (begin)", Header "Cashflow", Header "Value (end)", Header "PnL"]
|
||||||
, Tab.Group SingleLine [Header "IRR", Header "TWR"]])
|
, Tab.Group Tab.SingleLine [Header "IRR", Header "TWR"]])
|
||||||
tableBody
|
tableBody
|
||||||
|
|
||||||
TL.putStrLn $ Tab.render prettyTables id id id table
|
TL.putStrLn $ Tab.render prettyTables id id id table
|
||||||
@ -239,9 +239,9 @@ timeWeightedReturn showCashFlow prettyTables investmentsQuery trans mixedAmountV
|
|||||||
TL.putStr $ Tab.render prettyTables id id T.pack
|
TL.putStr $ Tab.render prettyTables id id T.pack
|
||||||
(Table
|
(Table
|
||||||
(Tab.Group NoLine (map (Header . showDate) dates))
|
(Tab.Group NoLine (map (Header . showDate) dates))
|
||||||
(Tab.Group DoubleLine [ Tab.Group SingleLine [Header "Portfolio value", Header "Unit balance"]
|
(Tab.Group DoubleLine [ Tab.Group Tab.SingleLine [Tab.Header "Portfolio value", Tab.Header "Unit balance"]
|
||||||
, Tab.Group SingleLine [Header "Pnl", Header "Cashflow", Header "Unit price", Header "Units"]
|
, Tab.Group Tab.SingleLine [Tab.Header "Pnl", Tab.Header "Cashflow", Tab.Header "Unit price", Tab.Header "Units"]
|
||||||
, Tab.Group SingleLine [Header "New Unit Balance"]])
|
, Tab.Group Tab.SingleLine [Tab.Header "New Unit Balance"]])
|
||||||
[ [value, oldBalance, pnl, cashflow, prc, udelta, balance]
|
[ [value, oldBalance, pnl, cashflow, prc, udelta, balance]
|
||||||
| value <- map showDecimal valuesOnDate
|
| value <- map showDecimal valuesOnDate
|
||||||
| oldBalance <- map showDecimal (0:unitBalances)
|
| oldBalance <- map showDecimal (0:unitBalances)
|
||||||
@ -268,8 +268,8 @@ internalRateOfReturn showCashFlow prettyTables (OneSpan spanBegin spanEnd valueB
|
|||||||
let (dates, amounts) = unzip totalCF
|
let (dates, amounts) = unzip totalCF
|
||||||
TL.putStrLn $ Tab.render prettyTables id id id
|
TL.putStrLn $ Tab.render prettyTables id id id
|
||||||
(Table
|
(Table
|
||||||
(Tab.Group NoLine (map (Header . showDate) dates))
|
(Tab.Group Tab.NoLine (map (Header . showDate) dates))
|
||||||
(Tab.Group SingleLine [Header "Amount"])
|
(Tab.Group Tab.SingleLine [Header "Amount"])
|
||||||
(map ((:[]) . T.pack . showMixedAmount) amounts))
|
(map ((:[]) . T.pack . showMixedAmount) amounts))
|
||||||
|
|
||||||
-- 0% is always a solution, so require at least something here
|
-- 0% is always a solution, so require at least something here
|
||||||
|
|||||||
@ -84,13 +84,21 @@ compoundBalanceCommandMode CompoundBalanceCommandSpec{..} =
|
|||||||
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
|
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
|
||||||
,flagNone ["sort-amount","S"] (setboolopt "sort-amount") "sort by amount instead of account code/name"
|
,flagNone ["sort-amount","S"] (setboolopt "sort-amount") "sort by amount instead of account code/name"
|
||||||
,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total"
|
,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total"
|
||||||
,flagNone ["commodity-column"] (setboolopt "commodity-column")
|
,flagReq ["commodity-layout"] (\s opts -> Right $ setopt "commodity-layout" s opts) "ARG"
|
||||||
"show commodity symbols in a separate column, amounts as bare numbers, one row per commodity"
|
(unlines
|
||||||
|
["show multicommodity amounts in the given ARG. ARG can be:"
|
||||||
|
,"'oneline': show all commodities on a single line"
|
||||||
|
,"'multiline': show each commodity on a new line"
|
||||||
|
,"'column': show commodity symbols in a separate column and amounts as bare numbers"
|
||||||
|
])
|
||||||
,outputFormatFlag ["txt","html","csv","json"]
|
,outputFormatFlag ["txt","html","csv","json"]
|
||||||
,outputFileFlag
|
,outputFileFlag
|
||||||
])
|
])
|
||||||
[generalflagsgroup1]
|
[generalflagsgroup1]
|
||||||
hiddenflags
|
(hiddenflags ++
|
||||||
|
[ flagNone ["commodity-column"] (setboolopt "commodity-column")
|
||||||
|
"show commodity symbols in a separate column, amounts as bare numbers, one row per commodity"
|
||||||
|
])
|
||||||
([], Just $ argsFlag "[QUERY]")
|
([], Just $ argsFlag "[QUERY]")
|
||||||
where
|
where
|
||||||
defaultMarker :: BalanceAccumulation -> String
|
defaultMarker :: BalanceAccumulation -> String
|
||||||
@ -219,7 +227,7 @@ compoundBalanceReportAsText ropts
|
|||||||
let totalrows = multiBalanceRowAsTableText ropts netrow
|
let totalrows = multiBalanceRowAsTableText ropts netrow
|
||||||
rh = Tab.Group NoLine $ map Header ("Net:" : replicate (length totalrows - 1) "")
|
rh = Tab.Group NoLine $ map Header ("Net:" : replicate (length totalrows - 1) "")
|
||||||
ch = Header [] -- ignored
|
ch = Header [] -- ignored
|
||||||
in ((concatTables DoubleLine) bigtable $ Table rh ch totalrows)
|
in ((concatTables Tab.DoubleLine) bigtable $ Table rh ch totalrows)
|
||||||
|
|
||||||
-- | Convert a named multi balance report to a table suitable for
|
-- | Convert a named multi balance report to a table suitable for
|
||||||
-- concatenating with others to make a compound balance report table.
|
-- concatenating with others to make a compound balance report table.
|
||||||
@ -228,7 +236,7 @@ compoundBalanceReportAsText ropts
|
|||||||
-- convert to table
|
-- convert to table
|
||||||
Table lefthdrs tophdrs cells = balanceReportAsTable ropts r
|
Table lefthdrs tophdrs cells = balanceReportAsTable ropts r
|
||||||
-- tweak the layout
|
-- tweak the layout
|
||||||
t = Table (Tab.Group SingleLine [Header title, lefthdrs]) tophdrs ([]:cells)
|
t = Table (Tab.Group Tab.SingleLine [Tab.Header title, lefthdrs]) tophdrs ([]:cells)
|
||||||
|
|
||||||
-- | Render a compound balance report as CSV.
|
-- | Render a compound balance report as CSV.
|
||||||
-- Subreports' CSV is concatenated, with the headings rows replaced by a
|
-- Subreports' CSV is concatenated, with the headings rows replaced by a
|
||||||
@ -239,7 +247,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor
|
|||||||
addtotals $
|
addtotals $
|
||||||
padRow title
|
padRow title
|
||||||
: ( "Account"
|
: ( "Account"
|
||||||
: ["Commodity" | commodity_column_ ropts]
|
: ["Commodity" | commodity_layout_ ropts == CommodityColumn]
|
||||||
++ map (reportPeriodName (balanceaccum_ ropts) colspans) colspans
|
++ map (reportPeriodName (balanceaccum_ ropts) colspans) colspans
|
||||||
++ (if row_total_ ropts then ["Total"] else [])
|
++ (if row_total_ ropts then ["Total"] else [])
|
||||||
++ (if average_ ropts then ["Average"] else [])
|
++ (if average_ ropts then ["Average"] else [])
|
||||||
@ -256,7 +264,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor
|
|||||||
| null subreports = 1
|
| null subreports = 1
|
||||||
| otherwise =
|
| otherwise =
|
||||||
(1 +) $ -- account name column
|
(1 +) $ -- account name column
|
||||||
(if commodity_column_ ropts then (1+) else id) $
|
(if commodity_layout_ ropts == CommodityColumn then (1+) else id) $
|
||||||
(if row_total_ ropts then (1+) else id) $
|
(if row_total_ ropts then (1+) else id) $
|
||||||
(if average_ ropts then (1+) else id) $
|
(if average_ ropts then (1+) else id) $
|
||||||
maximum $ -- depends on non-null subreports
|
maximum $ -- depends on non-null subreports
|
||||||
@ -278,7 +286,7 @@ compoundBalanceReportAsHtml ropts cbr =
|
|||||||
titlerows =
|
titlerows =
|
||||||
(tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title)
|
(tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title)
|
||||||
: [thRow $
|
: [thRow $
|
||||||
"" : ["Commodity" | commodity_column_ ropts] ++
|
"" : ["Commodity" | commodity_layout_ ropts == CommodityColumn] ++
|
||||||
map (reportPeriodName (balanceaccum_ ropts) colspans) colspans
|
map (reportPeriodName (balanceaccum_ ropts) colspans) colspans
|
||||||
++ (if row_total_ ropts then ["Total"] else [])
|
++ (if row_total_ ropts then ["Total"] else [])
|
||||||
++ (if average_ ropts then ["Average"] else [])
|
++ (if average_ ropts then ["Average"] else [])
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user