change comm: to sym: and require a match on the whole symbol
This commit is contained in:
		
							parent
							
								
									957f57a07b
								
							
						
					
					
						commit
						060d1fdd1b
					
				| @ -953,8 +953,7 @@ A query term can be any of the following: | |||||||
| - `REGEX` - match account names by this regular expression | - `REGEX` - match account names by this regular expression | ||||||
| - `acct:REGEX` - same as above | - `acct:REGEX` - same as above | ||||||
| - `code:REGEX` - match by transaction code (eg check number) | - `code:REGEX` - match by transaction code (eg check number) | ||||||
| - `comm:REGEX` - match by commodity symbol | - `desc:REGEX` - match transaction descriptions | ||||||
| - `desc:REGEX` - match transaction descriptions by regular expression |  | ||||||
| - `date:PERIODEXPR` - match dates within the specified [period](#period-expressions) | - `date:PERIODEXPR` - match dates within the specified [period](#period-expressions) | ||||||
| - `date2:PERIODEXPR` - as above, but match secondary dates | - `date2:PERIODEXPR` - as above, but match secondary dates | ||||||
| - `tag:NAME[=REGEX]` - match by (exact, case sensitive) [tag](#tags) name, and optionally match the tag value by regular expression | - `tag:NAME[=REGEX]` - match by (exact, case sensitive) [tag](#tags) name, and optionally match the tag value by regular expression | ||||||
| @ -963,6 +962,7 @@ A query term can be any of the following: | |||||||
| - `real:1` or `real:0` - match real/virtual-ness | - `real:1` or `real:0` - match real/virtual-ness | ||||||
| - `empty:1` or `empty:0` - match if amount is/is not zero | - `empty:1` or `empty:0` - match if amount is/is not zero | ||||||
| - `amt:N` or `amt:=N`, `amt:<N`, `amt:>N` - match postings with a single-commodity amount equal to, less than, or greater than N. (Multi-commodity amounts are always matched.) | - `amt:N` or `amt:=N`, `amt:<N`, `amt:>N` - match postings with a single-commodity amount equal to, less than, or greater than N. (Multi-commodity amounts are always matched.) | ||||||
|  | - `sym:REGEX` - match (whole) commodity symbols | ||||||
| - `not:` before any of the above negates the match | - `not:` before any of the above negates the match | ||||||
| 
 | 
 | ||||||
| <!-- | <!-- | ||||||
|  | |||||||
							
								
								
									
										2
									
								
								NEWS.md
									
									
									
									
									
								
							
							
						
						
									
										2
									
								
								NEWS.md
									
									
									
									
									
								
							| @ -6,7 +6,7 @@ title: hledger news | |||||||
| 
 | 
 | ||||||
| ## unreleased | ## unreleased | ||||||
| 
 | 
 | ||||||
| - queries: `comm:REGEXP` matches commodity symbols which match REGEXP | - queries: `sym:REGEXP` matches (whole) commodity symbols | ||||||
| - queries: `amt` now uses the = operator by default, eg amt:50 finds amounts equal to 50 | - queries: `amt` now uses the = operator by default, eg amt:50 finds amounts equal to 50 | ||||||
| - don't break when there are non-ascii characters in CSV files | - don't break when there are non-ascii characters in CSV files | ||||||
| - csv: add the `include` directive, useful for factoring out common rules used with multiple CSV files | - csv: add the `include` directive, useful for factoring out common rules used with multiple CSV files | ||||||
|  | |||||||
| @ -43,7 +43,7 @@ import Text.ParserCombinators.Parsec | |||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| import Hledger.Data.Types | import Hledger.Data.Types | ||||||
| import Hledger.Data.AccountName | import Hledger.Data.AccountName | ||||||
| import Hledger.Data.Amount (nullamt, usd) | import Hledger.Data.Amount (amount, usd) | ||||||
| import Hledger.Data.Dates | import Hledger.Data.Dates | ||||||
| import Hledger.Data.Posting | import Hledger.Data.Posting | ||||||
| import Hledger.Data.Transaction | import Hledger.Data.Transaction | ||||||
| @ -57,7 +57,6 @@ data Query = Any              -- ^ always match | |||||||
|            | Or [Query]       -- ^ match if any of these match |            | Or [Query]       -- ^ match if any of these match | ||||||
|            | And [Query]      -- ^ match if all of these match |            | And [Query]      -- ^ match if all of these match | ||||||
|            | Code String      -- ^ match if code matches this regexp |            | Code String      -- ^ match if code matches this regexp | ||||||
|            | Comm String      -- ^ match if the commodity symbol matches this regexp |  | ||||||
|            | Desc String      -- ^ match if description matches this regexp |            | Desc String      -- ^ match if description matches this regexp | ||||||
|            | Acct String      -- ^ match postings whose account matches this regexp |            | Acct String      -- ^ match postings whose account matches this regexp | ||||||
|            | Date DateSpan    -- ^ match if primary date in this date span |            | Date DateSpan    -- ^ match if primary date in this date span | ||||||
| @ -65,6 +64,7 @@ data Query = Any              -- ^ always match | |||||||
|            | Status Bool      -- ^ match if cleared status has this value |            | Status Bool      -- ^ match if cleared status has this value | ||||||
|            | Real Bool        -- ^ match if "realness" (involves a real non-virtual account ?) has this value |            | Real Bool        -- ^ match if "realness" (involves a real non-virtual account ?) has this value | ||||||
|            | Amt Ordering Quantity   -- ^ match if the amount's numeric quantity is less than/greater than/equal to some value |            | Amt Ordering Quantity   -- ^ match if the amount's numeric quantity is less than/greater than/equal to some value | ||||||
|  |            | Sym String       -- ^ match if the entire commodity symbol is matched by this regexp | ||||||
|            | Empty Bool       -- ^ if true, show zero-amount postings/accounts which are usually not shown |            | Empty Bool       -- ^ if true, show zero-amount postings/accounts which are usually not shown | ||||||
|                               --   more of a query option than a query criteria ? |                               --   more of a query option than a query criteria ? | ||||||
|            | Depth Int        -- ^ match if account depth is less than or equal to this value |            | Depth Int        -- ^ match if account depth is less than or equal to this value | ||||||
| @ -177,12 +177,12 @@ prefixes = map (++":") [ | |||||||
|     ,"inacct" |     ,"inacct" | ||||||
|     ,"amt" |     ,"amt" | ||||||
|     ,"code" |     ,"code" | ||||||
|     ,"comm" |  | ||||||
|     ,"desc" |     ,"desc" | ||||||
|     ,"acct" |     ,"acct" | ||||||
|     ,"date" |     ,"date" | ||||||
|     ,"edate" |     ,"edate" | ||||||
|     ,"status" |     ,"status" | ||||||
|  |     ,"sym" | ||||||
|     ,"real" |     ,"real" | ||||||
|     ,"empty" |     ,"empty" | ||||||
|     ,"depth" |     ,"depth" | ||||||
| @ -209,7 +209,6 @@ parseQueryTerm d ('n':'o':'t':':':s) = case parseQueryTerm d s of | |||||||
|                                        Left m  -> Left $ Not m |                                        Left m  -> Left $ Not m | ||||||
|                                        Right _ -> Left Any -- not:somequeryoption will be ignored |                                        Right _ -> Left Any -- not:somequeryoption will be ignored | ||||||
| parseQueryTerm _ ('c':'o':'d':'e':':':s) = Left $ Code s | parseQueryTerm _ ('c':'o':'d':'e':':':s) = Left $ Code s | ||||||
| parseQueryTerm _ ('c':'o':'m':'m':':':s) = Left $ Comm s |  | ||||||
| parseQueryTerm _ ('d':'e':'s':'c':':':s) = Left $ Desc s | parseQueryTerm _ ('d':'e':'s':'c':':':s) = Left $ Desc s | ||||||
| parseQueryTerm _ ('a':'c':'c':'t':':':s) = Left $ Acct s | parseQueryTerm _ ('a':'c':'c':'t':':':s) = Left $ Acct s | ||||||
| parseQueryTerm d ('d':'a':'t':'e':':':s) = | parseQueryTerm d ('d':'a':'t':'e':':':s) = | ||||||
| @ -223,6 +222,7 @@ parseQueryTerm _ ('r':'e':'a':'l':':':s) = Left $ Real $ parseBool s | |||||||
| parseQueryTerm _ ('a':'m':'t':':':s) = Left $ Amt op q where (op, q) = parseAmountTest s | parseQueryTerm _ ('a':'m':'t':':':s) = Left $ Amt op q where (op, q) = parseAmountTest s | ||||||
| parseQueryTerm _ ('e':'m':'p':'t':'y':':':s) = Left $ Empty $ parseBool s | parseQueryTerm _ ('e':'m':'p':'t':'y':':':s) = Left $ Empty $ parseBool s | ||||||
| parseQueryTerm _ ('d':'e':'p':'t':'h':':':s) = Left $ Depth $ readDef 0 s | parseQueryTerm _ ('d':'e':'p':'t':'h':':':s) = Left $ Depth $ readDef 0 s | ||||||
|  | parseQueryTerm _ ('s':'y':'m':':':s) = Left $ Sym s | ||||||
| parseQueryTerm _ ('t':'a':'g':':':s) = Left $ Tag n v where (n,v) = parseTag s | parseQueryTerm _ ('t':'a':'g':':':s) = Left $ Tag n v where (n,v) = parseTag s | ||||||
| parseQueryTerm _ "" = Left $ Any | parseQueryTerm _ "" = Left $ Any | ||||||
| parseQueryTerm d s = parseQueryTerm d $ defaultprefix++":"++s | parseQueryTerm d s = parseQueryTerm d $ defaultprefix++":"++s | ||||||
| @ -503,7 +503,6 @@ matchesPosting (None) _ = False | |||||||
| matchesPosting (Or qs) p = any (`matchesPosting` p) qs | matchesPosting (Or qs) p = any (`matchesPosting` p) qs | ||||||
| matchesPosting (And qs) p = all (`matchesPosting` p) qs | matchesPosting (And qs) p = all (`matchesPosting` p) qs | ||||||
| matchesPosting (Code r) p = regexMatchesCI r $ maybe "" tcode $ ptransaction p | matchesPosting (Code r) p = regexMatchesCI r $ maybe "" tcode $ ptransaction p | ||||||
| matchesPosting (Comm r) Posting{pamount=Mixed as} = any (regexMatchesCI r) $ map acommodity as |  | ||||||
| matchesPosting (Desc r) p = regexMatchesCI r $ maybe "" tdescription $ ptransaction p | matchesPosting (Desc r) p = regexMatchesCI r $ maybe "" tdescription $ ptransaction p | ||||||
| matchesPosting (Acct r) p = regexMatchesCI r $ paccount p | matchesPosting (Acct r) p = regexMatchesCI r $ paccount p | ||||||
| matchesPosting (Date span) p = span `spanContainsDate` postingDate p | matchesPosting (Date span) p = span `spanContainsDate` postingDate p | ||||||
| @ -516,6 +515,7 @@ matchesPosting (Amt op n) Posting{pamount=a} = compareMixedAmount op n a | |||||||
| -- matchesPosting (Empty False) Posting{pamount=a} = True | -- matchesPosting (Empty False) Posting{pamount=a} = True | ||||||
| -- matchesPosting (Empty True) Posting{pamount=a} = isZeroMixedAmount a | -- matchesPosting (Empty True) Posting{pamount=a} = isZeroMixedAmount a | ||||||
| matchesPosting (Empty _) _ = True | matchesPosting (Empty _) _ = True | ||||||
|  | matchesPosting (Sym r) Posting{pamount=Mixed as} = any (regexMatchesCI $ "^" ++ r ++ "$") $ map acommodity as | ||||||
| matchesPosting (Tag n Nothing) p = isJust $ lookupTagByName n $ postingAllTags p | matchesPosting (Tag n Nothing) p = isJust $ lookupTagByName n $ postingAllTags p | ||||||
| matchesPosting (Tag n (Just v)) p = isJust $ lookupTagByNameAndValue (n,v) $ postingAllTags p | matchesPosting (Tag n (Just v)) p = isJust $ lookupTagByNameAndValue (n,v) $ postingAllTags p | ||||||
| -- matchesPosting _ _ = False | -- matchesPosting _ _ = False | ||||||
| @ -523,7 +523,7 @@ matchesPosting (Tag n (Just v)) p = isJust $ lookupTagByNameAndValue (n,v) $ pos | |||||||
| -- | Is this simple mixed amount's quantity less than, equal to, or greater than this number ? | -- | Is this simple mixed amount's quantity less than, equal to, or greater than this number ? | ||||||
| -- For complext mixed amounts (with multiple commodities), this is always true. | -- For complext mixed amounts (with multiple commodities), this is always true. | ||||||
| compareMixedAmount :: Ordering -> Quantity -> MixedAmount -> Bool | compareMixedAmount :: Ordering -> Quantity -> MixedAmount -> Bool | ||||||
| compareMixedAmount op q (Mixed [])  = compareMixedAmount op q (Mixed [nullamt]) | compareMixedAmount op q (Mixed [])  = compareMixedAmount op q (Mixed [amount]) | ||||||
| -- compareMixedAmount op q (Mixed [a]) = strace (compare (strace $ aquantity a) (strace q)) == op | -- compareMixedAmount op q (Mixed [a]) = strace (compare (strace $ aquantity a) (strace q)) == op | ||||||
| compareMixedAmount op q (Mixed [a]) = compare (aquantity a) q == op | compareMixedAmount op q (Mixed [a]) = compare (aquantity a) q == op | ||||||
| compareMixedAmount _ _ _            = True | compareMixedAmount _ _ _            = True | ||||||
| @ -544,17 +544,20 @@ tests_matchesPosting = [ | |||||||
|     assertBool "real:1 on real posting" $ (Real True) `matchesPosting` nullposting{ptype=RegularPosting} |     assertBool "real:1 on real posting" $ (Real True) `matchesPosting` nullposting{ptype=RegularPosting} | ||||||
|     assertBool "real:1 on virtual posting fails" $ not $ (Real True) `matchesPosting` nullposting{ptype=VirtualPosting} |     assertBool "real:1 on virtual posting fails" $ not $ (Real True) `matchesPosting` nullposting{ptype=VirtualPosting} | ||||||
|     assertBool "real:1 on balanced virtual posting fails" $ not $ (Real True) `matchesPosting` nullposting{ptype=BalancedVirtualPosting} |     assertBool "real:1 on balanced virtual posting fails" $ not $ (Real True) `matchesPosting` nullposting{ptype=BalancedVirtualPosting} | ||||||
|     assertBool "" $ (Acct "'b") `matchesPosting` nullposting{paccount="'b"} |     assertBool "a" $ (Acct "'b") `matchesPosting` nullposting{paccount="'b"} | ||||||
|     assertBool "" $ not $ (Tag "a" (Just "r$")) `matchesPosting` nullposting |     assertBool "b" $ not $ (Tag "a" (Just "r$")) `matchesPosting` nullposting | ||||||
|     assertBool "" $ (Tag "foo" Nothing) `matchesPosting` nullposting{ptags=[("foo","")]} |     assertBool "c" $ (Tag "foo" Nothing) `matchesPosting` nullposting{ptags=[("foo","")]} | ||||||
|     assertBool "" $ (Tag "foo" Nothing) `matchesPosting` nullposting{ptags=[("foo","baz")]} |     assertBool "d" $ (Tag "foo" Nothing) `matchesPosting` nullposting{ptags=[("foo","baz")]} | ||||||
|     assertBool "" $ (Tag "foo" (Just "a")) `matchesPosting` nullposting{ptags=[("foo","bar")]} |     assertBool "e" $ (Tag "foo" (Just "a")) `matchesPosting` nullposting{ptags=[("foo","bar")]} | ||||||
|     assertBool "" $ not $ (Tag "foo" (Just "a$")) `matchesPosting` nullposting{ptags=[("foo","bar")]} |     assertBool "f" $ not $ (Tag "foo" (Just "a$")) `matchesPosting` nullposting{ptags=[("foo","bar")]} | ||||||
|     assertBool "" $ not $ (Tag " foo " (Just "a")) `matchesPosting` nullposting{ptags=[("foo","bar")]} |     assertBool "g" $ not $ (Tag " foo " (Just "a")) `matchesPosting` nullposting{ptags=[("foo","bar")]} | ||||||
|     assertBool "" $ not $ (Tag "foo foo" (Just " ar ba ")) `matchesPosting` nullposting{ptags=[("foo foo","bar bar")]} |     assertBool "h" $ not $ (Tag "foo foo" (Just " ar ba ")) `matchesPosting` nullposting{ptags=[("foo foo","bar bar")]} | ||||||
|     -- a tag match on a posting also sees inherited tags |     -- a tag match on a posting also sees inherited tags | ||||||
|     assertBool "" $ (Tag "txntag" Nothing) `matchesPosting` nullposting{ptransaction=Just nulltransaction{ttags=[("txntag","")]}} |     assertBool "i" $ (Tag "txntag" Nothing) `matchesPosting` nullposting{ptransaction=Just nulltransaction{ttags=[("txntag","")]}} | ||||||
|     assertBool "" $ (Comm "$") `matchesPosting` nullposting{pamount=Mixed [usd 1]} |     assertBool "j" $ not $ (Sym "$") `matchesPosting` nullposting{pamount=Mixed [usd 1]} -- becomes "^$$", ie testing for null symbol | ||||||
|  |     assertBool "k" $ (Sym "\\$") `matchesPosting` nullposting{pamount=Mixed [usd 1]} -- have to quote $ for regexpr | ||||||
|  |     assertBool "l" $ (Sym "shekels") `matchesPosting` nullposting{pamount=Mixed [amount{acommodity="shekels"}]} | ||||||
|  |     assertBool "m" $ not $ (Sym "shek") `matchesPosting` nullposting{pamount=Mixed [amount{acommodity="shekels"}]} | ||||||
|  ] |  ] | ||||||
| 
 | 
 | ||||||
| -- | Does the match expression match this transaction ? | -- | Does the match expression match this transaction ? | ||||||
| @ -565,7 +568,6 @@ matchesTransaction (None) _ = False | |||||||
| matchesTransaction (Or qs) t = any (`matchesTransaction` t) qs | matchesTransaction (Or qs) t = any (`matchesTransaction` t) qs | ||||||
| matchesTransaction (And qs) t = all (`matchesTransaction` t) qs | matchesTransaction (And qs) t = all (`matchesTransaction` t) qs | ||||||
| matchesTransaction (Code r) t = regexMatchesCI r $ tcode t | matchesTransaction (Code r) t = regexMatchesCI r $ tcode t | ||||||
| matchesTransaction q@(Comm _) t = any (q `matchesPosting`) $ tpostings t |  | ||||||
| matchesTransaction (Desc r) t = regexMatchesCI r $ tdescription t | matchesTransaction (Desc r) t = regexMatchesCI r $ tdescription t | ||||||
| matchesTransaction q@(Acct _) t = any (q `matchesPosting`) $ tpostings t | matchesTransaction q@(Acct _) t = any (q `matchesPosting`) $ tpostings t | ||||||
| matchesTransaction (Date span) t = spanContainsDate span $ tdate t | matchesTransaction (Date span) t = spanContainsDate span $ tdate t | ||||||
| @ -575,6 +577,7 @@ matchesTransaction (Real v) t = v == hasRealPostings t | |||||||
| matchesTransaction q@(Amt _ _) t = any (q `matchesPosting`) $ tpostings t | matchesTransaction q@(Amt _ _) t = any (q `matchesPosting`) $ tpostings t | ||||||
| matchesTransaction (Empty _) _ = True | matchesTransaction (Empty _) _ = True | ||||||
| matchesTransaction (Depth d) t = any (Depth d `matchesPosting`) $ tpostings t | matchesTransaction (Depth d) t = any (Depth d `matchesPosting`) $ tpostings t | ||||||
|  | matchesTransaction q@(Sym _) t = any (q `matchesPosting`) $ tpostings t | ||||||
| matchesTransaction (Tag n Nothing) t = isJust $ lookupTagByName n $ transactionAllTags t | matchesTransaction (Tag n Nothing) t = isJust $ lookupTagByName n $ transactionAllTags t | ||||||
| matchesTransaction (Tag n (Just v)) t = isJust $ lookupTagByNameAndValue (n,v) $ transactionAllTags t | matchesTransaction (Tag n (Just v)) t = isJust $ lookupTagByNameAndValue (n,v) $ transactionAllTags t | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -95,7 +95,6 @@ searchform VD{..} = [hamlet| | |||||||
|       Transactions/postings may additionally be filtered by |       Transactions/postings may additionally be filtered by | ||||||
|       acct:REGEXP (target account), # |       acct:REGEXP (target account), # | ||||||
|       code:REGEXP (transaction code), # |       code:REGEXP (transaction code), # | ||||||
|       comm:REGEXP (commodity symbol), # |  | ||||||
|       desc:REGEXP (description), # |       desc:REGEXP (description), # | ||||||
|       date:PERIODEXP (date), # |       date:PERIODEXP (date), # | ||||||
|       date2:PERIODEXP (secondary date), # |       date2:PERIODEXP (secondary date), # | ||||||
| @ -105,6 +104,7 @@ searchform VD{..} = [hamlet| | |||||||
|       real:BOOL (real/virtual-ness), # |       real:BOOL (real/virtual-ness), # | ||||||
|       empty:BOOL (is amount zero), # |       empty:BOOL (is amount zero), # | ||||||
|       amt:N, amt:<N, amt:>N (test magnitude of single-commodity amount). |       amt:N, amt:<N, amt:>N (test magnitude of single-commodity amount). | ||||||
|  |       sym:REGEXP (commodity symbol), # | ||||||
|       <br> |       <br> | ||||||
|       Prepend not: to negate, enclose multi-word patterns in quotes, multiple search terms are AND'ed. |       Prepend not: to negate, enclose multi-word patterns in quotes, multiple search terms are AND'ed. | ||||||
| |] | |] | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user