hledger-lib-1.3.2: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger.Query

Contents

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

Empty Bool

if true, show zero-amount postings/accounts which are usually not shown more of a query option than a query criteria ?

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

Instances

Eq Query Source # 

Methods

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

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

Data Query Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Query -> c Query #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Query #

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Query) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query) #

gmapT :: (forall b. Data b => b -> b) -> Query -> Query #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r #

gmapQ :: (forall d. Data d => d -> u) -> Query -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Query -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Query -> m Query #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Query -> m Query #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Query -> m Query #

Show Query Source # 

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

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

Eq QueryOpt Source # 
Data QueryOpt Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QueryOpt -> c QueryOpt #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QueryOpt #

toConstr :: QueryOpt -> Constr #

dataTypeOf :: QueryOpt -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QueryOpt) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QueryOpt) #

gmapT :: (forall b. Data b => b -> b) -> QueryOpt -> QueryOpt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QueryOpt -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QueryOpt -> r #

gmapQ :: (forall d. Data d => d -> u) -> QueryOpt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QueryOpt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QueryOpt -> m QueryOpt #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryOpt -> m QueryOpt #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryOpt -> m QueryOpt #

Show QueryOpt Source # 

parsing

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

Convert a query expression containing zero or more space-separated terms to a query and zero or more query options. 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

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.

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

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

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

accessors

queryIsNull :: Query -> Bool Source #

Does this query match everything ?

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 secondary date span) does this query specify ? For OR expressions, use the widest possible span. NOT is ignored.

queryDateSpan' :: Query -> DateSpan Source #

What date span (or secondary date span) does this query specify ? For OR expressions, use the widest possible span. NOT is ignored.

queryDepth :: Query -> Int Source #

The depth limit this query specifies, or a large number if none.

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 ?

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

Does the match expression match this posting ?

Note that for account match we try both original and effective account

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

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

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

Does the match expression match this (simple) amount ?

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