lib!: Rename CommodityLayout to Layout and rename constructors.
Their scope is more than just commodities.
This commit is contained in:
parent
6ce70351fd
commit
3884f90cc6
@ -241,7 +241,7 @@ budgetReportAsTable
|
|||||||
(Tab.Group Tab.NoLine $ map Tab.Header colheadings)
|
(Tab.Group Tab.NoLine $ map Tab.Header colheadings)
|
||||||
rows
|
rows
|
||||||
where
|
where
|
||||||
colheadings = ["Commodity" | commodity_layout_ == CommodityBare]
|
colheadings = ["Commodity" | layout_ == LayoutBare]
|
||||||
++ map (reportPeriodName balanceaccum_ spans) spans
|
++ map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | row_total_]
|
++ [" Total" | row_total_]
|
||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
@ -283,9 +283,9 @@ 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_layout_ == CommodityBare`
|
-- commodities are shown with the amounts without `layout_ == LayoutBare`
|
||||||
prependcs cs
|
prependcs cs
|
||||||
| commodity_layout_ /= CommodityBare = id
|
| layout_ /= LayoutBare = id
|
||||||
| otherwise = zipWith (:) cs
|
| otherwise = zipWith (:) cs
|
||||||
|
|
||||||
rowToBudgetCells (PeriodicReportRow _ as rowtot rowavg) = as
|
rowToBudgetCells (PeriodicReportRow _ as rowtot rowavg) = as
|
||||||
@ -294,8 +294,8 @@ budgetReportAsTable
|
|||||||
|
|
||||||
-- functions for displaying budget cells depending on `commodity-layout_` option
|
-- functions for displaying budget cells depending on `commodity-layout_` option
|
||||||
rowfuncs :: [CommoditySymbol] -> (BudgetShowMixed, BudgetPercBudget)
|
rowfuncs :: [CommoditySymbol] -> (BudgetShowMixed, BudgetPercBudget)
|
||||||
rowfuncs cs = case commodity_layout_ of
|
rowfuncs cs = case layout_ of
|
||||||
CommodityWide width ->
|
LayoutWide width ->
|
||||||
( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=width}
|
( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=width}
|
||||||
, \a -> pure . percentage a)
|
, \a -> pure . percentage a)
|
||||||
_ -> ( showMixedAmountLinesB noPrice{displayOrder=Just cs, displayMinWidth=Nothing, displayColour=color_}
|
_ -> ( showMixedAmountLinesB noPrice{displayOrder=Just cs, displayMinWidth=Nothing, displayColour=color_}
|
||||||
@ -407,7 +407,7 @@ budgetReportAsCsv
|
|||||||
|
|
||||||
-- heading row
|
-- heading row
|
||||||
("Account" :
|
("Account" :
|
||||||
["Commodity" | commodity_layout_ == CommodityBare ]
|
["Commodity" | layout_ == LayoutBare ]
|
||||||
++ 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_]
|
||||||
@ -427,7 +427,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))
|
||||||
| commodity_layout_ /= CommodityBare = [render row : fmap showNorm all]
|
| layout_ /= LayoutBare = [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
|
||||||
|
|||||||
@ -586,11 +586,11 @@ 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
|
||||||
| commodity_layout_ /= CommodityBare || transpose_ = fmap (Tab.textCell Tab.TopRight)
|
| layout_ /= LayoutBare || 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)
|
||||||
| commodity_layout_ /= CommodityBare || transpose_ =
|
| layout_ /= LayoutBare || 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))
|
||||||
|
|||||||
@ -26,7 +26,7 @@ module Hledger.Reports.ReportOptions (
|
|||||||
BalanceAccumulation(..),
|
BalanceAccumulation(..),
|
||||||
AccountListMode(..),
|
AccountListMode(..),
|
||||||
ValuationType(..),
|
ValuationType(..),
|
||||||
CommodityLayout(..),
|
Layout(..),
|
||||||
defreportopts,
|
defreportopts,
|
||||||
rawOptsToReportOpts,
|
rawOptsToReportOpts,
|
||||||
defreportspec,
|
defreportspec,
|
||||||
@ -109,9 +109,9 @@ data AccountListMode = ALFlat | ALTree deriving (Eq, Show)
|
|||||||
|
|
||||||
instance Default AccountListMode where def = ALFlat
|
instance Default AccountListMode where def = ALFlat
|
||||||
|
|
||||||
data CommodityLayout = CommodityWide (Maybe Int)
|
data Layout = LayoutWide (Maybe Int)
|
||||||
| CommodityTall
|
| LayoutTall
|
||||||
| CommodityBare
|
| LayoutBare
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
-- | Standard options for customising report filtering and output.
|
-- | Standard options for customising report filtering and output.
|
||||||
@ -169,7 +169,7 @@ data ReportOpts = ReportOpts {
|
|||||||
-- 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_layout_ :: CommodityLayout
|
,layout_ :: Layout
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
||||||
instance Default ReportOpts where def = defreportopts
|
instance Default ReportOpts where def = defreportopts
|
||||||
@ -208,7 +208,7 @@ defreportopts = ReportOpts
|
|||||||
, normalbalance_ = Nothing
|
, normalbalance_ = Nothing
|
||||||
, color_ = False
|
, color_ = False
|
||||||
, transpose_ = False
|
, transpose_ = False
|
||||||
, commodity_layout_ = CommodityWide Nothing
|
, layout_ = LayoutWide Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Generate a ReportOpts from raw command-line input, given a day.
|
-- | Generate a ReportOpts from raw command-line input, given a day.
|
||||||
@ -262,7 +262,7 @@ rawOptsToReportOpts d 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_layout_ = commoditylayoutopt rawopts
|
,layout_ = layoutopt rawopts
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | The result of successfully parsing a ReportOpts on a particular
|
-- | The result of successfully parsing a ReportOpts on a particular
|
||||||
@ -337,17 +337,17 @@ balanceAccumulationOverride rawopts = choiceopt parse rawopts <|> reportbal
|
|||||||
CalcValueChange -> Just PerPeriod
|
CalcValueChange -> Just PerPeriod
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
commoditylayoutopt :: RawOpts -> CommodityLayout
|
layoutopt :: RawOpts -> Layout
|
||||||
commoditylayoutopt rawopts = fromMaybe (CommodityWide Nothing) $ layout <|> column
|
layoutopt rawopts = fromMaybe (LayoutWide Nothing) $ layout <|> column
|
||||||
where
|
where
|
||||||
layout = parse <$> maybestringopt "layout" rawopts
|
layout = parse <$> maybestringopt "layout" rawopts
|
||||||
column = CommodityBare <$ guard (boolopt "commodity-column" rawopts)
|
column = LayoutBare <$ guard (boolopt "commodity-column" rawopts)
|
||||||
|
|
||||||
parse opt = maybe err snd $ guard (not $ null s) *> find (isPrefixOf s . fst) checkNames
|
parse opt = maybe err snd $ guard (not $ null s) *> find (isPrefixOf s . fst) checkNames
|
||||||
where
|
where
|
||||||
checkNames = [ ("wide", CommodityWide w)
|
checkNames = [ ("wide", LayoutWide w)
|
||||||
, ("tall", CommodityTall)
|
, ("tall", LayoutTall)
|
||||||
, ("bare", CommodityBare)
|
, ("bare", LayoutBare)
|
||||||
]
|
]
|
||||||
-- For `--layout=elided,n`, elide to the given width
|
-- For `--layout=elided,n`, elide to the given width
|
||||||
(s,n) = break (==',') $ map toLower opt
|
(s,n) = break (==',') $ map toLower opt
|
||||||
|
|||||||
@ -408,13 +408,13 @@ 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_layout_ opts == CommodityBare then (:) "commodity" else id) $ ["balance"]))
|
("account" : ((if layout_ opts == LayoutBare 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 = case commodity_layout_ opts of
|
rows name ma = case layout_ opts of
|
||||||
CommodityBare ->
|
LayoutBare ->
|
||||||
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
|
||||||
_ -> [[showName name, renderAmount ma]]
|
_ -> [[showName name, renderAmount ma]]
|
||||||
@ -422,14 +422,14 @@ balanceReportAsCsv opts (items, total) =
|
|||||||
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_layout_ opts == CommodityBare then Just (S.toList $ maCommodities amt) else Nothing
|
order = if layout_ opts == LayoutBare 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)) = case commodity_layout_ opts of
|
balanceReportAsText opts ((items, total)) = case layout_ opts of
|
||||||
CommodityBare | iscustom -> error' "Custom format not supported with commodity columns" -- PARTIAL:
|
LayoutBare | iscustom -> error' "Custom format not supported with commodity columns" -- PARTIAL:
|
||||||
CommodityBare -> balanceReportAsText' opts ((items, total))
|
LayoutBare -> balanceReportAsText' opts ((items, total))
|
||||||
_ -> unlinesB lines <> unlinesB (if no_total_ opts then [] else [overline, totalLines])
|
_ -> unlinesB lines <> unlinesB (if no_total_ opts then [] else [overline, totalLines])
|
||||||
where
|
where
|
||||||
(lines, sizes) = unzip $ map (balanceReportItemAsText opts) items
|
(lines, sizes) = unzip $ map (balanceReportItemAsText opts) items
|
||||||
@ -525,7 +525,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_layout_ == CommodityBare] ++ map showDateSpan colspans
|
( ("account" : ["commodity" | layout_ == LayoutBare] ++ 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
|
||||||
@ -672,7 +672,7 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
|||||||
(concat rows)
|
(concat rows)
|
||||||
where
|
where
|
||||||
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
||||||
colheadings = ["Commodity" | commodity_layout_ opts == CommodityBare]
|
colheadings = ["Commodity" | layout_ opts == LayoutBare]
|
||||||
++ map (reportPeriodName balanceaccum_ spans) spans
|
++ map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | totalscolumn]
|
++ [" Total" | totalscolumn]
|
||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
@ -694,12 +694,12 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
|||||||
|
|
||||||
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) =
|
||||||
case commodity_layout_ of
|
case layout_ of
|
||||||
CommodityWide width -> [fmap (showMixedAmountB bopts{displayMaxWidth=width}) all]
|
LayoutWide width -> [fmap (showMixedAmountB bopts{displayMaxWidth=width}) all]
|
||||||
CommodityTall -> paddedTranspose mempty
|
LayoutTall -> paddedTranspose mempty
|
||||||
. fmap (showMixedAmountLinesB bopts{displayMaxWidth=Nothing})
|
. fmap (showMixedAmountLinesB bopts{displayMaxWidth=Nothing})
|
||||||
$ all
|
$ all
|
||||||
CommodityBare -> zipWith (:) (fmap wbFromText cs) -- add symbols
|
LayoutBare -> zipWith (:) (fmap wbFromText cs) -- add symbols
|
||||||
. transpose -- each row becomes a list of Text quantities
|
. transpose -- each row becomes a list of Text quantities
|
||||||
. fmap (showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing})
|
. fmap (showMixedAmountLinesB bopts{displayOrder=Just cs, displayMinWidth=Nothing})
|
||||||
$ all
|
$ all
|
||||||
|
|||||||
@ -248,7 +248,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor
|
|||||||
addtotals $
|
addtotals $
|
||||||
padRow title
|
padRow title
|
||||||
: ( "Account"
|
: ( "Account"
|
||||||
: ["Commodity" | commodity_layout_ ropts == CommodityBare]
|
: ["Commodity" | layout_ ropts == LayoutBare]
|
||||||
++ 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 [])
|
||||||
@ -265,7 +265,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_layout_ ropts == CommodityBare then (1+) else id) $
|
(if layout_ ropts == LayoutBare 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
|
||||||
@ -287,7 +287,7 @@ compoundBalanceReportAsHtml ropts cbr =
|
|||||||
titlerows =
|
titlerows =
|
||||||
(tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title)
|
(tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title)
|
||||||
: [thRow $
|
: [thRow $
|
||||||
"" : ["Commodity" | commodity_layout_ ropts == CommodityBare] ++
|
"" : ["Commodity" | layout_ ropts == LayoutBare] ++
|
||||||
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