--output -> --output-file/-o & --output-format/-O, refactor

Use two options and less surprising behaviour. Notes:
* a recognised suffix on the output file name can set the format
* but --output-format always wins
* -o - means stdout
* currently these are command-specific options on balance, print, register
* later, --output-file should become a global option
* and --output-format should be available at least on all commands which
  support multiple formats. Each command may support a different set of
  output formats, which should be listed in its command line help.
This commit is contained in:
Simon Michael 2014-10-21 17:14:37 -07:00
parent 827aaad08e
commit 9416d12d8a
5 changed files with 66 additions and 48 deletions

View File

@ -247,7 +247,6 @@ import Data.Maybe
-- import System.Console.CmdArgs -- import System.Console.CmdArgs
import System.Console.CmdArgs.Explicit as C import System.Console.CmdArgs.Explicit as C
-- import System.Console.CmdArgs.Text -- import System.Console.CmdArgs.Text
import System.FilePath
import Text.CSV import Text.CSV
import Test.HUnit import Test.HUnit
import Text.Printf (printf) import Text.Printf (printf)
@ -259,6 +258,7 @@ import Prelude hiding (putStr)
import Hledger.Utils.UTF8IOCompat (putStr) import Hledger.Utils.UTF8IOCompat (putStr)
import Hledger.Data.OutputFormat import Hledger.Data.OutputFormat
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Cli.Utils
-- | Command line options for this command. -- | Command line options for this command.
@ -274,8 +274,8 @@ balancemode = (defCommandMode $ ["balance"] ++ aliases) { -- also accept but don
,flagNone ["no-total"] (\opts -> setboolopt "no-total" opts) "don't show the final total" ,flagNone ["no-total"] (\opts -> setboolopt "no-total" opts) "don't show the final total"
,flagNone ["cumulative"] (\opts -> setboolopt "cumulative" opts) "multicolumn mode: show accumulated ending balances" ,flagNone ["cumulative"] (\opts -> setboolopt "cumulative" opts) "multicolumn mode: show accumulated ending balances"
,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) "multicolumn mode: show historical ending balances" ,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) "multicolumn mode: show historical ending balances"
,flagReq ["output","o"] (\s opts -> Right $ setopt "output" s opts) "[FILE][.FMT]" "write output to FILE (- or nothing means stdout). With a recognised FMT suffix, write that format (txt, csv)."
] ]
++ outputflags
,groupHidden = [] ,groupHidden = []
,groupNamed = [generalflagsgroup1] ,groupNamed = [generalflagsgroup1]
} }
@ -289,28 +289,22 @@ balance opts@CliOpts{reportopts_=ropts} j = do
case lineFormatFromOpts ropts of case lineFormatFromOpts ropts of
Left err -> putStr $ unlines [err] Left err -> putStr $ unlines [err]
Right _ -> do Right _ -> do
(path, ext) <- outputFilePathAndExtensionFromOpts opts let fmt = outputFormatFromOpts opts
let filename = fst $ splitExtension $ snd $ splitFileName path
case intervalFromOpts ropts of case intervalFromOpts ropts of
NoInterval -> do NoInterval -> do
let render | ext=="csv" = \_ r -> printCSV (balanceReportAsCsv ropts r) ++ "\n" let render | fmt=="csv" = \_ r -> printCSV (balanceReportAsCsv ropts r) ++ "\n"
| otherwise = \ropts r -> unlines $ balanceReportAsText ropts r | otherwise = \ropts r -> unlines $ balanceReportAsText ropts r
write | filename `elem` ["","-"] && ext `elem` ["","csv","txt"] = putStr writeOutput opts $ render ropts $ balanceReport ropts (queryFromOpts d ropts) j
| otherwise = writeFile path
write $ render ropts $ balanceReport ropts (queryFromOpts d ropts) j
_ -> _ ->
if ext=="csv" if fmt=="csv"
then error' "Sorry, CSV output with a report period is not supported yet" then error' "Sorry, CSV output with a report period is not supported yet"
else do else do
let render = case balancetype_ ropts of let render = case balancetype_ ropts of
PeriodBalance -> periodBalanceReportAsText PeriodBalance -> periodBalanceReportAsText
CumulativeBalance -> cumulativeBalanceReportAsText CumulativeBalance -> cumulativeBalanceReportAsText
HistoricalBalance -> historicalBalanceReportAsText HistoricalBalance -> historicalBalanceReportAsText
write | filename `elem` ["","-"] && ext `elem` ["","txt"] = putStr . unlines writeOutput opts $ unlines $ render ropts $ multiBalanceReport ropts (queryFromOpts d ropts) j
| otherwise = writeFile path . unlines
write $ render ropts $ multiBalanceReport ropts (queryFromOpts d ropts) j
-- | Render a single-column balance report as CSV. -- | Render a single-column balance report as CSV.
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV

View File

@ -13,6 +13,7 @@ module Hledger.Cli.Options (
detailedversionflag, detailedversionflag,
inputflags, inputflags,
reportflags, reportflags,
outputflags,
generalflagsgroup1, generalflagsgroup1,
generalflagsgroup2, generalflagsgroup2,
generalflagsgroup3, generalflagsgroup3,
@ -37,7 +38,8 @@ module Hledger.Cli.Options (
aliasesFromOpts, aliasesFromOpts,
journalFilePathFromOpts, journalFilePathFromOpts,
rulesFilePathFromOpts, rulesFilePathFromOpts,
outputFilePathAndExtensionFromOpts, outputFileFromOpts,
outputFormatFromOpts,
-- | For register: -- | For register:
OutputWidth(..), OutputWidth(..),
Width(..), Width(..),
@ -122,6 +124,12 @@ reportflags = [
,flagNone ["cost","B"] (setboolopt "cost") "show amounts in their cost price's commodity" ,flagNone ["cost","B"] (setboolopt "cost") "show amounts in their cost price's commodity"
] ]
-- | Common output-related flags: --output-file, --output-format...
outputflags = [
flagReq ["output-file","o"] (\s opts -> Right $ setopt "output-file" s opts) "FILE[.FMT]" "write output to FILE instead of stdout. A recognised FMT suffix influences the format."
,flagReq ["output-format","O"] (\s opts -> Right $ setopt "output-format" s opts) "FMT" "select the output format. Supported formats: txt, csv."
]
argsFlag :: FlagHelp -> Arg RawOpts argsFlag :: FlagHelp -> Arg RawOpts
argsFlag desc = flagArg (\s opts -> Right $ setopt "args" s opts) desc argsFlag desc = flagArg (\s opts -> Right $ setopt "args" s opts) desc
@ -237,7 +245,8 @@ data CliOpts = CliOpts {
,command_ :: String ,command_ :: String
,file_ :: Maybe FilePath ,file_ :: Maybe FilePath
,rules_file_ :: Maybe FilePath ,rules_file_ :: Maybe FilePath
,output_ :: Maybe FilePath ,output_file_ :: Maybe FilePath
,output_format_ :: Maybe String
,alias_ :: [String] ,alias_ :: [String]
,ignore_assertions_ :: Bool ,ignore_assertions_ :: Bool
,debug_ :: Int -- ^ debug level, set by @--debug[=N]@. See also 'Hledger.Utils.debugLevel'. ,debug_ :: Int -- ^ debug level, set by @--debug[=N]@. See also 'Hledger.Utils.debugLevel'.
@ -261,6 +270,7 @@ defcliopts = CliOpts
def def
def def
def def
def
-- | Convert possibly encoded option values to regular unicode strings. -- | Convert possibly encoded option values to regular unicode strings.
decodeRawOpts :: RawOpts -> RawOpts decodeRawOpts :: RawOpts -> RawOpts
@ -277,7 +287,8 @@ rawOptsToCliOpts rawopts = do
,command_ = stringopt "command" rawopts ,command_ = stringopt "command" rawopts
,file_ = maybestringopt "file" rawopts ,file_ = maybestringopt "file" rawopts
,rules_file_ = maybestringopt "rules-file" rawopts ,rules_file_ = maybestringopt "rules-file" rawopts
,output_ = maybestringopt "output" rawopts ,output_file_ = maybestringopt "output-file" rawopts
,output_format_ = maybestringopt "output-format" rawopts
,alias_ = map stripquotes $ listofstringopt "alias" rawopts ,alias_ = map stripquotes $ listofstringopt "alias" rawopts
,debug_ = intopt "debug" rawopts ,debug_ = intopt "debug" rawopts
,ignore_assertions_ = boolopt "ignore-assertions" rawopts ,ignore_assertions_ = boolopt "ignore-assertions" rawopts
@ -347,15 +358,33 @@ journalFilePathFromOpts opts = do
expandPath d $ fromMaybe f $ file_ opts expandPath d $ fromMaybe f $ file_ opts
-- | Get the (tilde-expanded, absolute) output file path and file -- | Get the expanded, absolute output file path from options,
-- extension (without the dot) from options, or the defaults ("-",""). -- or the default (-, meaning stdout).
outputFilePathAndExtensionFromOpts :: CliOpts -> IO (String, String) outputFileFromOpts :: CliOpts -> IO FilePath
outputFilePathAndExtensionFromOpts opts = do outputFileFromOpts opts = do
d <- getCurrentDirectory d <- getCurrentDirectory
p <- expandPath d <$> fromMaybe "-" $ output_ opts case output_file_ opts of
let (_,ext) = splitExtension p Just p -> expandPath d p
ext' = dropWhile (=='.') ext Nothing -> return "-"
return (p,ext')
-- | Get the output format from the --output-format option,
-- otherwise from a recognised file extension in the --output-file option,
-- otherwise the default (txt).
outputFormatFromOpts :: CliOpts -> String
outputFormatFromOpts opts =
case output_format_ opts of
Just f -> f
Nothing ->
let mext = (snd . splitExtension . snd . splitFileName) <$> output_file_ opts
in case mext of
Just ext | ext `elem` formats -> ext
_ -> defaultformat
defaultformat = "txt"
formats =
[defaultformat] ++
["csv"
]
-- | Get the (tilde-expanded) rules file path from options, if any. -- | Get the (tilde-expanded) rules file path from options, if any.
rulesFilePathFromOpts :: CliOpts -> IO (Maybe FilePath) rulesFilePathFromOpts :: CliOpts -> IO (Maybe FilePath)

View File

@ -13,22 +13,18 @@ where
import Data.List import Data.List
import System.Console.CmdArgs.Explicit import System.Console.CmdArgs.Explicit
import System.FilePath
import Test.HUnit import Test.HUnit
import Text.CSV import Text.CSV
import Hledger import Hledger
import Prelude hiding (putStr)
import Hledger.Utils.UTF8IOCompat (putStr)
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Cli.Utils
printmode = (defCommandMode $ ["print"] ++ aliases) { printmode = (defCommandMode $ ["print"] ++ aliases) {
modeHelp = "show transaction entries" `withAliases` aliases modeHelp = "show transaction entries" `withAliases` aliases
,modeGroupFlags = Group { ,modeGroupFlags = Group {
groupUnnamed = [ groupUnnamed = outputflags
flagReq ["output","o"] (\s opts -> Right $ setopt "output" s opts) "[FILE][.FMT]" "write output to FILE (- or nothing means stdout). With a recognised FMT suffix, write that format (txt, csv)."
]
,groupHidden = [] ,groupHidden = []
,groupNamed = [generalflagsgroup1] ,groupNamed = [generalflagsgroup1]
} }
@ -40,14 +36,11 @@ print' :: CliOpts -> Journal -> IO ()
print' opts@CliOpts{reportopts_=ropts} j = do print' opts@CliOpts{reportopts_=ropts} j = do
d <- getCurrentDay d <- getCurrentDay
let q = queryFromOpts d ropts let q = queryFromOpts d ropts
(path, ext) <- outputFilePathAndExtensionFromOpts opts fmt = outputFormatFromOpts opts
let filename = fst $ splitExtension $ snd $ splitFileName path (render, ropts') = case fmt of
write | filename `elem` ["","-"] && ext `elem` ["","csv","txt"] = putStr "csv" -> ((++"\n") . printCSV . entriesReportAsCsv, ropts{flat_=True})
| otherwise = writeFile path _ -> (entriesReportAsText, ropts)
(render,ropts') | ext=="csv" = ((++"\n") . printCSV . entriesReportAsCsv, ropts{flat_=True}) writeOutput opts $ render $ entriesReport ropts' q j
| otherwise = (entriesReportAsText, ropts)
write $ render $ entriesReport ropts' q j
entriesReportAsText :: EntriesReport -> String entriesReportAsText :: EntriesReport -> String
entriesReportAsText items = concatMap showTransactionUnelided items entriesReportAsText items = concatMap showTransactionUnelided items

View File

@ -15,15 +15,13 @@ module Hledger.Cli.Register (
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import System.Console.CmdArgs.Explicit import System.Console.CmdArgs.Explicit
import System.FilePath
import Text.CSV import Text.CSV
import Test.HUnit import Test.HUnit
import Text.Printf import Text.Printf
import Hledger import Hledger
import Prelude hiding (putStr)
import Hledger.Utils.UTF8IOCompat (putStr)
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Cli.Utils
registermode = (defCommandMode $ ["register"] ++ aliases) { registermode = (defCommandMode $ ["register"] ++ aliases) {
@ -34,8 +32,8 @@ registermode = (defCommandMode $ ["register"] ++ aliases) {
,flagNone ["average","A"] (\opts -> setboolopt "average" opts) "show a running average instead of the running total (implies --empty)" ,flagNone ["average","A"] (\opts -> setboolopt "average" opts) "show a running average instead of the running total (implies --empty)"
,flagNone ["related","r"] (\opts -> setboolopt "related" opts) "show postings' siblings instead" ,flagNone ["related","r"] (\opts -> setboolopt "related" opts) "show postings' siblings instead"
,flagReq ["width","w"] (\s opts -> Right $ setopt "width" s opts) "N" "set output width (default: 80)" ,flagReq ["width","w"] (\s opts -> Right $ setopt "width" s opts) "N" "set output width (default: 80)"
,flagReq ["output","o"] (\s opts -> Right $ setopt "output" s opts) "[FILE][.FMT]" "write output to FILE (- or nothing means stdout). With a recognised FMT suffix, write that format (txt, csv)."
] ]
++ outputflags
,groupHidden = [] ,groupHidden = []
,groupNamed = [generalflagsgroup1] ,groupNamed = [generalflagsgroup1]
} }
@ -46,13 +44,10 @@ registermode = (defCommandMode $ ["register"] ++ aliases) {
register :: CliOpts -> Journal -> IO () register :: CliOpts -> Journal -> IO ()
register opts@CliOpts{reportopts_=ropts} j = do register opts@CliOpts{reportopts_=ropts} j = do
d <- getCurrentDay d <- getCurrentDay
(path, ext) <- outputFilePathAndExtensionFromOpts opts let fmt = outputFormatFromOpts opts
let filename = fst $ splitExtension $ snd $ splitFileName path render | fmt=="csv" = const ((++"\n") . printCSV . postingsReportAsCsv)
write | filename `elem` ["","-"] && ext `elem` ["","csv","txt"] = putStr
| otherwise = writeFile path
render | ext=="csv" = const ((++"\n") . printCSV . postingsReportAsCsv)
| otherwise = postingsReportAsText | otherwise = postingsReportAsText
write $ render opts $ postingsReport ropts (queryFromOpts d ropts) j writeOutput opts $ render opts $ postingsReport ropts (queryFromOpts d ropts) j
postingsReportAsCsv :: PostingsReport -> CSV postingsReportAsCsv :: PostingsReport -> CSV
postingsReportAsCsv (_,is) = postingsReportAsCsv (_,is) =

View File

@ -9,6 +9,7 @@ Hledger.Utils.
module Hledger.Cli.Utils module Hledger.Cli.Utils
( (
withJournalDo, withJournalDo,
writeOutput,
journalReload, journalReload,
journalReloadIfChanged, journalReloadIfChanged,
journalFileIsNewer, journalFileIsNewer,
@ -70,6 +71,12 @@ withJournalDo opts cmd = do
ej <- readJournalFile Nothing rulespath (not $ ignore_assertions_ opts) journalpath ej <- readJournalFile Nothing rulespath (not $ ignore_assertions_ opts) journalpath
either error' (cmd opts . journalApplyAliases (aliasesFromOpts opts)) ej either error' (cmd opts . journalApplyAliases (aliasesFromOpts opts)) ej
-- | Write some output to stdout or to a file selected by --output-file.
writeOutput :: CliOpts -> String -> IO ()
writeOutput opts s = do
f <- outputFileFromOpts opts
(if f == "-" then putStr else writeFile f) s
-- -- | Get a journal from the given string and options, or throw an error. -- -- | Get a journal from the given string and options, or throw an error.
-- readJournalWithOpts :: CliOpts -> String -> IO Journal -- readJournalWithOpts :: CliOpts -> String -> IO Journal
-- readJournalWithOpts opts s = readJournal Nothing Nothing Nothing s >>= either error' return -- readJournalWithOpts opts s = readJournal Nothing Nothing Nothing s >>= either error' return