2009-09-22 16:22:44 +04:00
|
|
|
{-# LANGUAGE CPP #-}
|
2009-04-04 12:50:36 +04:00
|
|
|
{-|
|
|
|
|
Command-line options for the application.
|
|
|
|
-}
|
|
|
|
|
2008-10-10 05:53:39 +04:00
|
|
|
module Options
|
2007-02-10 20:36:50 +03:00
|
|
|
where
|
2007-01-30 12:07:12 +03:00
|
|
|
import System.Console.GetOpt
|
2009-01-23 05:04:31 +03:00
|
|
|
import System.Environment
|
2009-07-10 00:25:50 +04:00
|
|
|
import Ledger.IO (myLedgerPath,myTimelogPath)
|
2008-11-25 00:51:31 +03:00
|
|
|
import Ledger.Utils
|
2008-11-27 03:35:00 +03:00
|
|
|
import Ledger.Types
|
|
|
|
import Ledger.Dates
|
2009-05-15 00:44:06 +04:00
|
|
|
import Codec.Binary.UTF8.String (decodeString)
|
|
|
|
import Control.Monad (liftM)
|
2008-11-25 00:51:31 +03:00
|
|
|
|
2009-01-25 11:09:26 +03:00
|
|
|
progname = "hledger"
|
|
|
|
timeprogname = "hours"
|
2010-02-07 00:45:41 +03:00
|
|
|
#ifdef CHART
|
|
|
|
chartoutput = "hledger.png"
|
|
|
|
chartitems = 10
|
|
|
|
chartsize = "600x400"
|
|
|
|
#endif
|
2009-01-25 11:09:26 +03:00
|
|
|
|
2009-09-22 20:51:27 +04:00
|
|
|
usagehdr =
|
2009-04-09 04:24:34 +04:00
|
|
|
"Usage: hledger [OPTIONS] [COMMAND [PATTERNS]]\n" ++
|
|
|
|
" hours [OPTIONS] [COMMAND [PATTERNS]]\n" ++
|
2009-12-04 02:34:23 +03:00
|
|
|
" hledger convert CSVFILE\n" ++
|
2009-04-09 04:24:34 +04:00
|
|
|
"\n" ++
|
2009-05-15 16:11:56 +04:00
|
|
|
"hledger uses your ~/.ledger or $LEDGER file (or another specified with -f),\n" ++
|
|
|
|
"while hours uses your ~/.timelog or $TIMELOG file.\n" ++
|
2009-01-25 11:09:26 +03:00
|
|
|
"\n" ++
|
2009-04-02 11:22:04 +04:00
|
|
|
"COMMAND is one of (may be abbreviated):\n" ++
|
2009-04-10 07:10:58 +04:00
|
|
|
" add - prompt for new transactions and add them to the ledger\n" ++
|
|
|
|
" balance - show accounts, with balances\n" ++
|
2009-07-15 01:51:10 +04:00
|
|
|
" convert - read CSV bank data and display in ledger format\n" ++
|
|
|
|
" histogram - show a barchart of transactions per day or other interval\n" ++
|
2009-04-10 07:10:58 +04:00
|
|
|
" print - show transactions in ledger format\n" ++
|
|
|
|
" register - show transactions as a register with running balance\n" ++
|
2009-05-29 14:05:09 +04:00
|
|
|
" stats - show various statistics for a ledger\n" ++
|
2009-01-20 07:31:11 +03:00
|
|
|
#ifdef VTY
|
2009-07-15 01:51:10 +04:00
|
|
|
" ui - run a simple text-based UI\n" ++
|
2009-01-20 07:31:34 +03:00
|
|
|
#endif
|
2009-11-28 18:37:56 +03:00
|
|
|
#ifdef WEB
|
2009-07-15 01:51:10 +04:00
|
|
|
" web - run a simple web-based UI\n" ++
|
2009-09-27 02:53:54 +04:00
|
|
|
#endif
|
|
|
|
#ifdef CHART
|
|
|
|
" chart - generate balances pie chart\n" ++
|
2009-01-20 07:31:11 +03:00
|
|
|
#endif
|
2009-04-08 09:34:01 +04:00
|
|
|
" test - run self-tests\n" ++
|
2009-04-02 10:25:22 +04:00
|
|
|
"\n" ++
|
|
|
|
"PATTERNS are regular expressions which filter by account name.\n" ++
|
2009-04-10 04:25:28 +04:00
|
|
|
"Prefix with desc: to filter by transaction description instead.\n" ++
|
|
|
|
"Prefix with not: to negate a pattern. When using both, not: comes last.\n" ++
|
2009-01-25 11:09:26 +03:00
|
|
|
"\n" ++
|
2009-04-10 04:25:28 +04:00
|
|
|
"DATES can be y/m/d or ledger-style smart dates like \"last month\".\n" ++
|
2009-04-02 11:22:04 +04:00
|
|
|
"\n" ++
|
2009-02-27 06:56:26 +03:00
|
|
|
"Options:"
|
2009-09-22 20:51:27 +04:00
|
|
|
|
2009-04-10 04:25:28 +04:00
|
|
|
usageftr = ""
|
2008-11-26 08:21:44 +03:00
|
|
|
usage = usageInfo usagehdr options ++ usageftr
|
2007-02-16 12:00:17 +03:00
|
|
|
|
2008-10-08 21:24:59 +04:00
|
|
|
-- | Command-line options we accept.
|
|
|
|
options :: [OptDescr Opt]
|
|
|
|
options = [
|
2009-09-23 13:56:17 +04:00
|
|
|
Option "f" ["file"] (ReqArg File "FILE") "use a different ledger/timelog file; - means stdin"
|
|
|
|
,Option "b" ["begin"] (ReqArg Begin "DATE") "report on transactions on or after this date"
|
|
|
|
,Option "e" ["end"] (ReqArg End "DATE") "report on transactions before this date"
|
|
|
|
,Option "p" ["period"] (ReqArg Period "EXPR") ("report on transactions during the specified period\n" ++
|
2008-12-08 20:27:16 +03:00
|
|
|
"and/or with the specified reporting interval\n")
|
2009-09-23 13:56:17 +04:00
|
|
|
,Option "C" ["cleared"] (NoArg Cleared) "report only on cleared transactions"
|
|
|
|
,Option "U" ["uncleared"] (NoArg UnCleared) "report only on uncleared transactions"
|
|
|
|
,Option "B" ["cost","basis"] (NoArg CostBasis) "report cost of commodities"
|
2009-09-23 21:39:38 +04:00
|
|
|
,Option "" ["depth"] (ReqArg Depth "N") "hide accounts/transactions deeper than this"
|
2009-09-23 13:56:17 +04:00
|
|
|
,Option "d" ["display"] (ReqArg Display "EXPR") ("show only transactions matching EXPR (where\n" ++
|
2009-04-08 10:23:49 +04:00
|
|
|
"EXPR is 'dOP[DATE]' and OP is <, <=, =, >=, >)")
|
2009-09-23 21:39:38 +04:00
|
|
|
,Option "" ["effective"] (NoArg Effective) "use transactions' effective dates, if any"
|
2009-09-23 13:56:17 +04:00
|
|
|
,Option "E" ["empty"] (NoArg Empty) "show empty/zero things which are normally elided"
|
|
|
|
,Option "R" ["real"] (NoArg Real) "report only on real (non-virtual) transactions"
|
2009-09-23 21:39:38 +04:00
|
|
|
,Option "" ["no-total"] (NoArg NoTotal) "balance report: hide the final total"
|
2009-09-23 13:56:17 +04:00
|
|
|
-- ,Option "s" ["subtotal"] (NoArg SubTotal) "balance report: show subaccounts"
|
|
|
|
,Option "W" ["weekly"] (NoArg WeeklyOpt) "register report: show weekly summary"
|
|
|
|
,Option "M" ["monthly"] (NoArg MonthlyOpt) "register report: show monthly summary"
|
|
|
|
,Option "Q" ["quarterly"] (NoArg QuarterlyOpt) "register report: show quarterly summary"
|
|
|
|
,Option "Y" ["yearly"] (NoArg YearlyOpt) "register report: show yearly summary"
|
|
|
|
,Option "h" ["help"] (NoArg Help) "show this help"
|
|
|
|
,Option "V" ["version"] (NoArg Version) "show version information"
|
|
|
|
,Option "v" ["verbose"] (NoArg Verbose) "show verbose test output"
|
2009-09-23 21:39:38 +04:00
|
|
|
,Option "" ["binary-filename"] (NoArg BinaryFilename) "show the download filename for this hledger build"
|
|
|
|
,Option "" ["debug"] (NoArg Debug) "show extra debug output; implies verbose"
|
|
|
|
,Option "" ["debug-no-ui"] (NoArg DebugNoUI) "run ui commands with no output"
|
2009-09-27 02:53:54 +04:00
|
|
|
#ifdef CHART
|
2010-02-07 00:45:41 +03:00
|
|
|
,Option "o" ["output"] (ReqArg ChartOutput "FILE") ("chart: output filename (default: "++chartoutput++")")
|
|
|
|
,Option "" ["items"] (ReqArg ChartItems "N") ("chart: number of accounts to show (default: "++show chartitems++")")
|
|
|
|
,Option "" ["size"] (ReqArg ChartSize "WIDTHxHEIGHT") ("chart: image size (default: "++chartsize++")")
|
2009-09-27 02:53:54 +04:00
|
|
|
#endif
|
2008-10-08 21:24:59 +04:00
|
|
|
]
|
2007-02-09 04:23:12 +03:00
|
|
|
|
2008-10-08 21:24:59 +04:00
|
|
|
-- | An option value from a command-line flag.
|
|
|
|
data Opt =
|
2008-11-27 09:29:29 +03:00
|
|
|
File {value::String} |
|
|
|
|
Begin {value::String} |
|
|
|
|
End {value::String} |
|
|
|
|
Period {value::String} |
|
2008-10-16 13:04:44 +04:00
|
|
|
Cleared |
|
2009-04-03 15:45:56 +04:00
|
|
|
UnCleared |
|
2008-11-22 23:35:17 +03:00
|
|
|
CostBasis |
|
2008-11-27 09:29:29 +03:00
|
|
|
Depth {value::String} |
|
|
|
|
Display {value::String} |
|
2009-07-09 03:37:44 +04:00
|
|
|
Effective |
|
2008-11-22 12:39:58 +03:00
|
|
|
Empty |
|
2008-10-16 13:50:16 +04:00
|
|
|
Real |
|
2009-04-02 11:22:54 +04:00
|
|
|
NoTotal |
|
2008-10-17 20:58:09 +04:00
|
|
|
SubTotal |
|
2008-12-04 02:20:38 +03:00
|
|
|
WeeklyOpt |
|
|
|
|
MonthlyOpt |
|
2009-04-03 15:55:48 +04:00
|
|
|
QuarterlyOpt |
|
2008-12-04 02:20:38 +03:00
|
|
|
YearlyOpt |
|
2007-05-01 09:55:35 +04:00
|
|
|
Help |
|
2008-11-22 07:49:00 +03:00
|
|
|
Verbose |
|
2007-03-12 10:40:33 +03:00
|
|
|
Version
|
2009-06-05 06:07:38 +04:00
|
|
|
| BinaryFilename
|
2009-03-15 09:15:58 +03:00
|
|
|
| Debug
|
2008-12-08 20:27:16 +03:00
|
|
|
| DebugNoUI
|
2009-09-27 02:53:54 +04:00
|
|
|
#ifdef CHART
|
|
|
|
| ChartOutput {value::String}
|
2010-02-05 04:18:51 +03:00
|
|
|
| ChartItems {value::String}
|
2009-09-27 02:53:54 +04:00
|
|
|
| ChartSize {value::String}
|
|
|
|
#endif
|
2007-03-12 10:40:33 +03:00
|
|
|
deriving (Show,Eq)
|
2007-02-16 15:24:13 +03:00
|
|
|
|
2009-04-03 15:45:56 +04:00
|
|
|
-- these make me nervous
|
2008-12-04 02:20:38 +03:00
|
|
|
optsWithConstructor f opts = concatMap get opts
|
2009-09-23 13:45:39 +04:00
|
|
|
where get o = [o | f v == o] where v = value o
|
2008-12-04 02:20:38 +03:00
|
|
|
|
2009-04-03 15:45:56 +04:00
|
|
|
optsWithConstructors fs opts = concatMap get opts
|
2009-09-23 13:45:39 +04:00
|
|
|
where get o = [o | any (== o) fs]
|
2009-04-03 15:45:56 +04:00
|
|
|
|
2008-11-27 09:29:29 +03:00
|
|
|
optValuesForConstructor f opts = concatMap get opts
|
2009-09-23 13:45:39 +04:00
|
|
|
where get o = [v | f v == o] where v = value o
|
2008-10-10 05:36:21 +04:00
|
|
|
|
2008-12-04 02:20:38 +03:00
|
|
|
optValuesForConstructors fs opts = concatMap get opts
|
2009-09-23 13:45:39 +04:00
|
|
|
where get o = [v | any (\f -> f v == o) fs] where v = value o
|
2008-12-04 02:20:38 +03:00
|
|
|
|
2009-01-23 05:04:31 +03:00
|
|
|
-- | Parse the command-line arguments into options, command name, and
|
2009-04-09 04:24:34 +04:00
|
|
|
-- command arguments. Any dates in the options are converted to explicit
|
2009-05-15 16:11:56 +04:00
|
|
|
-- YYYY/MM/DD format based on the current time.
|
2008-10-08 21:24:59 +04:00
|
|
|
parseArguments :: IO ([Opt], String, [String])
|
2008-10-08 21:00:22 +04:00
|
|
|
parseArguments = do
|
2009-05-15 00:44:06 +04:00
|
|
|
args <- liftM (map decodeString) getArgs
|
2009-02-27 06:56:26 +03:00
|
|
|
let (os,as,es) = getOpt Permute options args
|
2009-05-15 16:11:56 +04:00
|
|
|
-- istimequery <- usingTimeProgramName
|
|
|
|
-- let os' = if istimequery then (Period "today"):os else os
|
2009-08-12 13:07:56 +04:00
|
|
|
os' <- fixOptDates os
|
2009-09-22 20:51:27 +04:00
|
|
|
let os'' = if Debug `elem` os' then Verbose:os' else os'
|
2009-04-09 04:24:34 +04:00
|
|
|
case (as,es) of
|
|
|
|
(cmd:args,[]) -> return (os'',cmd,args)
|
|
|
|
([],[]) -> return (os'',"",[])
|
|
|
|
(_,errs) -> ioError (userError (concat errs ++ usage))
|
2008-11-26 07:04:05 +03:00
|
|
|
|
2008-11-27 02:21:24 +03:00
|
|
|
-- | Convert any fuzzy dates within these option values to explicit ones,
|
|
|
|
-- based on today's date.
|
2008-11-27 03:35:00 +03:00
|
|
|
fixOptDates :: [Opt] -> IO [Opt]
|
|
|
|
fixOptDates opts = do
|
2009-01-24 22:48:37 +03:00
|
|
|
d <- getCurrentDay
|
|
|
|
return $ map (fixopt d) opts
|
2008-11-26 07:04:05 +03:00
|
|
|
where
|
2009-01-24 22:48:37 +03:00
|
|
|
fixopt d (Begin s) = Begin $ fixSmartDateStr d s
|
|
|
|
fixopt d (End s) = End $ fixSmartDateStr d s
|
|
|
|
fixopt d (Display s) = -- hacky
|
2008-11-27 02:21:24 +03:00
|
|
|
Display $ gsubRegexPRBy "\\[.+?\\]" fixbracketeddatestr s
|
2009-09-22 15:55:11 +04:00
|
|
|
where fixbracketeddatestr s = "[" ++ fixSmartDateStr d (init $ tail s) ++ "]"
|
2008-11-26 07:04:05 +03:00
|
|
|
fixopt _ o = o
|
|
|
|
|
2008-12-04 02:20:38 +03:00
|
|
|
-- | Figure out the overall date span we should report on, based on any
|
|
|
|
-- begin/end/period options provided. If there is a period option, the
|
|
|
|
-- others are ignored.
|
2008-11-27 09:29:29 +03:00
|
|
|
dateSpanFromOpts :: Day -> [Opt] -> DateSpan
|
2008-12-04 02:20:38 +03:00
|
|
|
dateSpanFromOpts refdate opts
|
2008-12-04 23:11:35 +03:00
|
|
|
| not $ null popts = snd $ parsePeriodExpr refdate $ last popts
|
|
|
|
| otherwise = DateSpan lastb laste
|
2007-03-12 10:40:33 +03:00
|
|
|
where
|
2008-12-04 02:20:38 +03:00
|
|
|
popts = optValuesForConstructor Period opts
|
|
|
|
bopts = optValuesForConstructor Begin opts
|
|
|
|
eopts = optValuesForConstructor End opts
|
2008-12-04 23:11:35 +03:00
|
|
|
lastb = listtomaybeday bopts
|
|
|
|
laste = listtomaybeday eopts
|
|
|
|
listtomaybeday vs = if null vs then Nothing else Just $ parse $ last vs
|
2008-12-04 02:20:38 +03:00
|
|
|
where parse = parsedate . fixSmartDateStr refdate
|
|
|
|
|
|
|
|
-- | Figure out the reporting interval, if any, specified by the options.
|
|
|
|
-- If there is a period option, the others are ignored.
|
|
|
|
intervalFromOpts :: [Opt] -> Interval
|
2009-06-05 13:44:20 +04:00
|
|
|
intervalFromOpts opts =
|
|
|
|
case (periodopts, intervalopts) of
|
|
|
|
((p:_), _) -> fst $ parsePeriodExpr d p where d = parsedate "0001/01/01" -- unused
|
|
|
|
(_, (WeeklyOpt:_)) -> Weekly
|
|
|
|
(_, (MonthlyOpt:_)) -> Monthly
|
|
|
|
(_, (QuarterlyOpt:_)) -> Quarterly
|
|
|
|
(_, (YearlyOpt:_)) -> Yearly
|
|
|
|
(_, _) -> NoInterval
|
2008-12-04 02:20:38 +03:00
|
|
|
where
|
2009-06-05 13:44:20 +04:00
|
|
|
periodopts = reverse $ optValuesForConstructor Period opts
|
|
|
|
intervalopts = reverse $ filter (`elem` [WeeklyOpt,MonthlyOpt,QuarterlyOpt,YearlyOpt]) opts
|
2008-10-08 21:00:22 +04:00
|
|
|
|
2009-03-15 14:09:49 +03:00
|
|
|
-- | Get the value of the (last) depth option, if any, otherwise a large number.
|
2009-12-21 08:23:07 +03:00
|
|
|
depthFromOpts :: [Opt] -> Maybe Int
|
|
|
|
depthFromOpts opts = listtomaybeint $ optValuesForConstructor Depth opts
|
2008-11-22 16:11:54 +03:00
|
|
|
where
|
2008-11-27 09:48:46 +03:00
|
|
|
listtomaybeint [] = Nothing
|
2008-12-04 23:11:35 +03:00
|
|
|
listtomaybeint vs = Just $ read $ last vs
|
2008-11-22 16:11:54 +03:00
|
|
|
|
2008-12-04 23:11:35 +03:00
|
|
|
-- | Get the value of the (last) display option, if any.
|
2009-12-21 08:23:07 +03:00
|
|
|
displayExprFromOpts :: [Opt] -> Maybe String
|
|
|
|
displayExprFromOpts opts = listtomaybe $ optValuesForConstructor Display opts
|
2008-11-25 00:51:31 +03:00
|
|
|
where
|
2008-11-27 09:48:46 +03:00
|
|
|
listtomaybe [] = Nothing
|
2008-12-04 23:11:35 +03:00
|
|
|
listtomaybe vs = Just $ last vs
|
2008-11-25 00:51:31 +03:00
|
|
|
|
2009-04-04 12:50:36 +04:00
|
|
|
-- | Get a maybe boolean representing the last cleared/uncleared option if any.
|
|
|
|
clearedValueFromOpts opts | null os = Nothing
|
|
|
|
| last os == Cleared = Just True
|
|
|
|
| otherwise = Just False
|
|
|
|
where os = optsWithConstructors [Cleared,UnCleared] opts
|
|
|
|
|
2009-01-23 05:04:31 +03:00
|
|
|
-- | Was the program invoked via the \"hours\" alias ?
|
|
|
|
usingTimeProgramName :: IO Bool
|
|
|
|
usingTimeProgramName = do
|
|
|
|
progname <- getProgName
|
|
|
|
return $ map toLower progname == timeprogname
|
|
|
|
|
2008-11-27 09:29:29 +03:00
|
|
|
-- | Get the ledger file path from options, an environment variable, or a default
|
|
|
|
ledgerFilePathFromOpts :: [Opt] -> IO String
|
|
|
|
ledgerFilePathFromOpts opts = do
|
2009-01-23 05:04:31 +03:00
|
|
|
istimequery <- usingTimeProgramName
|
2009-04-04 12:50:36 +04:00
|
|
|
f <- if istimequery then myTimelogPath else myLedgerPath
|
2009-09-22 20:51:27 +04:00
|
|
|
return $ last $ f : optValuesForConstructor File opts
|
2008-11-27 09:29:29 +03:00
|
|
|
|
2009-04-04 13:14:04 +04:00
|
|
|
-- | Gather filter pattern arguments into a list of account patterns and a
|
|
|
|
-- list of description patterns. We interpret pattern arguments as
|
2009-04-02 10:25:22 +04:00
|
|
|
-- follows: those prefixed with "desc:" are description patterns, all
|
2009-04-04 13:14:04 +04:00
|
|
|
-- others are account patterns; also patterns prefixed with "not:" are
|
2009-04-02 10:25:22 +04:00
|
|
|
-- negated. not: should come after desc: if both are used.
|
2009-04-04 13:14:04 +04:00
|
|
|
parsePatternArgs :: [String] -> ([String],[String])
|
|
|
|
parsePatternArgs args = (as, ds')
|
2009-04-02 10:25:22 +04:00
|
|
|
where
|
|
|
|
descprefix = "desc:"
|
|
|
|
(ds, as) = partition (descprefix `isPrefixOf`) args
|
|
|
|
ds' = map (drop (length descprefix)) ds
|
|
|
|
|
2009-07-10 00:25:50 +04:00
|
|
|
-- | Convert application options to the library's generic filter specification.
|
|
|
|
optsToFilterSpec :: [Opt] -> [String] -> LocalTime -> FilterSpec
|
|
|
|
optsToFilterSpec opts args t = FilterSpec {
|
|
|
|
datespan=dateSpanFromOpts (localDay t) opts
|
|
|
|
,cleared=clearedValueFromOpts opts
|
|
|
|
,real=Real `elem` opts
|
2009-12-21 08:23:07 +03:00
|
|
|
,empty=Empty `elem` opts
|
2009-07-10 00:25:50 +04:00
|
|
|
,costbasis=CostBasis `elem` opts
|
|
|
|
,acctpats=apats
|
|
|
|
,descpats=dpats
|
2009-09-23 13:29:31 +04:00
|
|
|
,whichdate = if Effective `elem` opts then EffectiveDate else ActualDate
|
2009-12-21 08:23:07 +03:00
|
|
|
,depth = depthFromOpts opts
|
2009-07-10 00:25:50 +04:00
|
|
|
}
|
|
|
|
where (apats,dpats) = parsePatternArgs args
|
2009-04-04 12:50:36 +04:00
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
-- currentLocalTimeFromOpts opts = listtomaybe $ optValuesForConstructor CurrentLocalTime opts
|
|
|
|
-- where
|
|
|
|
-- listtomaybe [] = Nothing
|
|
|
|
-- listtomaybe vs = Just $ last vs
|
|
|
|
|