mirror of
https://github.com/simonmichael/hledger.git
synced 2024-11-08 07:09:28 +03:00
gather match functions in one place
This commit is contained in:
parent
83d36dae63
commit
47cf7c3eb6
@ -99,3 +99,78 @@ elideAccountName width s =
|
||||
| (length $ accountNameFromComponents $ done++ss) <= width = done++ss
|
||||
| length ss > 1 = elideparts width (done++[take 2 $ head ss]) (tail ss)
|
||||
| otherwise = done++ss
|
||||
|
||||
|
||||
-- -- | Check if a set of ledger account/description patterns matches the
|
||||
-- -- given account name or entry description. Patterns are case-insensitive
|
||||
-- -- regular expression strings; those beginning with - are anti-patterns.
|
||||
-- --
|
||||
-- -- Call with forbalancereport=True to mimic ledger's balance report
|
||||
-- -- matching. Account patterns usually match the full account name, but in
|
||||
-- -- balance reports when the pattern does not contain : and is not an
|
||||
-- -- anti-pattern, it matches only the leaf name.
|
||||
-- matchpats :: Bool -> [String] -> String -> Bool
|
||||
-- matchpats forbalancereport pats str =
|
||||
-- (null positives || any ismatch positives) && (null negatives || not (any ismatch negatives))
|
||||
-- where
|
||||
-- isnegative = (== negativepatternchar) . head
|
||||
-- (negatives,positives) = partition isnegative pats
|
||||
-- ismatch pat = containsRegex (mkRegexWithOpts pat' True True) matchee
|
||||
-- where
|
||||
-- pat' = if isnegative pat then drop 1 pat else pat
|
||||
-- matchee = if forbalancereport && not (':' `elem` pat) && not (isnegative pat)
|
||||
-- then accountLeafName str
|
||||
-- else str
|
||||
|
||||
-- | Check if a set of ledger account/description patterns matches the
|
||||
-- given account name or entry description. Patterns are case-insensitive
|
||||
-- regular expression strings; those beginning with - are anti-patterns.
|
||||
matchpats :: [String] -> String -> Bool
|
||||
matchpats pats str =
|
||||
(null positives || any match positives) && (null negatives || not (any match negatives))
|
||||
where
|
||||
(negatives,positives) = partition isnegativepat pats
|
||||
match "" = True
|
||||
match pat = matchregex (abspat pat) str
|
||||
|
||||
-- | Similar to matchpats, but follows the special behaviour of ledger
|
||||
-- 2.6's balance command: positive patterns which do not contain : match
|
||||
-- the account leaf name, other patterns match the full account name.
|
||||
matchpats_balance :: [String] -> String -> Bool
|
||||
matchpats_balance pats str = match_positive_pats pats str && (not $ match_negative_pats pats str)
|
||||
-- (null positives || any match positives) && (null negatives || not (any match negatives))
|
||||
-- where
|
||||
-- (negatives,positives) = partition isnegativepat pats
|
||||
-- match "" = True
|
||||
-- match pat = matchregex (abspat pat) matchee
|
||||
-- where
|
||||
-- matchee = if not (':' `elem` pat) && not (isnegativepat pat)
|
||||
-- then accountLeafName str
|
||||
-- else str
|
||||
|
||||
-- | Do the positives in these patterns permit a match for this string ?
|
||||
match_positive_pats :: [String] -> String -> Bool
|
||||
match_positive_pats pats str = (null ps) || (any match ps)
|
||||
where
|
||||
ps = positivepats pats
|
||||
match "" = True
|
||||
match p = matchregex (abspat p) matchee
|
||||
where
|
||||
matchee | ':' `elem` p = str
|
||||
| otherwise = accountLeafName str
|
||||
|
||||
-- | Do the negatives in these patterns prevent a match for this string ?
|
||||
match_negative_pats :: [String] -> String -> Bool
|
||||
match_negative_pats pats str = (not $ null ns) && (any match ns)
|
||||
where
|
||||
ns = map abspat $ negativepats pats
|
||||
match "" = True
|
||||
match p = matchregex (abspat p) str
|
||||
|
||||
negativepatternchar = '-'
|
||||
isnegativepat pat = (== [negativepatternchar]) $ take 1 pat
|
||||
abspat pat = if isnegativepat pat then drop 1 pat else pat
|
||||
positivepats = filter (not . isnegativepat)
|
||||
negativepats = filter isnegativepat
|
||||
matchregex pat str = containsRegex (mkRegexWithOpts pat True True) str
|
||||
|
||||
|
@ -65,10 +65,8 @@ topAccounts :: Ledger -> [Account]
|
||||
topAccounts l = map root $ branches $ ledgerAccountTree 9999 l
|
||||
|
||||
-- | Accounts in ledger whose name matches the pattern, in tree order.
|
||||
-- We apply ledger's special rules for balance report account matching
|
||||
-- (see 'matchLedgerPatterns').
|
||||
accountsMatching :: [String] -> Ledger -> [Account]
|
||||
accountsMatching pats l = filter (matchLedgerPatterns True pats . aname) $ accounts l
|
||||
accountsMatching pats l = filter (matchpats pats . aname) $ accounts l
|
||||
|
||||
-- | List a ledger account's immediate subaccounts
|
||||
subAccounts :: Ledger -> Account -> [Account]
|
||||
|
@ -17,8 +17,6 @@ import Ledger.Transaction
|
||||
import Ledger.RawTransaction
|
||||
|
||||
|
||||
negativepatternchar = '-'
|
||||
|
||||
instance Show RawLedger where
|
||||
show l = printf "RawLedger with %d entries, %d accounts: %s"
|
||||
((length $ entries l) +
|
||||
@ -56,7 +54,7 @@ filterRawLedger begin end pats clearedonly realonly =
|
||||
filterRawLedgerEntriesByDescription :: [String] -> RawLedger -> RawLedger
|
||||
filterRawLedgerEntriesByDescription pats (RawLedger ms ps es f) =
|
||||
RawLedger ms ps (filter matchdesc es) f
|
||||
where matchdesc = matchLedgerPatterns False pats . edescription
|
||||
where matchdesc = matchpats pats . edescription
|
||||
|
||||
-- | Keep only entries which fall between begin and end dates.
|
||||
-- We include entries on the begin date and exclude entries on the end
|
||||
@ -85,27 +83,6 @@ filterRawLedgerTransactionsByRealness True (RawLedger ms ps es f) =
|
||||
RawLedger ms ps (map filtertxns es) f
|
||||
where filtertxns e@Entry{etransactions=ts} = e{etransactions=filter isReal ts}
|
||||
|
||||
-- | Check if a set of ledger account/description patterns matches the
|
||||
-- given account name or entry description. Patterns are case-insensitive
|
||||
-- regular expression strings; those beginning with - are anti-patterns.
|
||||
--
|
||||
-- Call with forbalancereport=True to mimic ledger's balance report
|
||||
-- matching. Account patterns usually match the full account name, but in
|
||||
-- balance reports when the pattern does not contain : and is not an
|
||||
-- anti-pattern, it matches only the leaf name.
|
||||
matchLedgerPatterns :: Bool -> [String] -> String -> Bool
|
||||
matchLedgerPatterns forbalancereport pats str =
|
||||
(null positives || any ismatch positives) && (null negatives || not (any ismatch negatives))
|
||||
where
|
||||
isnegative = (== negativepatternchar) . head
|
||||
(negatives,positives) = partition isnegative pats
|
||||
ismatch pat = containsRegex (mkRegexWithOpts pat' True True) matchee
|
||||
where
|
||||
pat' = if isnegative pat then drop 1 pat else pat
|
||||
matchee = if forbalancereport && not (':' `elem` pat) && not (isnegative pat)
|
||||
then accountLeafName str
|
||||
else str
|
||||
|
||||
-- | Give all a ledger's amounts their canonical display settings. That
|
||||
-- is, in each commodity all amounts will use the display settings of the
|
||||
-- first amount detected, and the greatest precision of all amounts
|
||||
|
@ -3,7 +3,7 @@ where
|
||||
import System
|
||||
import System.Console.GetOpt
|
||||
import System.Directory
|
||||
import Ledger.RawLedger (negativepatternchar)
|
||||
import Ledger.AccountName (negativepatternchar)
|
||||
|
||||
usagehdr = "Usage: hledger [OPTS] balance|print|register [ACCTPATS] [-- DESCPATS]\n\nOptions"++warning++":"
|
||||
warning = if negativepatternchar=='-' then " (must appear before command)" else " (can appear anywhere)"
|
||||
|
@ -29,7 +29,7 @@ showRegisterReport :: [Opt] -> [String] -> Ledger -> String
|
||||
showRegisterReport opts args l = showtxns ts nulltxn nullamt
|
||||
where
|
||||
ts = filter matchtxn $ ledgerTransactions l
|
||||
matchtxn Transaction{account=a} = matchLedgerPatterns False apats a
|
||||
matchtxn Transaction{account=a} = matchpats apats a
|
||||
apats = fst $ parseAccountDescriptionArgs args
|
||||
|
||||
-- show transactions, one per line, with a running balance
|
||||
|
50
Utils.hs
50
Utils.hs
@ -41,53 +41,3 @@ myledger = do
|
||||
myaccount :: AccountName -> IO Account
|
||||
myaccount a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accountmap)
|
||||
|
||||
-- | Check if a set of ledger account/description patterns matches the
|
||||
-- given account name or entry description. Patterns are case-insensitive
|
||||
-- regular expression strings; those beginning with - are anti-patterns.
|
||||
matchpats :: [String] -> String -> Bool
|
||||
matchpats pats str =
|
||||
(null positives || any match positives) && (null negatives || not (any match negatives))
|
||||
where
|
||||
(negatives,positives) = partition isnegativepat pats
|
||||
match "" = True
|
||||
match pat = matchregex (abspat pat) str
|
||||
|
||||
-- | Similar to matchpats, but follows the special behaviour of ledger
|
||||
-- 2.6's balance command: positive patterns which do not contain : match
|
||||
-- the account leaf name, other patterns match the full account name.
|
||||
matchpats_balance :: [String] -> String -> Bool
|
||||
matchpats_balance pats str = match_positive_pats pats str && (not $ match_negative_pats pats str)
|
||||
-- (null positives || any match positives) && (null negatives || not (any match negatives))
|
||||
-- where
|
||||
-- (negatives,positives) = partition isnegativepat pats
|
||||
-- match "" = True
|
||||
-- match pat = matchregex (abspat pat) matchee
|
||||
-- where
|
||||
-- matchee = if not (':' `elem` pat) && not (isnegativepat pat)
|
||||
-- then accountLeafName str
|
||||
-- else str
|
||||
|
||||
-- | Do the positives in these patterns permit a match for this string ?
|
||||
match_positive_pats :: [String] -> String -> Bool
|
||||
match_positive_pats pats str = (null ps) || (any match ps)
|
||||
where
|
||||
ps = positivepats pats
|
||||
match "" = True
|
||||
match p = matchregex (abspat p) matchee
|
||||
where
|
||||
matchee | ':' `elem` p = str
|
||||
| otherwise = accountLeafName str
|
||||
|
||||
-- | Do the negatives in these patterns prevent a match for this string ?
|
||||
match_negative_pats :: [String] -> String -> Bool
|
||||
match_negative_pats pats str = (not $ null ns) && (any match ns)
|
||||
where
|
||||
ns = map abspat $ negativepats pats
|
||||
match "" = True
|
||||
match p = matchregex (abspat p) str
|
||||
|
||||
matchregex pat str = containsRegex (mkRegexWithOpts pat True True) str
|
||||
isnegativepat pat = (== [Ledger.negativepatternchar]) $ take 1 pat
|
||||
abspat pat = if isnegativepat pat then drop 1 pat else pat
|
||||
positivepats = filter (not . isnegativepat)
|
||||
negativepats = filter isnegativepat
|
||||
|
Loading…
Reference in New Issue
Block a user