bs,cf,is,bal,print,reg: support json output format
This commit is contained in:
parent
bc9bdf8108
commit
2a5f7819af
@ -1,6 +1,8 @@
|
|||||||
{- |
|
{- |
|
||||||
New common report types, used by the BudgetReport for now, perhaps all reports later.
|
New common report types, used by the BudgetReport for now, perhaps all reports later.
|
||||||
-}
|
-}
|
||||||
|
{-# LANGUAGE DeriveAnyClass #-}
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
|
||||||
module Hledger.Reports.ReportTypes
|
module Hledger.Reports.ReportTypes
|
||||||
( PeriodicReport(..)
|
( PeriodicReport(..)
|
||||||
@ -17,7 +19,9 @@ module Hledger.Reports.ReportTypes
|
|||||||
, prNormaliseSign
|
, prNormaliseSign
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Aeson
|
||||||
import Data.Decimal
|
import Data.Decimal
|
||||||
|
import GHC.Generics (Generic)
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
|
|
||||||
type Percentage = Decimal
|
type Percentage = Decimal
|
||||||
@ -63,7 +67,7 @@ data PeriodicReport a b =
|
|||||||
-- significant. Usually displayed as report columns.
|
-- significant. Usually displayed as report columns.
|
||||||
, prRows :: [PeriodicReportRow a b] -- One row per account in the report.
|
, prRows :: [PeriodicReportRow a b] -- One row per account in the report.
|
||||||
, prTotals :: PeriodicReportRow () b -- The grand totals row.
|
, prTotals :: PeriodicReportRow () b -- The grand totals row.
|
||||||
} deriving (Show)
|
} deriving (Show, Generic, ToJSON)
|
||||||
|
|
||||||
data PeriodicReportRow a b =
|
data PeriodicReportRow a b =
|
||||||
PeriodicReportRow
|
PeriodicReportRow
|
||||||
@ -72,7 +76,7 @@ data PeriodicReportRow a b =
|
|||||||
, prrAmounts :: [b] -- The data value for each subperiod.
|
, prrAmounts :: [b] -- The data value for each subperiod.
|
||||||
, prrTotal :: b -- The total of this row's values.
|
, prrTotal :: b -- The total of this row's values.
|
||||||
, prrAverage :: b -- The average of this row's values.
|
, prrAverage :: b -- The average of this row's values.
|
||||||
} deriving (Show)
|
} deriving (Show, Generic, ToJSON)
|
||||||
|
|
||||||
-- | Figure out the overall date span of a PeridicReport
|
-- | Figure out the overall date span of a PeridicReport
|
||||||
periodicReportSpan :: PeriodicReport a b -> DateSpan
|
periodicReportSpan :: PeriodicReport a b -> DateSpan
|
||||||
|
|||||||
@ -253,6 +253,7 @@ module Hledger.Cli.Commands.Balance (
|
|||||||
,tests_Balance
|
,tests_Balance
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Aeson (toJSON)
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
--import qualified Data.Map as Map
|
--import qualified Data.Map as Map
|
||||||
@ -318,6 +319,7 @@ balance opts@CliOpts{rawopts_=rawopts,reportopts_=ropts@ReportOpts{..}} j = do
|
|||||||
assrt = not $ ignore_assertions_ $ inputopts_ opts
|
assrt = not $ ignore_assertions_ $ inputopts_ opts
|
||||||
render = case fmt of
|
render = case fmt of
|
||||||
"txt" -> budgetReportAsText ropts
|
"txt" -> budgetReportAsText ropts
|
||||||
|
"json" -> (++"\n") . pshow . toJSON -- XXX pshow for pretty output, but it may generate some junk
|
||||||
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
||||||
writeOutput opts $ render budgetreport
|
writeOutput opts $ render budgetreport
|
||||||
|
|
||||||
@ -326,8 +328,9 @@ balance opts@CliOpts{rawopts_=rawopts,reportopts_=ropts@ReportOpts{..}} j = do
|
|||||||
let report = multiBalanceReport ropts (queryFromOpts d ropts) j
|
let report = multiBalanceReport ropts (queryFromOpts d ropts) j
|
||||||
render = case fmt of
|
render = case fmt of
|
||||||
"txt" -> multiBalanceReportAsText ropts
|
"txt" -> multiBalanceReportAsText ropts
|
||||||
"csv" -> (++ "\n") . printCSV . multiBalanceReportAsCsv ropts
|
"csv" -> (++"\n") . printCSV . multiBalanceReportAsCsv ropts
|
||||||
"html" -> (++ "\n") . TL.unpack . L.renderText . multiBalanceReportAsHtml ropts
|
"html" -> (++"\n") . TL.unpack . L.renderText . multiBalanceReportAsHtml ropts
|
||||||
|
"json" -> (++"\n") . pshow . toJSON -- XXX pshow for pretty output, but it may generate some junk
|
||||||
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
||||||
writeOutput opts $ render report
|
writeOutput opts $ render report
|
||||||
|
|
||||||
@ -342,6 +345,7 @@ balance opts@CliOpts{rawopts_=rawopts,reportopts_=ropts@ReportOpts{..}} j = do
|
|||||||
render = case fmt of
|
render = case fmt of
|
||||||
"txt" -> balanceReportAsText
|
"txt" -> balanceReportAsText
|
||||||
"csv" -> \ropts r -> (++ "\n") $ printCSV $ balanceReportAsCsv ropts r
|
"csv" -> \ropts r -> (++ "\n") $ printCSV $ balanceReportAsCsv ropts r
|
||||||
|
"json" -> const $ (++"\n") . pshow . toJSON -- XXX pshow for pretty output, but it may generate some junk
|
||||||
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
||||||
writeOutput opts $ render ropts report
|
writeOutput opts $ render ropts report
|
||||||
|
|
||||||
|
|||||||
@ -511,5 +511,8 @@ Budget performance in 2019/01:
|
|||||||
|
|
||||||
### Output format
|
### Output format
|
||||||
|
|
||||||
The balance command supports [output destination](hledger.html#output-destination) and [output format](hledger.html#output-format) selection.
|
This command also supports the
|
||||||
|
[output destination](hledger.html#output-destination) and
|
||||||
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, (multicolumn non-budget reports only) `html`, and (experimental) `json`.
|
||||||
|
|||||||
@ -43,6 +43,8 @@ dates (and `-T/--row-total`, since summing end balances generally does not make
|
|||||||
Instead of absolute values [percentages](#percentages) can be displayed
|
Instead of absolute values [percentages](#percentages) can be displayed
|
||||||
with `-%`.
|
with `-%`.
|
||||||
|
|
||||||
This command also supports
|
This command also supports the
|
||||||
[output destination](hledger.html#output-destination) and
|
[output destination](hledger.html#output-destination) and
|
||||||
[output format](hledger.html#output-format) selection.
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, `html`, and (experimental) `json`.
|
||||||
|
|||||||
@ -30,3 +30,10 @@ Total:
|
|||||||
--------------------
|
--------------------
|
||||||
0
|
0
|
||||||
```
|
```
|
||||||
|
|
||||||
|
|
||||||
|
This command also supports the
|
||||||
|
[output destination](hledger.html#output-destination) and
|
||||||
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, `html`, and (experimental) `json`.
|
||||||
|
|||||||
@ -34,6 +34,8 @@ you can alter the report mode with `--change`/`--cumulative`/`--historical`.
|
|||||||
Instead of absolute values [percentages](#percentages) can be displayed
|
Instead of absolute values [percentages](#percentages) can be displayed
|
||||||
with `-%`.
|
with `-%`.
|
||||||
|
|
||||||
This command also supports
|
This command also supports the
|
||||||
[output destination](hledger.html#output-destination) and
|
[output destination](hledger.html#output-destination) and
|
||||||
[output format](hledger.html#output-format) selection.
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, `html`, and (experimental) `json`.
|
||||||
|
|||||||
@ -45,6 +45,8 @@ you can alter the report mode with `--change`/`--cumulative`/`--historical`.
|
|||||||
Instead of absolute values [percentages](#percentages) can be displayed
|
Instead of absolute values [percentages](#percentages) can be displayed
|
||||||
with `-%`.
|
with `-%`.
|
||||||
|
|
||||||
This command also supports
|
This command also supports the
|
||||||
[output destination](hledger.html#output-destination) and
|
[output destination](hledger.html#output-destination) and
|
||||||
[output format](hledger.html#output-format) selection.
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, `html`, and (experimental) `json`.
|
||||||
|
|||||||
@ -15,6 +15,7 @@ module Hledger.Cli.Commands.Print (
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
import Data.Aeson (toJSON)
|
||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
@ -56,6 +57,7 @@ printEntries opts@CliOpts{reportopts_=ropts} j = do
|
|||||||
render = case fmt of
|
render = case fmt of
|
||||||
"txt" -> entriesReportAsText opts
|
"txt" -> entriesReportAsText opts
|
||||||
"csv" -> (++"\n") . printCSV . entriesReportAsCsv
|
"csv" -> (++"\n") . printCSV . entriesReportAsCsv
|
||||||
|
"json" -> (++"\n") . pshow . toJSON -- XXX pshow for pretty output, but it may generate some junk
|
||||||
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
_ -> const $ error' $ unsupportedOutputFormatError fmt
|
||||||
writeOutput opts $ render $ entriesReport ropts q j
|
writeOutput opts $ render $ entriesReport ropts q j
|
||||||
|
|
||||||
|
|||||||
@ -71,7 +71,12 @@ This assumes that transactions added to FILE always have same or increasing date
|
|||||||
and that transactions on the same day do not get reordered.
|
and that transactions on the same day do not get reordered.
|
||||||
See also the [import](#import) command.
|
See also the [import](#import) command.
|
||||||
|
|
||||||
This command also supports [output destination](hledger.html#output-destination) and [output format](hledger.html#output-format) selection.
|
This command also supports the
|
||||||
|
[output destination](hledger.html#output-destination) and
|
||||||
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, and (experimental) `json`.
|
||||||
|
|
||||||
Here's an example of print's CSV output:
|
Here's an example of print's CSV output:
|
||||||
|
|
||||||
```shell
|
```shell
|
||||||
|
|||||||
@ -18,6 +18,7 @@ module Hledger.Cli.Commands.Register (
|
|||||||
,tests_Register
|
,tests_Register
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Aeson (toJSON)
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
-- import Data.Text (Text)
|
-- import Data.Text (Text)
|
||||||
@ -60,6 +61,7 @@ register opts@CliOpts{reportopts_=ropts} j = do
|
|||||||
let fmt = outputFormatFromOpts opts
|
let fmt = outputFormatFromOpts opts
|
||||||
render | fmt=="txt" = postingsReportAsText
|
render | fmt=="txt" = postingsReportAsText
|
||||||
| fmt=="csv" = const ((++"\n") . printCSV . postingsReportAsCsv)
|
| fmt=="csv" = const ((++"\n") . printCSV . postingsReportAsCsv)
|
||||||
|
| fmt=="json" = const ((++"\n") . pshow . toJSON) -- XXX pshow for pretty output, but it may generate some junk
|
||||||
| otherwise = const $ error' $ unsupportedOutputFormatError fmt
|
| otherwise = const $ error' $ unsupportedOutputFormatError fmt
|
||||||
writeOutput opts $ render opts $ postingsReport ropts (queryFromOpts d ropts) j
|
writeOutput opts $ render opts $ postingsReport ropts (queryFromOpts d ropts) j
|
||||||
|
|
||||||
|
|||||||
@ -117,7 +117,9 @@ $ hledger reg -w 100,40 # set overall width 100, description width 40
|
|||||||
$ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40
|
$ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40
|
||||||
```
|
```
|
||||||
|
|
||||||
This command also supports
|
This command also supports the
|
||||||
[output destination](hledger.html#output-destination) and
|
[output destination](hledger.html#output-destination) and
|
||||||
[output format](hledger.html#output-format) selection.
|
[output format](hledger.html#output-format) options
|
||||||
|
The output formats supported are
|
||||||
|
`txt`, `csv`, and (experimental) `json`.
|
||||||
|
|
||||||
|
|||||||
@ -13,6 +13,7 @@ module Hledger.Cli.CompoundBalanceCommand (
|
|||||||
,compoundBalanceCommand
|
,compoundBalanceCommand
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Aeson (toJSON)
|
||||||
import Data.List (foldl')
|
import Data.List (foldl')
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import qualified Data.Text as TS
|
import qualified Data.Text as TS
|
||||||
@ -238,7 +239,8 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportopts_=r
|
|||||||
case fmt of
|
case fmt of
|
||||||
"txt" -> compoundBalanceReportAsText ropts' cbr
|
"txt" -> compoundBalanceReportAsText ropts' cbr
|
||||||
"csv" -> printCSV (compoundBalanceReportAsCsv ropts cbr) ++ "\n"
|
"csv" -> printCSV (compoundBalanceReportAsCsv ropts cbr) ++ "\n"
|
||||||
"html" -> (++ "\n") $ TL.unpack $ L.renderText $ compoundBalanceReportAsHtml ropts cbr
|
"html" -> (++"\n") $ TL.unpack $ L.renderText $ compoundBalanceReportAsHtml ropts cbr
|
||||||
|
"json" -> (++"\n") $ pshow $ toJSON cbr -- XXX pshow for pretty output, but it may generate some junk
|
||||||
_ -> error' $ unsupportedOutputFormatError fmt
|
_ -> error' $ unsupportedOutputFormatError fmt
|
||||||
|
|
||||||
-- | Summarise one or more (inclusive) end dates, in a way that's
|
-- | Summarise one or more (inclusive) end dates, in a way that's
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user