hledger-lib-1.25: A reusable library providing the core functionality of hledger
Safe HaskellNone
LanguageHaskell2010

Hledger.Query

Description

A general query system for matching things (accounts, postings, transactions..) by various criteria, and a SimpleTextParser for query expressions.

Synopsis

Query and QueryOpt

data Query Source #

A query is a composition of search criteria, which can be used to match postings, transactions, accounts and more.

Constructors

Any

always match

None

never match

Not Query

negate this match

Or [Query]

match if any of these match

And [Query]

match if all of these match

Code Regexp

match if code matches this regexp

Desc Regexp

match if description matches this regexp

Acct Regexp

match postings whose account matches this regexp

Date DateSpan

match if primary date in this date span

Date2 DateSpan

match if secondary date in this date span

StatusQ Status

match txns/postings with this status

Real Bool

match if "realness" (involves a real non-virtual account ?) has this value

Amt OrdPlus Quantity

match if the amount's numeric quantity is less thangreater thanequal to/unsignedly equal to some value

Sym Regexp

match if the entire commodity symbol is matched by this regexp

Depth Int

match if account depth is less than or equal to this value. Depth is sometimes used like a query (for filtering report data) and sometimes like a query option (for controlling display)

Tag Regexp (Maybe Regexp)

match if a tag's name, and optionally its value, is matched by these respective regexps matching the regexp if provided, exists

Type [AccountType]

match accounts whose type is one of these (or with no types, any account)

Instances

Instances details
Eq Query Source # 
Instance details

Defined in Hledger.Query

Methods

(==) :: Query -> Query -> Bool #

(/=) :: Query -> Query -> Bool #

Show Query Source # 
Instance details

Defined in Hledger.Query

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Default Query Source # 
Instance details

Defined in Hledger.Query

Methods

def :: Query #

data QueryOpt Source #

A query option changes a query's/report's behaviour and output in some way.

Constructors

QueryOptInAcctOnly AccountName

show an account register focussed on this account

QueryOptInAcct AccountName

as above but include sub-accounts in the account register | QueryOptCostBasis -- ^ show amounts converted to cost where possible | QueryOptDate2 -- ^ show secondary dates instead of primary dates

Instances

Instances details
Eq QueryOpt Source # 
Instance details

Defined in Hledger.Query

Show QueryOpt Source # 
Instance details

Defined in Hledger.Query

data OrdPlus Source #

A more expressive Ord, used for amt: queries. The Abs* variants compare with the absolute value of a number, ignoring sign.

Constructors

Lt 
LtEq 
Gt 
GtEq 
Eq 
AbsLt 
AbsLtEq 
AbsGt 
AbsGtEq 
AbsEq 

Instances

Instances details
Eq OrdPlus Source # 
Instance details

Defined in Hledger.Query

Methods

(==) :: OrdPlus -> OrdPlus -> Bool #

(/=) :: OrdPlus -> OrdPlus -> Bool #

Show OrdPlus Source # 
Instance details

Defined in Hledger.Query

payeeTag :: Maybe Text -> Either RegexError Query Source #

Construct a payee tag

noteTag :: Maybe Text -> Either RegexError Query Source #

Construct a note tag

generatedTransactionTag :: Query Source #

Construct a generated-transaction tag

parsing

parseQuery :: Day -> Text -> Either String (Query, [QueryOpt]) Source #

A version of parseQueryList which acts on a single Text of space-separated terms.

The usual shell quoting rules are assumed. When a pattern contains whitespace, it (or the whole term including prefix) should be enclosed in single or double quotes.

>>> parseQuery nulldate "expenses:dining out"
Right (Or [Acct (RegexpCI "expenses:dining"),Acct (RegexpCI "out")],[])
>>> parseQuery nulldate "\"expenses:dining out\""
Right (Acct (RegexpCI "expenses:dining out"),[])

parseQueryList :: Day -> [Text] -> Either String (Query, [QueryOpt]) Source #

Convert a list of query expression containing to a query and zero or more query options; or return an error message if query parsing fails.

A query term is either:

  1. a search pattern, which matches on one or more fields, eg:

    acct:REGEXP - match the account name with a regular expression desc:REGEXP - match the transaction description date:PERIODEXP - match the date with a period expression

The prefix indicates the field to match, or if there is no prefix account name is assumed.

  1. a query option, which modifies the reporting behaviour in some way. There is currently one of these, which may appear only once:

    inacct:FULLACCTNAME

Period expressions may contain relative dates, so a reference date is required to fully parse these.

Multiple terms are combined as follows: 1. multiple account patterns are OR'd together 2. multiple description patterns are OR'd together 3. multiple status patterns are OR'd together 4. then all terms are AND'd together

parseQueryTerm :: Day -> Text -> Either String (Either Query QueryOpt) Source #

Parse a single query term as either a query or a query option, or return an error message if parsing fails.

parseAccountType :: Bool -> Text -> Either String AccountType Source #

Case-insensitively parse one single-letter code, or one long-form word if permitted, to an account type. On failure, returns the unparseable text.

filterQuery :: (Query -> Bool) -> Query -> Query Source #

Remove query terms (or whole sub-expressions) from this query which do not match the given predicate. XXX Semantics not completely clear.

filterQueryOrNotQuery :: (Query -> Bool) -> Query -> Query Source #

Remove query terms (or whole sub-expressions) from this query which match neither the given predicate nor that predicate negated (eg, if predicate is queryIsAcct, this will keep both "acct:" and "not:acct:" terms). (Since 1.24.1, might be merged into filterQuery in future.) XXX Semantics not completely clear.

accessors

queryIsNull :: Query -> Bool Source #

Does this query match everything ?

queryIsDepth :: Query -> Bool Source #

Is this a simple query of this type ("depth:D") ? Note, does not match a compound query like "not:depth:D" or "depth:D acct:A". Likewise for the following functions.

queryIsStartDateOnly :: Bool -> Query -> Bool Source #

Does this query specify a start date and nothing else (that would filter postings prior to the date) ? When the flag is true, look for a starting secondary date instead.

queryStartDate :: Bool -> Query -> Maybe Day Source #

What start date (or secondary date) does this query specify, if any ? For OR expressions, use the earliest of the dates. NOT is ignored.

queryEndDate :: Bool -> Query -> Maybe Day Source #

What end date (or secondary date) does this query specify, if any ? For OR expressions, use the latest of the dates. NOT is ignored.

queryDateSpan :: Bool -> Query -> DateSpan Source #

What date span (or with a true argument, what secondary date span) does this query specify ? OR clauses specifying multiple spans return their union (the span enclosing all of them). AND clauses specifying multiple spans return their intersection. NOT clauses are ignored.

queryDateSpan' :: Query -> DateSpan Source #

What date span does this query specify, treating primary and secondary dates as equivalent ? OR clauses specifying multiple spans return their union (the span enclosing all of them). AND clauses specifying multiple spans return their intersection. NOT clauses are ignored.

queryDepth :: Query -> Maybe Int Source #

The depth limit this query specifies, if it has one

inAccount :: [QueryOpt] -> Maybe (AccountName, Bool) Source #

The account we are currently focussed on, if any, and whether subaccounts are included. Just looks at the first query option.

inAccountQuery :: [QueryOpt] -> Maybe Query Source #

A query for the account(s) we are currently focussed on, if any. Just looks at the first query option.

matching

matchesTransaction :: Query -> Transaction -> Bool Source #

Does the match expression match this transaction ?

matchesTransactionExtra :: (AccountName -> Maybe AccountType) -> Query -> Transaction -> Bool Source #

Like matchesTransaction, but if the journal's account types are provided, any type: terms in the query must match at least one posting's account type (and any negated type: terms must match none).

matchesDescription :: Query -> Text -> Bool Source #

Does the query match this transaction description ? Tests desc: terms, any other terms are ignored.

matchesPayeeWIP :: Query -> Payee -> Bool Source #

Does the query match this transaction payee ? Tests desc: (and payee: ?) terms, any other terms are ignored. XXX Currently an alias for matchDescription. I'm not sure if more is needed, There's some shenanigan with payee: and "payeeTag" to figure out.

matchesPosting :: Query -> Posting -> Bool Source #

Does the match expression match this posting ? When matching account name, and the posting has been transformed in some way, we will match either the original or transformed name.

matchesPostingExtra :: (AccountName -> Maybe AccountType) -> Query -> Posting -> Bool Source #

Like matchesPosting, but if the posting's account's type is provided, any type: terms in the query must match it (and any negated type: terms must not match it).

matchesAccount :: Query -> AccountName -> Bool Source #

Does the query match this account name ? A matching in: clause is also considered a match.

matchesAccountExtra :: (AccountName -> Maybe AccountType) -> (AccountName -> [Tag]) -> Query -> AccountName -> Bool Source #

Like matchesAccount, but with optional extra matching features:

  • If the account's type is provided, any type: terms in the query must match it (and any negated type: terms must not match it).
  • If the account's tags are provided, any tag: terms must match at least one of them (and any negated tag: terms must match none).

matchesAmount :: Query -> Amount -> Bool Source #

Does the match expression match this (simple) amount ?

matchesTags :: Regexp -> Maybe Regexp -> [Tag] -> Bool Source #

Does the query match the name and optionally the value of any of these tags ?

matchesPriceDirective :: Query -> PriceDirective -> Bool Source #

Does the query match this market price ?

words'' :: [Text] -> Text -> [Text] Source #

Quote-and-prefix-aware version of words - don't split on spaces which are inside quotes, including quotes which may have one of the specified prefixes in front, and maybe an additional not: prefix in front of that.

tests