feat:commodities,payees,tags: add --find mode, like accounts command
This improves consistency (in error messages too) and seems useful. Also sync the order of account's options/option docs.
This commit is contained in:
parent
102c972130
commit
25f04dd367
@ -81,8 +81,9 @@ module Hledger.Cli.CliOptions (
|
||||
|
||||
-- * Other utils
|
||||
topicForMode,
|
||||
UsedOrDeclared(..),
|
||||
usedOrDeclaredFromOpts,
|
||||
DeclarablesSelector(..),
|
||||
declarablesSelectorFromOpts,
|
||||
findMatchedByArgument,
|
||||
|
||||
-- -- * Convenience re-exports
|
||||
-- module Data.String.Here,
|
||||
@ -120,7 +121,8 @@ import Hledger
|
||||
import Hledger.Cli.DocFiles
|
||||
import Hledger.Cli.Version
|
||||
import Data.Time.Clock.POSIX (POSIXTime)
|
||||
import Data.List (isPrefixOf, isSuffixOf)
|
||||
import Data.List (find, isPrefixOf, isSuffixOf)
|
||||
import Data.Function ((&))
|
||||
|
||||
|
||||
-- | The name of this program's executable.
|
||||
@ -825,28 +827,49 @@ registerWidthsFromOpts CliOpts{width_=Just s} =
|
||||
eof
|
||||
return (totalwidth, descwidth)
|
||||
|
||||
-- A common choice for filtering lists of declarable things.
|
||||
data UsedOrDeclared
|
||||
-- Some common ways to select items from a list of declarable things.
|
||||
-- Used by the accounts, commodities, payees, tags commands, eg.
|
||||
data DeclarablesSelector
|
||||
= Used
|
||||
| Declared
|
||||
| Undeclared
|
||||
| Unused
|
||||
| Find
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- Get the flag of this kind from opts, or raise an error if there's more than one.
|
||||
usedOrDeclaredFromOpts :: CliOpts -> Maybe UsedOrDeclared
|
||||
usedOrDeclaredFromOpts CliOpts{rawopts_=rawopts} =
|
||||
declarablesSelectorFromOpts :: CliOpts -> Maybe DeclarablesSelector
|
||||
declarablesSelectorFromOpts CliOpts{rawopts_=rawopts} =
|
||||
case ( boolopt "used" rawopts
|
||||
, boolopt "declared" rawopts
|
||||
, boolopt "undeclared" rawopts
|
||||
, boolopt "unused" rawopts
|
||||
, boolopt "find" rawopts
|
||||
) of
|
||||
(False, False, False, False) -> Nothing
|
||||
(True, False, False, False) -> Just Used
|
||||
(False, True, False, False) -> Just Declared
|
||||
(False, False, True, False) -> Just Undeclared
|
||||
(False, False, False, True) -> Just Unused
|
||||
_ -> error' "please pick at most one of --used, --declared, --undeclared, --unused"
|
||||
(False, False, False, False, False) -> Nothing
|
||||
(True, False, False, False, False) -> Just Used
|
||||
(False, True, False, False, False) -> Just Declared
|
||||
(False, False, True, False, False) -> Just Undeclared
|
||||
(False, False, False, True, False) -> Just Unused
|
||||
(False, False, False, False, True ) -> Just Find
|
||||
_ -> error' "please pick at most one of --used, --declared, --undeclared, --unused, --find"
|
||||
|
||||
-- | A helper for the --find mode offered by commands like accounts, commodities, payees, tags (see also 'DeclarablesSelector').
|
||||
-- Interpret the first command argument found in rawopts as a case insensitive regular expression,
|
||||
-- then return the first of the provided items that it matches;
|
||||
-- or raise an error if there's no valid argument or no matched item.
|
||||
-- This function's second argument describes the items' type, for the error message.
|
||||
findMatchedByArgument :: RawOpts -> String -> [T.Text] -> T.Text
|
||||
findMatchedByArgument rawopts itemtype items =
|
||||
let
|
||||
arg = headDef err $ listofstringopt "args" rawopts
|
||||
where err = error' $ "With --find, please provide a " ++ itemtype ++ " name or\n" ++
|
||||
itemtype ++ " pattern (case-insensitive, infix, regexp) as first command argument."
|
||||
firstmatch = case toRegexCI $ T.pack arg of -- keep synced with aregister's matching
|
||||
Right re -> find (regexMatchText re)
|
||||
Left _ -> const Nothing
|
||||
in firstmatch items
|
||||
& fromMaybe (error' $ show arg ++ " did not match any " ++ itemtype ++ ".")
|
||||
|
||||
-- Other utils
|
||||
|
||||
|
||||
@ -22,10 +22,8 @@ module Hledger.Cli.Commands.Accounts (
|
||||
|
||||
import Control.Monad (forM_)
|
||||
import Data.List
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Text qualified as T
|
||||
import Data.Text.IO qualified as T
|
||||
import Safe (headDef)
|
||||
import System.Console.CmdArgs.Explicit as C
|
||||
|
||||
import Hledger
|
||||
@ -41,7 +39,6 @@ accountsmode = hledgerCommandMode
|
||||
,flagNone ["undeclared"] (setboolopt "undeclared") "list accounts used but not declared"
|
||||
,flagNone ["unused"] (setboolopt "unused") "list accounts declared but not used"
|
||||
,flagNone ["find"] (setboolopt "find") "list the first account matched by the first argument (a case-insensitive infix regexp)"
|
||||
|
||||
,flagNone ["directives"] (setboolopt "directives") "show as account directives, for use in journals"
|
||||
,flagNone ["positions"] (setboolopt "positions") "also show where accounts were declared"
|
||||
,flagNone ["types"] (setboolopt "types") "also show account types when known"
|
||||
@ -78,27 +75,16 @@ accounts opts@CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query,_r
|
||||
map fst $ jdeclaredaccounts j
|
||||
matchedundeclared = dbg5 "matchedundeclared" $ nub $ matchedused \\ matcheddeclared
|
||||
matchedunused = dbg5 "matchedunused" $ nub $ matcheddeclared \\ matchedused
|
||||
-- keep synced with aregister
|
||||
matchedacct = dbg5 "matchedacct" $
|
||||
fromMaybe (error' $ show apat ++ " did not match any account.") -- PARTIAL:
|
||||
. firstMatch $ journalAccountNamesDeclaredOrImplied j
|
||||
where
|
||||
firstMatch = case toRegexCI $ T.pack apat of
|
||||
Right re -> find (regexMatchText re)
|
||||
Left _ -> const Nothing
|
||||
apat = headDef
|
||||
(error' "With --find, please provide an account name or\naccount pattern (case-insensitive, infix, regexp) as first command argument.")
|
||||
$ listofstringopt "args" rawopts
|
||||
found = dbg5 "matchedacct" $ findMatchedByArgument rawopts "account" $ journalAccountNamesDeclaredOrImplied j
|
||||
matchedall = matcheddeclared ++ matchedused
|
||||
accts = dbg5 "accts to show" $
|
||||
case (usedOrDeclaredFromOpts opts, boolopt "find" rawopts) of
|
||||
(Nothing, False) -> matchedall
|
||||
(Nothing, True) -> [matchedacct]
|
||||
(Just Used, False) -> matchedused
|
||||
(Just Declared, False) -> matcheddeclared
|
||||
(Just Undeclared, False) -> matchedundeclared
|
||||
(Just Unused, False) -> matchedunused
|
||||
_ -> error' "please pick at most one of --used, --declared, --undeclared, --unused, --find"
|
||||
case declarablesSelectorFromOpts opts of
|
||||
Nothing -> matchedall
|
||||
Just Used -> matchedused
|
||||
Just Declared -> matcheddeclared
|
||||
Just Undeclared -> matchedundeclared
|
||||
Just Unused -> matchedunused
|
||||
Just Find -> [found]
|
||||
|
||||
-- 2. sort them by declaration order (then undeclared accounts alphabetically)
|
||||
-- within each group of siblings
|
||||
|
||||
@ -10,42 +10,39 @@ Flags:
|
||||
--unused list accounts declared but not used
|
||||
--find list the first account matched by the first
|
||||
argument (a case-insensitive infix regexp)
|
||||
--types also show account types when known
|
||||
--positions also show where accounts were declared
|
||||
--directives show as account directives, for use in journals
|
||||
--positions also show where accounts were declared
|
||||
--types also show account types when known
|
||||
-l --flat list/tree mode: show accounts as a flat list
|
||||
(default)
|
||||
-t --tree list/tree mode: show accounts as a tree
|
||||
--drop=N flat mode: omit N leading account name parts
|
||||
```
|
||||
|
||||
This command lists account names - all of them by default.
|
||||
or just the ones which have been used in transactions,
|
||||
or declared with `account` directives,
|
||||
or used but not declared,
|
||||
or declared but not used,
|
||||
or just the first account name matched by a pattern.
|
||||
This command lists account names -
|
||||
all of them by default,
|
||||
or just the ones which have been used in transactions (`-u/--used`),
|
||||
or declared with `account` directives (`-d/--declared`),
|
||||
or used but not declared (`--undeclared`),
|
||||
or declared but not used (`--unused`),
|
||||
or just the first one matched by a pattern (`--find`, returning a non-zero exit code if it fails).
|
||||
|
||||
You can add query arguments to select a subset of transactions or accounts.
|
||||
|
||||
It shows a flat list by default. With `--tree`, it uses indentation to show the account hierarchy.
|
||||
In flat mode you can add `--drop N` to omit the first few account name components.
|
||||
Account names can be depth-clipped with `depth:N` or `--depth N` or `-N`.
|
||||
|
||||
With `--types`, it also shows each account's type, if it's known.
|
||||
(See Declaring accounts > Account types.)
|
||||
|
||||
With `--positions`, it also shows the file and line number of each
|
||||
account's declaration, if any, and the account's overall declaration order;
|
||||
these may be useful when troubleshooting account display order.
|
||||
You can add [query arguments](#queries) to select a subset of transactions or accounts.
|
||||
|
||||
With `--directives`, it shows valid account directives which could be pasted into a journal file.
|
||||
This is useful together with `--undeclared` when updating your account declarations
|
||||
to satisfy `hledger check accounts`.
|
||||
|
||||
The `--find` flag can be used to look up a single account name, in the same way
|
||||
that the `aregister` command does. It returns the alphanumerically-first matched
|
||||
account name, or if none can be found, it fails with a non-zero exit code.
|
||||
With `--positions`, it also shows the file and line number of each
|
||||
account's declaration, if any, and the account's overall declaration order;
|
||||
these may be useful when troubleshooting account display order.
|
||||
|
||||
With `--types`, it also shows each account's type, if it's known.
|
||||
(See Declaring accounts > Account types.)
|
||||
|
||||
It shows a flat list by default. With `--tree`, it uses indentation to show the account hierarchy.
|
||||
In flat mode you can add `--drop N` to omit the first few account name components.
|
||||
Account names can be depth-clipped with `depth:N` or `--depth N` or `-N`.
|
||||
|
||||
Examples:
|
||||
|
||||
|
||||
@ -88,7 +88,7 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
||||
[] -> error' $ help <> ".\nPlease provide an account name or a (case-insensitive, infix, regexp) pattern."
|
||||
(a:as) -> return (a, map T.pack as)
|
||||
let
|
||||
-- keep synced with accounts --find
|
||||
-- keep synced with findMatchedByArgument's matching
|
||||
acct = fromMaybe (error' $ help <> ",\nbut " ++ show apat++" did not match any account.") -- PARTIAL:
|
||||
. firstMatch $ journalAccountNamesDeclaredOrImplied j
|
||||
firstMatch = case toRegexCI $ T.pack apat of
|
||||
|
||||
@ -30,16 +30,17 @@ commoditiesmode = hledgerCommandMode
|
||||
,flagNone ["declared"] (setboolopt "declared") "list commodities declared"
|
||||
,flagNone ["undeclared"] (setboolopt "undeclared") "list commodities used but not declared"
|
||||
,flagNone ["unused"] (setboolopt "unused") "list commodities declared but not used"
|
||||
,flagNone ["find"] (setboolopt "find") "list the first commodity matched by the first argument (a case-insensitive infix regexp)"
|
||||
]
|
||||
[generalflagsgroup2]
|
||||
confflags
|
||||
([], Just $ argsFlag "[QUERY..]")
|
||||
|
||||
commodities :: CliOpts -> Journal -> IO ()
|
||||
commodities opts@CliOpts{reportspec_ = ReportSpec{_rsQuery = query}} j = do
|
||||
commodities opts@CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query}} j = do
|
||||
let
|
||||
used = dbg5 "used" $
|
||||
S.toList $ journalCommoditiesFromPriceDirectives j <> journalCommoditiesFromTransactions j
|
||||
filt = filter (matchesCommodity query)
|
||||
used = dbg5 "used" $ S.toList $ journalCommoditiesFromPriceDirectives j <> journalCommoditiesFromTransactions j
|
||||
declared' = dbg5 "declared" $ M.keys $ jdeclaredcommodities j
|
||||
unused = dbg5 "unused" $ declared' \\ used
|
||||
undeclared = dbg5 "undeclared" $ used \\ declared'
|
||||
@ -48,11 +49,13 @@ commodities opts@CliOpts{reportspec_ = ReportSpec{_rsQuery = query}} j = do
|
||||
,map pdcommodity $ jpricedirectives j -- gets the first symbol from P directives
|
||||
,map acommodity (S.toList $ journalAmounts j) -- includes the second symbol from P directives
|
||||
]
|
||||
found = dbg5 "found" $ findMatchedByArgument rawopts "commodity" all'
|
||||
|
||||
mapM_ T.putStrLn $ filter (matchesCommodity query) $
|
||||
case usedOrDeclaredFromOpts opts of
|
||||
Nothing -> all'
|
||||
Just Used -> used
|
||||
Just Declared -> declared'
|
||||
Just Undeclared -> undeclared
|
||||
Just Unused -> unused
|
||||
mapM_ T.putStrLn $
|
||||
case declarablesSelectorFromOpts opts of
|
||||
Nothing -> filt all'
|
||||
Just Used -> filt used
|
||||
Just Declared -> filt declared'
|
||||
Just Undeclared -> filt undeclared
|
||||
Just Unused -> filt unused
|
||||
Just Find -> [found]
|
||||
|
||||
@ -8,12 +8,17 @@ Flags:
|
||||
--declared list commodities declared
|
||||
--undeclared list commodities used but not declared
|
||||
--unused list commodities declared but not used
|
||||
--find list the first commodity matched by the first
|
||||
argument (a case-insensitive infix regexp)
|
||||
```
|
||||
|
||||
This command lists commodity symbols/names - all of them by default,
|
||||
|
||||
This command lists commodity symbols/names -
|
||||
all of them by default,
|
||||
or just the ones which have been used in transactions or `P` directives,
|
||||
or declared with `commodity` directives,
|
||||
or used but not declared,
|
||||
or declared but not used.
|
||||
or declared but not used,
|
||||
or just the first one matched by a pattern (with `--find`, returning a non-zero exit code if it fails).
|
||||
|
||||
You can add cur: query arguments to further limit the commodities.
|
||||
You can add `cur:` [query arguments](#queries) to further limit the commodities.
|
||||
|
||||
@ -30,6 +30,7 @@ payeesmode = hledgerCommandMode
|
||||
,flagNone ["declared"] (setboolopt "declared") "list payees declared"
|
||||
,flagNone ["undeclared"] (setboolopt "undeclared") "list payees used but not declared"
|
||||
,flagNone ["unused"] (setboolopt "unused") "list payees declared but not used"
|
||||
,flagNone ["find"] (setboolopt "find") "list the first payee matched by the first argument (a case-insensitive infix regexp)"
|
||||
]
|
||||
cligeneralflagsgroups1
|
||||
hiddenflags
|
||||
@ -37,7 +38,7 @@ payeesmode = hledgerCommandMode
|
||||
|
||||
-- | The payees command.
|
||||
payees :: CliOpts -> Journal -> IO ()
|
||||
payees opts@CliOpts{reportspec_=ReportSpec{_rsQuery=query}} j = do
|
||||
payees opts@CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query}} j = do
|
||||
let
|
||||
-- XXX matchesPayeeWIP is currently an alias for matchesDescription, not sure if it matters
|
||||
matchedused = dbg5 "matchedused" $ nubSort $ map transactionPayee $ filter (matchesTransaction query) $ jtxns j
|
||||
@ -45,10 +46,13 @@ payees opts@CliOpts{reportspec_=ReportSpec{_rsQuery=query}} j = do
|
||||
matchedunused = dbg5 "matchedunused" $ nubSort $ matcheddeclared \\ matchedused
|
||||
matchedundeclared = dbg5 "matchedundeclared" $ nubSort $ matchedused \\ matcheddeclared
|
||||
matchedall = dbg5 "matchedall" $ nubSort $ matcheddeclared ++ matchedused
|
||||
mapM_ T.putStrLn $ case usedOrDeclaredFromOpts opts of
|
||||
found = dbg5 "found" $ findMatchedByArgument rawopts "payee" all'
|
||||
where all' = nubSort $ map transactionPayee (jtxns j) <> journalPayeesDeclared j
|
||||
mapM_ T.putStrLn $ case declarablesSelectorFromOpts opts of
|
||||
Nothing -> matchedall
|
||||
Just Used -> matchedused
|
||||
Just Declared -> matcheddeclared
|
||||
Just Undeclared -> matchedundeclared
|
||||
Just Unused -> matchedunused
|
||||
Just Find -> [found]
|
||||
|
||||
|
||||
@ -8,18 +8,22 @@ Flags:
|
||||
--declared list payees declared
|
||||
--undeclared list payees used but not declared
|
||||
--unused list payees declared but not used
|
||||
--find list the first payee matched by the first
|
||||
argument (a case-insensitive infix regexp)
|
||||
```
|
||||
|
||||
This command lists unique payee/payer names - all of them by default,
|
||||
This command lists unique payee/payer names -
|
||||
all of them by default,
|
||||
or just the ones which have been used in transaction descriptions,
|
||||
or declared with `payee` directives,
|
||||
or used but not declared,
|
||||
or declared but not used.
|
||||
or declared but not used,
|
||||
or just the first one matched by a pattern (with `--find`, returning a non-zero exit code if it fails).
|
||||
|
||||
The payee/payer name is the part of the transaction description before a | character
|
||||
(or if there is no |, the whole description).
|
||||
|
||||
You can add query arguments to select a subset of transactions or payees.
|
||||
You can add [query arguments](#queries) to select a subset of transactions or payees.
|
||||
|
||||
Example:
|
||||
```cli
|
||||
|
||||
@ -17,6 +17,9 @@ import System.Console.CmdArgs.Explicit
|
||||
|
||||
import Hledger
|
||||
import Hledger.Cli.CliOptions
|
||||
import Data.Function ((&))
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.List (find)
|
||||
|
||||
|
||||
tagsmode = hledgerCommandMode
|
||||
@ -26,6 +29,7 @@ tagsmode = hledgerCommandMode
|
||||
,flagNone ["declared"] (setboolopt "declared") "list tags declared"
|
||||
,flagNone ["undeclared"] (setboolopt "undeclared") "list tags used but not declared"
|
||||
,flagNone ["unused"] (setboolopt "unused") "list tags declared but not used"
|
||||
,flagNone ["find"] (setboolopt "find") "list the first tag whose name is matched by the first argument (a case-insensitive infix regexp)"
|
||||
,flagNone ["values"] (setboolopt "values") "list tag values instead of tag names"
|
||||
,flagNone ["parsed"] (setboolopt "parsed") "show them in the order they were parsed (mostly), including duplicates"
|
||||
]
|
||||
@ -57,21 +61,32 @@ tags opts@CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{_rsQuery=_q, _r
|
||||
then []
|
||||
else filter (matchesAccountExtra (journalAccountType j) (journalInheritedAccountTags j) q) $
|
||||
map fst $ jdeclaredaccounts j
|
||||
|
||||
-- bit of a mess.
|
||||
used = dbg5 "used" $ concatMap (journalAccountTags j) accts ++ concatMap transactionAllTags txns
|
||||
declared' = dbg5 "declared" $ filter (q `matchesTag`) $ map (,"") $ journalTagsDeclared j
|
||||
(usednames, declarednames) = (map fst used, map fst declared')
|
||||
unused = dbg5 "unused" $ filter (not . (`elem` usednames) . fst) declared'
|
||||
declared' = dbg5 "declared'" $ map (,"") $ journalTagsDeclared j
|
||||
filtereddeclared = dbg5 "filtereddeclared'" $ filter (q `matchesTag`) declared'
|
||||
(usednames, declarednames) = (map fst used, map fst filtereddeclared)
|
||||
unused = dbg5 "unused" $ filter (not . (`elem` usednames) . fst) filtereddeclared
|
||||
undeclared = dbg5 "undeclared" $ filter (not . (`elem` declarednames) . fst) used
|
||||
all' = dbg5 "all" $ declared' <> used
|
||||
all' = dbg5 "all''" $ filtereddeclared <> used
|
||||
found = dbg5 "found" $ foundtag
|
||||
where
|
||||
-- First find the name, then the first occurrence of that tag.
|
||||
-- So that --values and --parsed still work with --find (in some reasonably stable way).
|
||||
alltags = declared' <> used
|
||||
allnames = dbg5 "allnames" $ nubSort $ map fst alltags
|
||||
foundname = dbg5 "foundname" $ findMatchedByArgument rawopts "tag name" allnames
|
||||
foundtag = find ((==foundname).fst) alltags
|
||||
& fromMaybe (error' "tags: could not find a tag's first occurrence") -- PARTIAL: should not happen because allnames and alltags correspond
|
||||
|
||||
tags' =
|
||||
case usedOrDeclaredFromOpts opts of
|
||||
case declarablesSelectorFromOpts opts of
|
||||
Nothing -> all'
|
||||
Just Used -> used
|
||||
Just Declared -> declared'
|
||||
Just Undeclared -> undeclared
|
||||
Just Unused -> unused
|
||||
Just Find -> [found]
|
||||
|
||||
results =
|
||||
(if parsed then id else nubSort)
|
||||
|
||||
@ -2,7 +2,7 @@
|
||||
|
||||
List the tag names used or declared in the journal, or their values.
|
||||
<!-- This section has the same name as Journal > Tags;
|
||||
if reordering this and that, update all #tags[-1] links -->
|
||||
if changing their relative order, all #tags[-1] links need to be updated -->
|
||||
|
||||
```flags
|
||||
Flags:
|
||||
@ -10,22 +10,24 @@ Flags:
|
||||
--declared list tags declared
|
||||
--undeclared list tags used but not declared
|
||||
--unused list tags declared but not used
|
||||
--find list the first tag whose name is matched by the
|
||||
first argument (a case-insensitive infix regexp)
|
||||
--values list tag values instead of tag names
|
||||
--parsed show them in the order they were parsed (mostly),
|
||||
including duplicates
|
||||
```
|
||||
|
||||
This command lists tag names - all of them by default,
|
||||
This command lists tag names -
|
||||
all of them by default,
|
||||
or just the ones which have been used on transactions/postings/accounts,
|
||||
or declared with `tag` directives,
|
||||
or used but not declared,
|
||||
or declared but not used.
|
||||
or declared but not used,
|
||||
or just the first one matched by a pattern (with `--find`, returning a non-zero exit code if it fails).
|
||||
|
||||
You can add one TAGREGEX argument, to show only tags whose name is
|
||||
matched by this case-insensitive, infix-matching regular expression.
|
||||
|
||||
After that, you can add query arguments to filter the
|
||||
transactions, postings, or accounts providing tags.
|
||||
Note this command's non-standard first argument:
|
||||
it is a case-insensitive infix regular expression for matching tag names, which limits the tags shown.
|
||||
Any additional arguments are standard [query arguments](#queries), which limit the transactions, postings, or accounts providing tags.
|
||||
|
||||
With `--values`, the tags' unique non-empty values are listed instead.
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user