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] | ||||
| 
 | ||||
| orderedAmounts :: AmountDisplayOpts -> MixedAmount -> [Amount] | ||||
| orderedAmounts AmountDisplayOpts{displayOrder=ord} ma | ||||
|   | Just cs <- ord = fmap pad cs | ||||
|   | otherwise = as | ||||
| orderedAmounts dopts = maybe id (mapM pad) (displayOrder dopts) . amounts | ||||
|   where | ||||
|     as = amounts ma | ||||
|     pad c = fromMaybe (amountWithCommodity c nullamt) . find ((==) c . acommodity) $ as | ||||
|     pad c = fromMaybe (amountWithCommodity c nullamt) . find ((c==) . acommodity) | ||||
| 
 | ||||
| 
 | ||||
| data AmountDisplay = AmountDisplay | ||||
|  | ||||
| @ -38,7 +38,7 @@ import qualified Data.Text.Lazy as TL | ||||
| import qualified Data.Text.Lazy.Builder as TB | ||||
| --import System.Console.CmdArgs.Explicit as C | ||||
| --import Lucid as L | ||||
| import Text.Tabular.AsciiWide as Tab | ||||
| import qualified Text.Tabular.AsciiWide as Tab | ||||
| 
 | ||||
| import Hledger.Data | ||||
| import Hledger.Utils | ||||
| @ -230,18 +230,18 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $ | ||||
|            <> ":" | ||||
| 
 | ||||
| -- | 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 | ||||
|   ReportOpts{..} | ||||
|   (PeriodicReport spans items tr) = | ||||
|     maybetransposetable $ | ||||
|     addtotalrow $ | ||||
|     Table | ||||
|       (Tab.Group NoLine $ map Header accts) | ||||
|       (Tab.Group NoLine $ map Header colheadings) | ||||
|     Tab.Table | ||||
|       (Tab.Group Tab.NoLine $ map Tab.Header accts) | ||||
|       (Tab.Group Tab.NoLine $ map Tab.Header colheadings) | ||||
|       rows | ||||
|   where | ||||
|     colheadings = ["Commodity" | commodity_column_] | ||||
|     colheadings = ["Commodity" | commodity_layout_ == CommodityColumn] | ||||
|                   ++ map (reportPeriodName balanceaccum_ spans) spans | ||||
|                   ++ ["  Total" | row_total_] | ||||
|                   ++ ["Average" | average_] | ||||
| @ -255,16 +255,16 @@ budgetReportAsTable | ||||
| 
 | ||||
|     addtotalrow | ||||
|       | no_total_ = id | ||||
|       | otherwise = let rh = Tab.Group NoLine . replicate (length totalrows) $ Header "" | ||||
|                         ch = Header [] -- ignored | ||||
|                      in (flip (concatTables SingleLine) $ Table rh ch totalrows) | ||||
|       | otherwise = let rh = Tab.Group Tab.NoLine . replicate (length totalrows) $ Tab.Header "" | ||||
|                         ch = Tab.Header [] -- ignored | ||||
|                      in (flip (Tab.concatTables Tab.SingleLine) $ Tab.Table rh ch totalrows) | ||||
| 
 | ||||
|     maybetranspose | ||||
|       | transpose_ = transpose | ||||
|       | otherwise  = id | ||||
| 
 | ||||
|     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 | ||||
| 
 | ||||
|     (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 | ||||
|         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 | ||||
|           | commodity_column_ = zipWith (:) cs | ||||
|           | otherwise = id | ||||
|           | commodity_layout_ /= CommodityColumn = id | ||||
|           | otherwise = zipWith (:) cs | ||||
| 
 | ||||
|     rowToBudgetCells (PeriodicReportRow _ as rowtot rowavg) = as | ||||
|         ++ [rowtot | row_total_ && 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 cs | ||||
|       | not commodity_column_ = | ||||
|       | commodity_layout_ == CommodityOneLine = | ||||
|           ( pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=Just 32} | ||||
|           , \a -> pure . percentage a) | ||||
|       | otherwise = | ||||
| @ -408,7 +408,7 @@ budgetReportAsCsv | ||||
| 
 | ||||
|   -- heading row | ||||
|   ("Account" : | ||||
|   ["Commodity" | commodity_column_ ] | ||||
|   ["Commodity" | commodity_layout_ == CommodityColumn ] | ||||
|    ++ concatMap (\span -> [showDateSpan span, "budget"]) colspans | ||||
|    ++ concat [["Total"  ,"budget"] | row_total_] | ||||
|    ++ concat [["Average","budget"] | average_] | ||||
| @ -428,7 +428,7 @@ budgetReportAsCsv | ||||
|                -> PeriodicReportRow a BudgetCell | ||||
|                -> [[Text]] | ||||
|     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 = | ||||
|             joinNames . zipWith (:) cs  -- add symbols and names | ||||
|           . 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 | ||||
|   where | ||||
|     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)) | ||||
| 
 | ||||
|     renderRow (rh, row) | ||||
|       | not commodity_column_ || transpose_ = | ||||
|       | commodity_layout_ /= CommodityColumn || transpose_ = | ||||
|           (Tab.textCell Tab.TopLeft rh, fmap (Tab.Cell Tab.TopRight . pure) row) | ||||
|       | otherwise = | ||||
|           (Tab.textCell Tab.TopLeft rh, zipWith ($) (Tab.Cell Tab.TopLeft : repeat (Tab.Cell Tab.TopRight)) (fmap pure row)) | ||||
| 
 | ||||
| 
 | ||||
| 
 | ||||
| -- tests | ||||
| 
 | ||||
| tests_MultiBalanceReport = testGroup "MultiBalanceReport" [ | ||||
|  | ||||
| @ -26,6 +26,7 @@ module Hledger.Reports.ReportOptions ( | ||||
|   BalanceAccumulation(..), | ||||
|   AccountListMode(..), | ||||
|   ValuationType(..), | ||||
|   CommodityLayout(..), | ||||
|   defreportopts, | ||||
|   rawOptsToReportOpts, | ||||
|   defreportspec, | ||||
| @ -62,7 +63,8 @@ module Hledger.Reports.ReportOptions ( | ||||
| where | ||||
| 
 | ||||
| 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.Extra (eitherToMaybe) | ||||
| import Data.Functor.Identity (Identity(..)) | ||||
| @ -71,7 +73,7 @@ import Data.Maybe (fromMaybe, mapMaybe) | ||||
| import qualified Data.Text as T | ||||
| import Data.Time.Calendar (Day, addDays) | ||||
| import Data.Default (Default(..)) | ||||
| import Safe (headMay, lastDef, lastMay, maximumMay) | ||||
| import Safe (headDef, headMay, lastDef, lastMay, maximumMay) | ||||
| 
 | ||||
| import Text.Megaparsec.Custom | ||||
| 
 | ||||
| @ -107,6 +109,8 @@ data AccountListMode = ALFlat | ALTree deriving (Eq, Show) | ||||
| 
 | ||||
| instance Default AccountListMode where def = ALFlat | ||||
| 
 | ||||
| data CommodityLayout = CommodityOneLine | CommodityMultiLine | CommodityColumn deriving (Eq, Show) | ||||
| 
 | ||||
| -- | Standard options for customising report filtering and output. | ||||
| -- Most of these correspond to standard hledger command-line options | ||||
| -- or query arguments, but not all. Some are used only by certain | ||||
| @ -161,7 +165,7 @@ data ReportOpts = ReportOpts { | ||||
|       --   whether stdout is an interactive terminal, and the value of | ||||
|       --   TERM and existence of NO_COLOR environment variables. | ||||
|     ,transpose_        :: Bool | ||||
|     ,commodity_column_:: Bool | ||||
|     ,commodity_layout_ :: CommodityLayout | ||||
|  } deriving (Show) | ||||
| 
 | ||||
| instance Default ReportOpts where def = defreportopts | ||||
| @ -199,7 +203,7 @@ defreportopts = ReportOpts | ||||
|     , normalbalance_    = Nothing | ||||
|     , color_            = False | ||||
|     , transpose_        = False | ||||
|     , commodity_column_ = False | ||||
|     , commodity_layout_ = CommodityOneLine | ||||
|     } | ||||
| 
 | ||||
| -- | Generate a ReportOpts from raw command-line input, given a day. | ||||
| @ -252,7 +256,7 @@ rawOptsToReportOpts d rawopts = | ||||
|           ,pretty_           = pretty | ||||
|           ,color_            = useColorOnStdout -- a lower-level helper | ||||
|           ,transpose_        = boolopt "transpose" rawopts | ||||
|           ,commodity_column_= boolopt "commodity-column" rawopts | ||||
|           ,commodity_layout_ = commoditylayoutopt rawopts | ||||
|           } | ||||
| 
 | ||||
| -- | The result of successfully parsing a ReportOpts on a particular | ||||
| @ -327,6 +331,18 @@ balanceAccumulationOverride rawopts = choiceopt parse rawopts <|> reportbal | ||||
|       CalcValueChange -> Just PerPeriod | ||||
|       _               -> 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 | ||||
| -- options appearing in the command line. | ||||
| -- 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 Lucid as L | ||||
| 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.Cli.CliOptions | ||||
| @ -315,14 +318,22 @@ balancemode = hledgerCommandMode | ||||
|     ,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total" | ||||
|     ,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign" | ||||
|     ,flagNone ["transpose"] (setboolopt "transpose") "transpose rows and columns" | ||||
|     ,flagNone ["commodity-column"] (setboolopt "commodity-column") | ||||
|       "show commodity symbols in a separate column, amounts as bare numbers, one row per commodity" | ||||
|     ,flagReq  ["commodity-layout"] (\s opts -> Right $ setopt "commodity-layout" s opts) "ARG" | ||||
|       (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"] | ||||
|     ,outputFileFlag | ||||
|     ] | ||||
|   ) | ||||
|   [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]") | ||||
| 
 | ||||
| -- | 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. | ||||
| balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV | ||||
| 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) | ||||
|   ++ if no_total_ opts then [] else rows "total" total | ||||
|   where | ||||
|     rows :: AccountName -> MixedAmount -> [[T.Text]] | ||||
|     rows name ma | ||||
|       | commodity_column_ opts = | ||||
|     rows name ma = case commodity_layout_ opts of | ||||
|       CommodityColumn -> | ||||
|           fmap (\(k, a) -> [showName name, k, renderAmount . mixedAmount . amountStripPrices $ a]) | ||||
|           . M.toList . foldl' sumAmounts mempty . amounts $ ma | ||||
|       | otherwise = [[showName name, renderAmount ma]] | ||||
|       _ -> [[showName name, renderAmount ma]] | ||||
| 
 | ||||
|     showName = accountNameDrop (drop_ opts) | ||||
|     renderAmount amt = wbToText $ showMixedAmountB bopts amt | ||||
|       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 | ||||
| 
 | ||||
| -- | Render a single-column balance report as plain text. | ||||
| balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder | ||||
| balanceReportAsText opts ((items, total)) | ||||
|   | not (commodity_column_ opts) = | ||||
|       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)) | ||||
| balanceReportAsText opts ((items, total)) = case commodity_layout_ opts of | ||||
|     CommodityColumn | iscustom -> error' "Custom format not supported with commodity columns"  -- PARTIAL: | ||||
|     CommodityColumn -> balanceReportAsText' opts ((items, total)) | ||||
|     _ -> unlinesB lines <> unlinesB (if no_total_ opts then [] else [overline, totalLines]) | ||||
|   where | ||||
|     (lines, sizes) = unzip $ map (balanceReportItemAsText opts) items | ||||
|     -- 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 | ||||
| balanceReportAsText' :: ReportOpts -> BalanceReport -> TB.Builder | ||||
| 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)] | ||||
|   where | ||||
|     render (_, acctname, depth, amt) = | ||||
| @ -483,7 +492,7 @@ renderBalanceReportItem opts (acctname, depth, total) = | ||||
|       BottomAligned comps -> renderRow' $ render False False comps | ||||
|   where | ||||
|     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 ) | ||||
| 
 | ||||
|     render topaligned oneline = map (renderComponent topaligned oneline opts (acctname, depth, total)) | ||||
| @ -515,7 +524,7 @@ multiBalanceReportAsCsv opts@ReportOpts{..} = | ||||
| 
 | ||||
| multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV) | ||||
| 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_] | ||||
|        ++ ["average" | average_] | ||||
|       ) : concatMap (fullRowAsTexts (accountNameDrop drop_ . prrFullName)) items | ||||
| @ -657,12 +666,12 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_} | ||||
|    maybetranspose $ | ||||
|    addtotalrow $ | ||||
|    Table | ||||
|      (Tab.Group NoLine $ map Header (concat accts)) | ||||
|      (Tab.Group NoLine $ map Header colheadings) | ||||
|      (Tab.Group Tab.NoLine $ map Tab.Header (concat accts)) | ||||
|      (Tab.Group Tab.NoLine $ map Tab.Header colheadings) | ||||
|      (concat rows) | ||||
|   where | ||||
|     totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical] | ||||
|     colheadings = ["Commodity" | commodity_column_ opts] | ||||
|     colheadings = ["Commodity" | commodity_layout_ opts == CommodityColumn] | ||||
|                   ++ map (reportPeriodName balanceaccum_ spans) spans | ||||
|                   ++ ["  Total" | totalscolumn] | ||||
|                   ++ ["Average" | average_] | ||||
| @ -676,17 +685,20 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_} | ||||
|       | no_total_ opts = id | ||||
|       | otherwise = | ||||
|         let totalrows = multiBalanceRowAsTableText opts tr | ||||
|             rh = Tab.Group NoLine . replicate (length totalrows) $ Header "" | ||||
|             ch = Header [] -- ignored | ||||
|          in (flip (concatTables SingleLine) $ Table rh ch totalrows) | ||||
|             rh = Tab.Group Tab.NoLine . replicate (length totalrows) $ Tab.Header "" | ||||
|             ch = Tab.Header [] -- ignored | ||||
|          in (flip (concatTables Tab.SingleLine) $ Table rh ch totalrows) | ||||
|     maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals) | ||||
|                    | otherwise       = id | ||||
| 
 | ||||
| multiBalanceRowAsWbs :: AmountDisplayOpts -> ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]] | ||||
| multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg) | ||||
|   | not commodity_column_ = [fmap (showMixedAmountB bopts) all] | ||||
|   | otherwise = | ||||
|         zipWith (:) (fmap wbFromText cs)  -- add symbols | ||||
| multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg) = | ||||
|     case commodity_layout_ of | ||||
|       CommodityOneLine   -> [fmap (showMixedAmountB bopts) all] | ||||
|       CommodityMultiLine -> paddedTranspose mempty | ||||
|                           . fmap (showMixedAmountLinesB bopts{displayMaxWidth=Nothing}) | ||||
|                           $ 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 | ||||
| @ -697,6 +709,20 @@ multiBalanceRowAsWbs bopts ReportOpts{..} (PeriodicReportRow _ as rowtot rowavg) | ||||
|         ++ [rowtot | totalscolumn && 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 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 ] | ||||
| 
 | ||||
|   let table = Table | ||||
|               (Tab.Group NoLine (map (Header . T.pack . show) (take (length tableBody) [1..]))) | ||||
|               (Tab.Group DoubleLine | ||||
|                [ Tab.Group SingleLine [Header "Begin", Header "End"] | ||||
|                , Tab.Group SingleLine [Header "Value (begin)", Header "Cashflow", Header "Value (end)", Header "PnL"] | ||||
|                , Tab.Group SingleLine [Header "IRR", Header "TWR"]]) | ||||
|               (Tab.Group Tab.NoLine (map (Header . T.pack . show) (take (length tableBody) [1..]))) | ||||
|               (Tab.Group Tab.DoubleLine | ||||
|                [ Tab.Group Tab.SingleLine [Header "Begin", Header "End"] | ||||
|                , Tab.Group Tab.SingleLine [Header "Value (begin)", Header "Cashflow", Header "Value (end)", Header "PnL"] | ||||
|                , Tab.Group Tab.SingleLine [Header "IRR", Header "TWR"]]) | ||||
|               tableBody | ||||
| 
 | ||||
|   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 | ||||
|       (Table | ||||
|        (Tab.Group NoLine (map (Header . showDate) dates)) | ||||
|        (Tab.Group DoubleLine [ Tab.Group SingleLine [Header "Portfolio value", Header "Unit balance"] | ||||
|                          , Tab.Group SingleLine [Header "Pnl", Header "Cashflow", Header "Unit price", Header "Units"] | ||||
|                          , Tab.Group SingleLine [Header "New Unit Balance"]]) | ||||
|        (Tab.Group DoubleLine [ Tab.Group Tab.SingleLine [Tab.Header "Portfolio value", Tab.Header "Unit balance"] | ||||
|                          , Tab.Group Tab.SingleLine [Tab.Header "Pnl", Tab.Header "Cashflow", Tab.Header "Unit price", Tab.Header "Units"] | ||||
|                          , Tab.Group Tab.SingleLine [Tab.Header "New Unit Balance"]]) | ||||
|        [ [value, oldBalance, pnl, cashflow, prc, udelta, balance] | ||||
|        | value <- map showDecimal valuesOnDate | ||||
|        | oldBalance <- map showDecimal (0:unitBalances) | ||||
| @ -268,8 +268,8 @@ internalRateOfReturn showCashFlow prettyTables (OneSpan spanBegin spanEnd valueB | ||||
|     let (dates, amounts) = unzip totalCF | ||||
|     TL.putStrLn $ Tab.render prettyTables id id id | ||||
|       (Table | ||||
|        (Tab.Group NoLine (map (Header . showDate) dates)) | ||||
|        (Tab.Group SingleLine [Header "Amount"]) | ||||
|        (Tab.Group Tab.NoLine (map (Header . showDate) dates)) | ||||
|        (Tab.Group Tab.SingleLine [Header "Amount"]) | ||||
|        (map ((:[]) . T.pack . showMixedAmount) amounts)) | ||||
| 
 | ||||
|   -- 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)" | ||||
|     ,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 ["commodity-column"] (setboolopt "commodity-column") | ||||
|       "show commodity symbols in a separate column, amounts as bare numbers, one row per commodity" | ||||
|     ,flagReq  ["commodity-layout"] (\s opts -> Right $ setopt "commodity-layout" s opts) "ARG" | ||||
|       (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"] | ||||
|     ,outputFileFlag | ||||
|     ]) | ||||
|     [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]") | ||||
|  where | ||||
|    defaultMarker :: BalanceAccumulation -> String | ||||
| @ -219,7 +227,7 @@ compoundBalanceReportAsText ropts | ||||
|         let totalrows = multiBalanceRowAsTableText ropts netrow | ||||
|             rh = Tab.Group NoLine $ map Header ("Net:" : replicate (length totalrows - 1) "") | ||||
|             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 | ||||
|     -- concatenating with others to make a compound balance report table. | ||||
| @ -228,7 +236,7 @@ compoundBalanceReportAsText ropts | ||||
|         -- convert to table | ||||
|         Table lefthdrs tophdrs cells = balanceReportAsTable ropts r | ||||
|         -- 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. | ||||
| -- Subreports' CSV is concatenated, with the headings rows replaced by a | ||||
| @ -239,7 +247,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor | ||||
|     addtotals $ | ||||
|       padRow title | ||||
|       : ( "Account" | ||||
|         : ["Commodity" | commodity_column_ ropts] | ||||
|         : ["Commodity" | commodity_layout_ ropts == CommodityColumn] | ||||
|         ++ map (reportPeriodName (balanceaccum_ ropts) colspans) colspans | ||||
|         ++ (if row_total_ ropts then ["Total"] else []) | ||||
|         ++ (if average_ ropts then ["Average"] else []) | ||||
| @ -256,7 +264,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor | ||||
|           | null subreports = 1 | ||||
|           | otherwise = | ||||
|             (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 average_ ropts then (1+) else id) $ | ||||
|             maximum $ -- depends on non-null subreports | ||||
| @ -278,7 +286,7 @@ compoundBalanceReportAsHtml ropts cbr = | ||||
|     titlerows = | ||||
|       (tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title) | ||||
|       : [thRow $ | ||||
|          "" : ["Commodity" | commodity_column_ ropts] ++ | ||||
|          "" : ["Commodity" | commodity_layout_ ropts == CommodityColumn] ++ | ||||
|          map (reportPeriodName (balanceaccum_ ropts) colspans) colspans | ||||
|          ++ (if row_total_ ropts then ["Total"] else []) | ||||
|          ++ (if average_ ropts then ["Average"] else []) | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user