{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TupleSections #-}
module Hledger.Query (
Query(..),
QueryOpt(..),
OrdPlus(..),
payeeTag,
noteTag,
generatedTransactionTag,
parseQuery,
parseQueryList,
parseQueryTerm,
parseAccountType,
parseDepthSpec,
simplifyQuery,
filterQuery,
filterQueryOrNotQuery,
matchesQuery,
queryIsNull,
queryIsDate,
queryIsDate2,
queryIsDateOrDate2,
queryIsStatus,
queryIsCode,
queryIsDesc,
queryIsTag,
queryIsAcct,
queryIsType,
queryIsDepth,
queryIsReal,
queryIsAmt,
queryIsSym,
queryIsStartDateOnly,
queryIsTransactionRelated,
queryStartDate,
queryEndDate,
queryDateSpan,
queryDateSpan',
queryDepth,
inAccount,
inAccountQuery,
matchesTransaction,
matchesTransactionExtra,
matchesDescription,
matchesPayeeWIP,
matchesPosting,
matchesPostingExtra,
matchesAccount,
matchesAccountExtra,
matchesMixedAmount,
matchesAmount,
matchesCommodity,
matchesTags,
matchesPriceDirective,
words'',
queryprefixes,
tests_Query
)
where
import Control.Applicative ((<|>), many, optional)
import Data.Default (Default(..))
import Data.Either (partitionEithers)
import Data.List (partition, intercalate)
import Data.Maybe (fromMaybe, isJust, mapMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar (Day, fromGregorian )
import Safe (headErr, readMay, maximumByMay, maximumMay, minimumMay)
import Text.Megaparsec (between, noneOf, sepBy, try, (<?>), notFollowedBy)
import Text.Megaparsec.Char (char, string, string')
import Hledger.Utils hiding (words')
import Hledger.Data.Types
import Hledger.Data.AccountName
import Hledger.Data.Amount (amountsRaw, mixedAmount, nullamt, usd)
import Hledger.Data.Dates
import Hledger.Data.Posting
import Hledger.Data.Transaction
data Query =
Not Query
| And [Query]
| Or [Query]
| Any
| None
| Date DateSpan
| Date2 DateSpan
| StatusQ Status
| Code Regexp
| Desc Regexp
| Tag Regexp (Maybe Regexp)
| Acct Regexp
| Type [AccountType]
| Depth Int
| DepthAcct Regexp Int
| Real Bool
| Amt OrdPlus Quantity
| Sym Regexp
deriving (Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
/= :: Query -> Query -> Bool
Eq,Int -> Query -> ShowS
[Query] -> ShowS
Query -> [Char]
(Int -> Query -> ShowS)
-> (Query -> [Char]) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Query -> ShowS
showsPrec :: Int -> Query -> ShowS
$cshow :: Query -> [Char]
show :: Query -> [Char]
$cshowList :: [Query] -> ShowS
showList :: [Query] -> ShowS
Show)
instance Default Query where def :: Query
def = Query
Any
payeeTag :: Maybe Text -> Either RegexError Query
payeeTag :: Maybe Text -> Either [Char] Query
payeeTag = (Maybe Regexp -> Query)
-> Either [Char] (Maybe Regexp) -> Either [Char] Query
forall a b. (a -> b) -> Either [Char] a -> Either [Char] b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"payee")) (Either [Char] (Maybe Regexp) -> Either [Char] Query)
-> (Maybe Text -> Either [Char] (Maybe Regexp))
-> Maybe Text
-> Either [Char] Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either [Char] (Maybe Regexp)
-> (Text -> Either [Char] (Maybe Regexp))
-> Maybe Text
-> Either [Char] (Maybe Regexp)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Regexp -> Either [Char] (Maybe Regexp)
forall a. a -> Either [Char] a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Regexp
forall a. Maybe a
Nothing) ((Regexp -> Maybe Regexp)
-> Either [Char] Regexp -> Either [Char] (Maybe Regexp)
forall a b. (a -> b) -> Either [Char] a -> Either [Char] b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Either [Char] Regexp -> Either [Char] (Maybe Regexp))
-> (Text -> Either [Char] Regexp)
-> Text
-> Either [Char] (Maybe Regexp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either [Char] Regexp
toRegexCI)
noteTag :: Maybe Text -> Either RegexError Query
noteTag :: Maybe Text -> Either [Char] Query
noteTag = (Maybe Regexp -> Query)
-> Either [Char] (Maybe Regexp) -> Either [Char] Query
forall a b. (a -> b) -> Either [Char] a -> Either [Char] b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"note")) (Either [Char] (Maybe Regexp) -> Either [Char] Query)
-> (Maybe Text -> Either [Char] (Maybe Regexp))
-> Maybe Text
-> Either [Char] Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either [Char] (Maybe Regexp)
-> (Text -> Either [Char] (Maybe Regexp))
-> Maybe Text
-> Either [Char] (Maybe Regexp)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Regexp -> Either [Char] (Maybe Regexp)
forall a. a -> Either [Char] a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Regexp
forall a. Maybe a
Nothing) ((Regexp -> Maybe Regexp)
-> Either [Char] Regexp -> Either [Char] (Maybe Regexp)
forall a b. (a -> b) -> Either [Char] a -> Either [Char] b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Either [Char] Regexp -> Either [Char] (Maybe Regexp))
-> (Text -> Either [Char] Regexp)
-> Text
-> Either [Char] (Maybe Regexp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either [Char] Regexp
toRegexCI)
generatedTransactionTag :: Query
generatedTransactionTag :: Query
generatedTransactionTag = Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"generated-transaction") Maybe Regexp
forall a. Maybe a
Nothing
data OrdPlus = Lt | LtEq | Gt | GtEq | Eq | AbsLt | AbsLtEq | AbsGt | AbsGtEq | AbsEq
deriving (Int -> OrdPlus -> ShowS
[OrdPlus] -> ShowS
OrdPlus -> [Char]
(Int -> OrdPlus -> ShowS)
-> (OrdPlus -> [Char]) -> ([OrdPlus] -> ShowS) -> Show OrdPlus
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OrdPlus -> ShowS
showsPrec :: Int -> OrdPlus -> ShowS
$cshow :: OrdPlus -> [Char]
show :: OrdPlus -> [Char]
$cshowList :: [OrdPlus] -> ShowS
showList :: [OrdPlus] -> ShowS
Show,OrdPlus -> OrdPlus -> Bool
(OrdPlus -> OrdPlus -> Bool)
-> (OrdPlus -> OrdPlus -> Bool) -> Eq OrdPlus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OrdPlus -> OrdPlus -> Bool
== :: OrdPlus -> OrdPlus -> Bool
$c/= :: OrdPlus -> OrdPlus -> Bool
/= :: OrdPlus -> OrdPlus -> Bool
Eq)
data QueryOpt = QueryOptInAcctOnly AccountName
| QueryOptInAcct AccountName
deriving (Int -> QueryOpt -> ShowS
[QueryOpt] -> ShowS
QueryOpt -> [Char]
(Int -> QueryOpt -> ShowS)
-> (QueryOpt -> [Char]) -> ([QueryOpt] -> ShowS) -> Show QueryOpt
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QueryOpt -> ShowS
showsPrec :: Int -> QueryOpt -> ShowS
$cshow :: QueryOpt -> [Char]
show :: QueryOpt -> [Char]
$cshowList :: [QueryOpt] -> ShowS
showList :: [QueryOpt] -> ShowS
Show, QueryOpt -> QueryOpt -> Bool
(QueryOpt -> QueryOpt -> Bool)
-> (QueryOpt -> QueryOpt -> Bool) -> Eq QueryOpt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueryOpt -> QueryOpt -> Bool
== :: QueryOpt -> QueryOpt -> Bool
$c/= :: QueryOpt -> QueryOpt -> Bool
/= :: QueryOpt -> QueryOpt -> Bool
Eq)
parseQuery :: Day -> T.Text -> Either String (Query,[QueryOpt])
parseQuery :: Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
d Text
t = Day -> [Text] -> Either [Char] (Query, [QueryOpt])
parseQueryList Day
d ([Text] -> Either [Char] (Query, [QueryOpt]))
-> [Text] -> Either [Char] (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ [Text] -> Text -> [Text]
words'' [Text]
queryprefixes Text
t
parseQueryList :: Day -> [T.Text] -> Either String (Query, [QueryOpt])
parseQueryList :: Day -> [Text] -> Either [Char] (Query, [QueryOpt])
parseQueryList Day
d [Text]
termstrs = do
[(Query, [QueryOpt])]
eterms <- (Text -> Either [Char] (Query, [QueryOpt]))
-> [Text] -> Either [Char] [(Query, [QueryOpt])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
d) [Text]
termstrs
let ([Query]
pats, [[QueryOpt]]
optss) = [(Query, [QueryOpt])] -> ([Query], [[QueryOpt]])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Query, [QueryOpt])]
eterms
q :: Query
q = [Query] -> Query
combineQueriesByType [Query]
pats
(Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query
q, [[QueryOpt]] -> [QueryOpt]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[QueryOpt]]
optss)
combineQueriesByType :: [Query] -> Query
combineQueriesByType :: [Query] -> Query
combineQueriesByType [Query]
pats = Query
q
where
([Query]
descpats, [Query]
pats') = (Query -> Bool) -> [Query] -> ([Query], [Query])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Query -> Bool
queryIsDesc [Query]
pats
([Query]
acctpats, [Query]
pats'') = (Query -> Bool) -> [Query] -> ([Query], [Query])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Query -> Bool
queryIsAcct [Query]
pats'
([Query]
statuspats, [Query]
otherpats) = (Query -> Bool) -> [Query] -> ([Query], [Query])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Query -> Bool
queryIsStatus [Query]
pats''
q :: Query
q = Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ [[Query] -> Query
Or [Query]
acctpats, [Query] -> Query
Or [Query]
descpats, [Query] -> Query
Or [Query]
statuspats] [Query] -> [Query] -> [Query]
forall a. [a] -> [a] -> [a]
++ [Query]
otherpats
words'' :: [T.Text] -> T.Text -> [T.Text]
words'' :: [Text] -> Text -> [Text]
words'' [Text]
prefixes = Either (ParseErrorBundle Text HledgerParseErrorData) [Text]
-> [Text]
forall t e a.
(Show t, Show (Token t), Show e) =>
Either (ParseErrorBundle t e) a -> a
fromparse (Either (ParseErrorBundle Text HledgerParseErrorData) [Text]
-> [Text])
-> (Text
-> Either (ParseErrorBundle Text HledgerParseErrorData) [Text])
-> Text
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parsec HledgerParseErrorData Text [Text]
-> Text
-> Either (ParseErrorBundle Text HledgerParseErrorData) [Text]
forall e a.
Parsec e Text a -> Text -> Either (ParseErrorBundle Text e) a
parsewith Parsec HledgerParseErrorData Text [Text]
maybePrefixedQuotedPhrases
where
maybePrefixedQuotedPhrases :: SimpleTextParser [T.Text]
maybePrefixedQuotedPhrases :: Parsec HledgerParseErrorData Text [Text]
maybePrefixedQuotedPhrases = [ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (m :: * -> *) a. [TextParser m a] -> TextParser m a
choice' [ParsecT HledgerParseErrorData Text Identity Text
prefixedQuotedPattern, ParsecT HledgerParseErrorData Text Identity Text
singleQuotedPattern, ParsecT HledgerParseErrorData Text Identity Text
doubleQuotedPattern, ParsecT HledgerParseErrorData Text Identity Text
patterns] ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity ()
-> Parsec HledgerParseErrorData Text [Text]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy`
(ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity ()
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
')') ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1)
prefixedQuotedPattern :: SimpleTextParser T.Text
prefixedQuotedPattern :: ParsecT HledgerParseErrorData Text Identity Text
prefixedQuotedPattern = do
Text
not' <- Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text)
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text)
-> ParsecT HledgerParseErrorData Text Identity Text
forall a b.
(a -> b)
-> ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text))
-> ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Text
Tokens Text
"not:")
let allowednexts :: [Text]
allowednexts | Text -> Bool
T.null Text
not' = [Text]
prefixes
| Bool
otherwise = [Text]
prefixes [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
""]
Text
next <- [ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (m :: * -> *) a. [TextParser m a] -> TextParser m a
choice' ([ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text)
-> [ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text
forall a b. (a -> b) -> a -> b
$ (Text -> ParsecT HledgerParseErrorData Text Identity Text)
-> [Text] -> [ParsecT HledgerParseErrorData Text Identity Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ParsecT HledgerParseErrorData Text Identity Text
Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string [Text]
allowednexts
let prefix :: T.Text
prefix :: Text
prefix = Text
not' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
next
Text
p <- ParsecT HledgerParseErrorData Text Identity Text
singleQuotedPattern ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity Text
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT HledgerParseErrorData Text Identity Text
doubleQuotedPattern
Text -> ParsecT HledgerParseErrorData Text Identity Text
forall a. a -> ParsecT HledgerParseErrorData Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT HledgerParseErrorData Text Identity Text)
-> Text -> ParsecT HledgerParseErrorData Text Identity Text
forall a b. (a -> b) -> a -> b
$ Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
stripquotes Text
p
singleQuotedPattern :: SimpleTextParser T.Text
singleQuotedPattern :: ParsecT HledgerParseErrorData Text Identity Text
singleQuotedPattern = Text -> Text
stripquotes (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\'') (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\'') (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char])
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a b. (a -> b) -> a -> b
$ [Token Text]
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf ([Char]
"'" :: [Char]))
doubleQuotedPattern :: SimpleTextParser T.Text
doubleQuotedPattern :: ParsecT HledgerParseErrorData Text Identity Text
doubleQuotedPattern = Text -> Text
stripquotes (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'"') (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'"') (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char])
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a b. (a -> b) -> a -> b
$ [Token Text]
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf ([Char]
"\"" :: [Char]))
patterns :: SimpleTextParser T.Text
patterns :: ParsecT HledgerParseErrorData Text Identity Text
patterns = [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ([Token Text]
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf ([Char]
" \n\r" :: [Char]))
queryprefixes :: [T.Text]
queryprefixes :: [Text]
queryprefixes = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
":") [
Text
"inacctonly"
,Text
"inacct"
,Text
"amt"
,Text
"code"
,Text
"desc"
,Text
"payee"
,Text
"note"
,Text
"acct"
,Text
"date"
,Text
"date2"
,Text
"status"
,Text
"cur"
,Text
"real"
,Text
"empty"
,Text
"depth"
,Text
"tag"
,Text
"type"
,Text
"expr"
]
defaultprefix :: T.Text
defaultprefix :: Text
defaultprefix = Text
"acct"
parseQueryTerm :: Day -> T.Text -> Either String (Query, [QueryOpt])
parseQueryTerm :: Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"inacctonly:" -> Just Text
s) = (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query
Any, [Text -> QueryOpt
QueryOptInAcctOnly Text
s])
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"inacct:" -> Just Text
s) = (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query
Any, [Text -> QueryOpt
QueryOptInAcct Text
s])
parseQueryTerm Day
d (Text -> Text -> Maybe Text
T.stripPrefix Text
"not:" -> Just Text
s) =
case Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
d Text
s of
Right (Query
q, [QueryOpt]
qopts) -> (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query -> Query
Not Query
q, [QueryOpt]
qopts)
Left [Char]
err -> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. a -> Either a b
Left [Char]
err
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"code:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> (Regexp -> Query) -> Regexp -> (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Code (Regexp -> (Query, [QueryOpt]))
-> Either [Char] Regexp -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Regexp
toRegexCI Text
s
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"desc:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> (Regexp -> Query) -> Regexp -> (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Desc (Regexp -> (Query, [QueryOpt]))
-> Either [Char] Regexp -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Regexp
toRegexCI Text
s
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"payee:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text -> Either [Char] Query
payeeTag (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s)
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"note:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text -> Either [Char] Query
noteTag (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s)
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"acct:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> (Regexp -> Query) -> Regexp -> (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Acct (Regexp -> (Query, [QueryOpt]))
-> Either [Char] Regexp -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Regexp
toRegexCI Text
s
parseQueryTerm Day
d (Text -> Text -> Maybe Text
T.stripPrefix Text
"date2:" -> Just Text
s) =
case Day
-> Text
-> Either
(ParseErrorBundle Text HledgerParseErrorData) (Interval, DateSpan)
parsePeriodExpr Day
d Text
s of Left ParseErrorBundle Text HledgerParseErrorData
e -> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. a -> Either a b
Left ([Char] -> Either [Char] (Query, [QueryOpt]))
-> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ [Char]
"\"date2:"[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Text -> [Char]
T.unpack Text
s[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
"\" gave a "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ParseErrorBundle Text HledgerParseErrorData -> [Char]
forall t e.
(Show t, Show (Token t), Show e) =>
ParseErrorBundle t e -> [Char]
showDateParseError ParseErrorBundle Text HledgerParseErrorData
e
Right (Interval
_,DateSpan
spn) -> (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (DateSpan -> Query
Date2 DateSpan
spn, [])
parseQueryTerm Day
d (Text -> Text -> Maybe Text
T.stripPrefix Text
"date:" -> Just Text
s) =
case Day
-> Text
-> Either
(ParseErrorBundle Text HledgerParseErrorData) (Interval, DateSpan)
parsePeriodExpr Day
d Text
s of Left ParseErrorBundle Text HledgerParseErrorData
e -> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. a -> Either a b
Left ([Char] -> Either [Char] (Query, [QueryOpt]))
-> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ [Char]
"\"date:"[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Text -> [Char]
T.unpack Text
s[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
"\" gave a "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ParseErrorBundle Text HledgerParseErrorData -> [Char]
forall t e.
(Show t, Show (Token t), Show e) =>
ParseErrorBundle t e -> [Char]
showDateParseError ParseErrorBundle Text HledgerParseErrorData
e
Right (Interval
_,DateSpan
spn) -> (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (DateSpan -> Query
Date DateSpan
spn, [])
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"status:" -> Just Text
s) =
case Text -> Either [Char] Status
parseStatus Text
s of Left [Char]
e -> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. a -> Either a b
Left ([Char] -> Either [Char] (Query, [QueryOpt]))
-> [Char] -> Either [Char] (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ [Char]
"\"status:"[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Text -> [Char]
T.unpack Text
s[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
"\" gave a parse error: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
e
Right Status
st -> (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Status -> Query
StatusQ Status
st, [])
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"real:" -> Just Text
s) = (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Bool -> Query
Real (Bool -> Query) -> Bool -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Bool
parseBool Text
s Bool -> Bool -> Bool
|| Text -> Bool
T.null Text
s, [])
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"amt:" -> Just Text
s) = (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (OrdPlus -> Quantity -> Query
Amt OrdPlus
ord Quantity
q, []) where (OrdPlus
ord, Quantity
q) = ([Char] -> (OrdPlus, Quantity))
-> ((OrdPlus, Quantity) -> (OrdPlus, Quantity))
-> Either [Char] (OrdPlus, Quantity)
-> (OrdPlus, Quantity)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either [Char] -> (OrdPlus, Quantity)
forall a. HasCallStack => [Char] -> a
error (OrdPlus, Quantity) -> (OrdPlus, Quantity)
forall a. a -> a
id (Either [Char] (OrdPlus, Quantity) -> (OrdPlus, Quantity))
-> Either [Char] (OrdPlus, Quantity) -> (OrdPlus, Quantity)
forall a b. (a -> b) -> a -> b
$ Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
s
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"depth:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Query
parseDepthSpecQuery Text
s
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"cur:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> (Regexp -> Query) -> Regexp -> (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Sym (Regexp -> (Query, [QueryOpt]))
-> Either [Char] Regexp -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Regexp
toRegexCI (Text
"^" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"$")
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"tag:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Query
parseTag Text
s
parseQueryTerm Day
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
"type:" -> Just Text
s) = (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Query
parseTypeCodes Text
s
parseQueryTerm Day
d (Text -> Text -> Maybe Text
T.stripPrefix Text
"expr:" -> Just Text
s) = Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
d Text
s
parseQueryTerm Day
_ Text
"" = (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query
Any, [])
parseQueryTerm Day
d Text
s = Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
d (Text -> Either [Char] (Query, [QueryOpt]))
-> Text -> Either [Char] (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ Text
defaultprefixText -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
":"Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
s
parseBooleanQuery :: Day -> T.Text -> Either String (Query,[QueryOpt])
parseBooleanQuery :: Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
d Text
t =
(ParseErrorBundle Text HledgerParseErrorData
-> Either [Char] (Query, [QueryOpt]))
-> ((Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt]))
-> Either
(ParseErrorBundle Text HledgerParseErrorData) (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt])
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Either [Char] (Query, [QueryOpt])
forall a b. a -> Either a b
Left ([Char] -> Either [Char] (Query, [QueryOpt]))
-> (ParseErrorBundle Text HledgerParseErrorData -> [Char])
-> ParseErrorBundle Text HledgerParseErrorData
-> Either [Char] (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char]
"failed to parse query:" [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<>) ShowS
-> (ParseErrorBundle Text HledgerParseErrorData -> [Char])
-> ParseErrorBundle Text HledgerParseErrorData
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text HledgerParseErrorData -> [Char]
customErrorBundlePretty) (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Either
(ParseErrorBundle Text HledgerParseErrorData) (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]))
-> Either
(ParseErrorBundle Text HledgerParseErrorData) (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$
Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> Text
-> Either
(ParseErrorBundle Text HledgerParseErrorData) (Query, [QueryOpt])
forall e a.
Parsec e Text a -> Text -> Either (ParseErrorBundle Text e) a
parsewith Parsec HledgerParseErrorData Text (Query, [QueryOpt])
spacedExprsP Text
t
where
spacedExprsP :: SimpleTextParser (Query, [QueryOpt])
spacedExprsP :: Parsec HledgerParseErrorData Text (Query, [QueryOpt])
spacedExprsP = ([Query] -> Query) -> [(Query, [QueryOpt])] -> (Query, [QueryOpt])
combineWith [Query] -> Query
combineQueriesByType ([(Query, [QueryOpt])] -> (Query, [QueryOpt]))
-> ParsecT
HledgerParseErrorData Text Identity [(Query, [QueryOpt])]
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
orExprsP Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT
HledgerParseErrorData Text Identity [(Query, [QueryOpt])]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy` ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1
where
combineWith :: ([Query] -> Query) -> [(Query, [QueryOpt])] -> (Query, [QueryOpt])
combineWith :: ([Query] -> Query) -> [(Query, [QueryOpt])] -> (Query, [QueryOpt])
combineWith [Query] -> Query
f [(Query, [QueryOpt])]
res =
let ([Query]
qs, [[QueryOpt]]
qoptss) = [(Query, [QueryOpt])] -> ([Query], [[QueryOpt]])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Query, [QueryOpt])]
res
qoptss' :: [QueryOpt]
qoptss' = [[QueryOpt]] -> [QueryOpt]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[QueryOpt]]
qoptss
in case [Query]
qs of
[] -> (Query
Any, [QueryOpt]
qoptss')
(Query
q:[]) -> (Query -> Query
simplifyQuery Query
q, [QueryOpt]
qoptss')
[Query]
_ -> (Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
f [Query]
qs, [QueryOpt]
qoptss')
orExprsP :: SimpleTextParser (Query, [QueryOpt])
orExprsP :: Parsec HledgerParseErrorData Text (Query, [QueryOpt])
orExprsP = do
[(Query, [QueryOpt])]
exprs <- Parsec HledgerParseErrorData Text (Query, [QueryOpt])
andExprsP Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT
HledgerParseErrorData Text Identity [(Query, [QueryOpt])]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy` (ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ())
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, FoldCase (Tokens s)) =>
Tokens s -> m (Tokens s)
string' Tokens Text
"or" ParsecT HledgerParseErrorData Text Identity (Tokens Text)
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1)
if ( [(Query, [QueryOpt])] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Query, [QueryOpt])]
exprs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
Bool -> Bool -> Bool
&& ((Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Query -> Bool
forall a. Eq a => a -> a -> Bool
/=Query
Any) ([Query] -> Bool) -> [Query] -> Bool
forall a b. (a -> b) -> a -> b
$ ((Query, [QueryOpt]) -> Query) -> [(Query, [QueryOpt])] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map ((Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDateOrDate2 (Query -> Query)
-> ((Query, [QueryOpt]) -> Query) -> (Query, [QueryOpt]) -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query, [QueryOpt]) -> Query
forall a b. (a, b) -> a
fst) [(Query, [QueryOpt])]
exprs))
then [Char] -> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a. [Char] -> ParsecT HledgerParseErrorData Text Identity a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"sorry, using date: in OR expressions is not supported."
else (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a. a -> ParsecT HledgerParseErrorData Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt]))
-> (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ ([Query] -> Query) -> [(Query, [QueryOpt])] -> (Query, [QueryOpt])
combineWith [Query] -> Query
Or [(Query, [QueryOpt])]
exprs
where
andExprsP :: SimpleTextParser (Query, [QueryOpt])
andExprsP :: Parsec HledgerParseErrorData Text (Query, [QueryOpt])
andExprsP = ([Query] -> Query) -> [(Query, [QueryOpt])] -> (Query, [QueryOpt])
combineWith [Query] -> Query
And ([(Query, [QueryOpt])] -> (Query, [QueryOpt]))
-> ParsecT
HledgerParseErrorData Text Identity [(Query, [QueryOpt])]
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
maybeNotExprP Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT
HledgerParseErrorData Text Identity [(Query, [QueryOpt])]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy` (ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ())
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, FoldCase (Tokens s)) =>
Tokens s -> m (Tokens s)
string' Tokens Text
"and" ParsecT HledgerParseErrorData Text Identity (Tokens Text)
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1)
where
maybeNotExprP :: SimpleTextParser (Query, [QueryOpt])
maybeNotExprP :: Parsec HledgerParseErrorData Text (Query, [QueryOpt])
maybeNotExprP = (((Query, [QueryOpt]) -> (Query, [QueryOpt]))
-> (() -> (Query, [QueryOpt]) -> (Query, [QueryOpt]))
-> Maybe ()
-> (Query, [QueryOpt])
-> (Query, [QueryOpt])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Query, [QueryOpt]) -> (Query, [QueryOpt])
forall a. a -> a
id (\()
_ (Query
q, [QueryOpt]
qopts) -> (Query -> Query
Not Query
q, [QueryOpt]
qopts)) (Maybe () -> (Query, [QueryOpt]) -> (Query, [QueryOpt]))
-> ParsecT HledgerParseErrorData Text Identity (Maybe ())
-> ParsecT
HledgerParseErrorData
Text
Identity
((Query, [QueryOpt]) -> (Query, [QueryOpt]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ())
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b. (a -> b) -> a -> b
$ Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, FoldCase (Tokens s)) =>
Tokens s -> m (Tokens s)
string' Tokens Text
"not" ParsecT HledgerParseErrorData Text Identity (Tokens Text)
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity ()
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
':') ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces1)) ParsecT
HledgerParseErrorData
Text
Identity
((Query, [QueryOpt]) -> (Query, [QueryOpt]))
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a b.
ParsecT HledgerParseErrorData Text Identity (a -> b)
-> ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
termOrParenthesisedExprP
where
termOrParenthesisedExprP :: SimpleTextParser (Query, [QueryOpt])
termOrParenthesisedExprP :: Parsec HledgerParseErrorData Text (Query, [QueryOpt])
termOrParenthesisedExprP =
ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity Char
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'(' ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity ()
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces) (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char)
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
forall a b. (a -> b) -> a -> b
$ ParsecT HledgerParseErrorData Text Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT HledgerParseErrorData s m ()
skipNonNewlineSpaces ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
')') Parsec HledgerParseErrorData Text (Query, [QueryOpt])
spacedExprsP
Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
queryTermP
where
queryTermP :: SimpleTextParser (Query, [QueryOpt])
queryTermP :: Parsec HledgerParseErrorData Text (Query, [QueryOpt])
queryTermP = do
Maybe Text
prefix <- ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT HledgerParseErrorData Text Identity Text
queryPrefixP
Text
arg <- ParsecT HledgerParseErrorData Text Identity Text
queryArgP
case Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
d (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" Maybe Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
arg) of
Right (Query, [QueryOpt])
q -> (Query, [QueryOpt])
-> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a. a -> ParsecT HledgerParseErrorData Text Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Query, [QueryOpt])
q
Left [Char]
err -> [Char] -> Parsec HledgerParseErrorData Text (Query, [QueryOpt])
forall a. [Char] -> a
error' [Char]
err
where
queryPrefixP :: SimpleTextParser T.Text
queryPrefixP :: ParsecT HledgerParseErrorData Text Identity Text
queryPrefixP =
(Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Text
Tokens Text
"not:" ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity Text
forall a. Semigroup a => a -> a -> a
<> (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text)
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text)
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT HledgerParseErrorData Text Identity Text
queryPrefixP))
ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity Text
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (m :: * -> *) a. [TextParser m a] -> TextParser m a
choice' (Text -> ParsecT HledgerParseErrorData Text Identity Text
Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string (Text -> ParsecT HledgerParseErrorData Text Identity Text)
-> [Text] -> [ParsecT HledgerParseErrorData Text Identity Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
queryprefixes)
ParsecT HledgerParseErrorData Text Identity Text
-> [Char] -> ParsecT HledgerParseErrorData Text Identity Text
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> [Char] -> m a
<?> [Char]
"query prefix"
queryArgP :: SimpleTextParser T.Text
queryArgP :: ParsecT HledgerParseErrorData Text Identity Text
queryArgP = [ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (m :: * -> *) a. [TextParser m a] -> TextParser m a
choice'
[ Text -> Text
stripquotes (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\'') (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\'') (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char])
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a b. (a -> b) -> a -> b
$ [Token Text]
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf ([Char]
"'" :: [Char])),
Text -> Text
stripquotes (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'"') (Token Text
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'"') (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char])
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a b. (a -> b) -> a -> b
$ [Token Text]
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf ([Char]
"\"" :: [Char])),
[Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT HledgerParseErrorData Text Identity Text
-> ParsecT HledgerParseErrorData Text Identity ()
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy ParsecT HledgerParseErrorData Text Identity Text
keywordP ParsecT HledgerParseErrorData Text Identity ()
-> ParsecT HledgerParseErrorData Text Identity [Char]
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a b.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity b
-> ParsecT HledgerParseErrorData Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a.
ParsecT HledgerParseErrorData Text Identity a
-> ParsecT HledgerParseErrorData Text Identity [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char])
-> ParsecT HledgerParseErrorData Text Identity Char
-> ParsecT HledgerParseErrorData Text Identity [Char]
forall a b. (a -> b) -> a -> b
$ [Token Text]
-> ParsecT HledgerParseErrorData Text Identity (Token Text)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf ([Char]
") \n\r" :: [Char]))) ]
where
keywordP :: SimpleTextParser T.Text
keywordP :: ParsecT HledgerParseErrorData Text Identity Text
keywordP = [ParsecT HledgerParseErrorData Text Identity Text]
-> ParsecT HledgerParseErrorData Text Identity Text
forall (m :: * -> *) a. [TextParser m a] -> TextParser m a
choice' (Tokens Text -> ParsecT HledgerParseErrorData Text Identity Text
Tokens Text
-> ParsecT HledgerParseErrorData Text Identity (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, FoldCase (Tokens s)) =>
Tokens s -> m (Tokens s)
string' (Tokens Text -> ParsecT HledgerParseErrorData Text Identity Text)
-> [Tokens Text]
-> [ParsecT HledgerParseErrorData Text Identity Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Tokens Text
"not ", Tokens Text
"and ", Tokens Text
"or "])
parseAmountQueryTerm :: T.Text -> Either String (OrdPlus, Quantity)
parseAmountQueryTerm :: Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
amtarg =
case Text
amtarg of
(Text -> Text -> Maybe Quantity
parse Text
"<=+" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
LtEq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"<+" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Lt ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
">=+" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
GtEq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
">+" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Gt ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"=+" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Eq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"+" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Eq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"<-" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Lt ,-Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"<=-" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
LtEq ,-Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
">-" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Gt ,-Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
">=-" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
GtEq ,-Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"=-" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Eq ,-Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"-" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Eq ,-Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"<=" -> Just Quantity
0) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
LtEq ,Quantity
0)
(Text -> Text -> Maybe Quantity
parse Text
"<" -> Just Quantity
0) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Lt ,Quantity
0)
(Text -> Text -> Maybe Quantity
parse Text
">=" -> Just Quantity
0) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
GtEq ,Quantity
0)
(Text -> Text -> Maybe Quantity
parse Text
">" -> Just Quantity
0) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Gt ,Quantity
0)
(Text -> Text -> Maybe Quantity
parse Text
"<=" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsLtEq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"<" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsLt ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
">=" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsGtEq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
">" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsGt ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"=" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsEq ,Quantity
q)
(Text -> Text -> Maybe Quantity
parse Text
"" -> Just Quantity
q) -> (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsEq ,Quantity
q)
Text
_ -> [Char] -> Either [Char] (OrdPlus, Quantity)
forall a b. a -> Either a b
Left ([Char] -> Either [Char] (OrdPlus, Quantity))
-> (Text -> [Char]) -> Text -> Either [Char] (OrdPlus, Quantity)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack (Text -> Either [Char] (OrdPlus, Quantity))
-> Text -> Either [Char] (OrdPlus, Quantity)
forall a b. (a -> b) -> a -> b
$
Text
"could not parse as a comparison operator followed by an optionally-signed number: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
amtarg
where
parse :: T.Text -> T.Text -> Maybe Quantity
parse :: Text -> Text -> Maybe Quantity
parse Text
p Text
s = (Text -> Text -> Maybe Text
T.stripPrefix Text
p (Text -> Maybe Text) -> (Text -> Text) -> Text -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip) Text
s Maybe Text -> (Text -> Maybe Quantity) -> Maybe Quantity
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Char] -> Maybe Quantity
forall a. Read a => [Char] -> Maybe a
readMay ([Char] -> Maybe Quantity)
-> (Text -> [Char]) -> Text -> Maybe Quantity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack (Text -> [Char]) -> (Text -> Text) -> Text -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
' ')
parseTag :: T.Text -> Either RegexError Query
parseTag :: Text -> Either [Char] Query
parseTag Text
s = do
Regexp
tag <- Text -> Either [Char] Regexp
toRegexCI (Text -> Either [Char] Regexp) -> Text -> Either [Char] Regexp
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
v then Text
s else Text
n
Maybe Regexp
body <- if Text -> Bool
T.null Text
v then Maybe Regexp -> Either [Char] (Maybe Regexp)
forall a. a -> Either [Char] a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Regexp
forall a. Maybe a
Nothing else Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp)
-> Either [Char] Regexp -> Either [Char] (Maybe Regexp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either [Char] Regexp
toRegexCI (HasCallStack => Text -> Text
Text -> Text
T.tail Text
v)
Query -> Either [Char] Query
forall a. a -> Either [Char] a
forall (m :: * -> *) a. Monad m => a -> m a
return (Query -> Either [Char] Query) -> Query -> Either [Char] Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Maybe Regexp -> Query
Tag Regexp
tag Maybe Regexp
body
where (Text
n,Text
v) = (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'=') Text
s
parseDepthSpec :: T.Text -> Either RegexError DepthSpec
parseDepthSpec :: Text -> Either [Char] DepthSpec
parseDepthSpec Text
s = do
let depthString :: [Char]
depthString = Text -> [Char]
T.unpack (Text -> [Char]) -> Text -> [Char]
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
b then Text
a else HasCallStack => Text -> Text
Text -> Text
T.tail Text
b
Int
depth <- case [Char] -> Maybe Int
forall a. Read a => [Char] -> Maybe a
readMay [Char]
depthString of
Just Int
d | Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 -> Int -> Either [Char] Int
forall a b. b -> Either a b
Right Int
d
Maybe Int
_ -> [Char] -> Either [Char] Int
forall a b. a -> Either a b
Left ([Char] -> Either [Char] Int) -> [Char] -> Either [Char] Int
forall a b. (a -> b) -> a -> b
$ [Char]
"depth: should be a positive number, but received " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
depthString
Maybe Regexp
regexp <- (Text -> Either [Char] Regexp)
-> Maybe Text -> Either [Char] (Maybe Regexp)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Maybe a -> m (Maybe b)
mapM Text -> Either [Char] Regexp
toRegexCI (Maybe Text -> Either [Char] (Maybe Regexp))
-> Maybe Text -> Either [Char] (Maybe Regexp)
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
b then Maybe Text
forall a. Maybe a
Nothing else Text -> Maybe Text
forall a. a -> Maybe a
Just Text
a
DepthSpec -> Either [Char] DepthSpec
forall a. a -> Either [Char] a
forall (m :: * -> *) a. Monad m => a -> m a
return (DepthSpec -> Either [Char] DepthSpec)
-> DepthSpec -> Either [Char] DepthSpec
forall a b. (a -> b) -> a -> b
$ case Maybe Regexp
regexp of
Maybe Regexp
Nothing -> Maybe Int -> [(Regexp, Int)] -> DepthSpec
DepthSpec (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
depth) []
Just Regexp
r -> Maybe Int -> [(Regexp, Int)] -> DepthSpec
DepthSpec Maybe Int
forall a. Maybe a
Nothing [(Regexp
r, Int
depth)]
where
(Text
a,Text
b) = (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'=') Text
s
parseDepthSpecQuery :: T.Text -> Either RegexError Query
parseDepthSpecQuery :: Text -> Either [Char] Query
parseDepthSpecQuery Text
s = do
DepthSpec Maybe Int
flat [(Regexp, Int)]
rs <- Text -> Either [Char] DepthSpec
parseDepthSpec Text
s
let regexps :: [Query]
regexps = ((Regexp, Int) -> Query) -> [(Regexp, Int)] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map ((Regexp -> Int -> Query) -> (Regexp, Int) -> Query
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Regexp -> Int -> Query
DepthAcct) [(Regexp, Int)]
rs
Query -> Either [Char] Query
forall a. a -> Either [Char] a
forall (m :: * -> *) a. Monad m => a -> m a
return (Query -> Either [Char] Query)
-> ([Query] -> Query) -> [Query] -> Either [Char] Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Query] -> Query
And ([Query] -> Either [Char] Query) -> [Query] -> Either [Char] Query
forall a b. (a -> b) -> a -> b
$ ([Query] -> [Query])
-> (Int -> [Query] -> [Query]) -> Maybe Int -> [Query] -> [Query]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Query] -> [Query]
forall a. a -> a
id (\Int
d -> (Int -> Query
Depth Int
d Query -> [Query] -> [Query]
forall a. a -> [a] -> [a]
:)) Maybe Int
flat [Query]
regexps
parseTypeCodes :: T.Text -> Either String Query
parseTypeCodes :: Text -> Either [Char] Query
parseTypeCodes Text
s =
case [Either [Char] AccountType] -> ([[Char]], [AccountType])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either [Char] AccountType] -> ([[Char]], [AccountType]))
-> [Either [Char] AccountType] -> ([[Char]], [AccountType])
forall a b. (a -> b) -> a -> b
$ (Char -> Either [Char] AccountType)
-> [Char] -> [Either [Char] AccountType]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Text -> Either [Char] AccountType
parseAccountType Bool
False (Text -> Either [Char] AccountType)
-> (Char -> Text) -> Char -> Either [Char] AccountType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton) ([Char] -> [Either [Char] AccountType])
-> [Char] -> [Either [Char] AccountType]
forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
s of
(([Char]
e:[[Char]]
_),[AccountType]
_) -> [Char] -> Either [Char] Query
forall a b. a -> Either a b
Left ([Char] -> Either [Char] Query) -> [Char] -> Either [Char] Query
forall a b. (a -> b) -> a -> b
$ [Char]
"could not parse " [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> [Char]
show [Char]
e [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Char]
" as an account type code.\n" [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Char]
help
([],[]) -> [Char] -> Either [Char] Query
forall a b. a -> Either a b
Left [Char]
help
([],[AccountType]
ts) -> Query -> Either [Char] Query
forall a b. b -> Either a b
Right (Query -> Either [Char] Query) -> Query -> Either [Char] Query
forall a b. (a -> b) -> a -> b
$ [AccountType] -> Query
Type [AccountType]
ts
where
help :: [Char]
help = [Char]
"type:'s argument should be one or more of " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Bool -> [Char]
accountTypeChoices Bool
False [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
" (case insensitive)."
accountTypeChoices :: Bool -> String
accountTypeChoices :: Bool -> [Char]
accountTypeChoices Bool
allowlongform =
[Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
", "
([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[Char]
"A",[Char]
"L",[Char]
"E",[Char]
"R",[Char]
"X",[Char]
"C",[Char]
"V"]
[[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ if Bool
allowlongform then [[Char]
"Asset",[Char]
"Liability",[Char]
"Equity",[Char]
"Revenue",[Char]
"Expense",[Char]
"Cash",[Char]
"Conversion"] else []
parseAccountType :: Bool -> Text -> Either String AccountType
parseAccountType :: Bool -> Text -> Either [Char] AccountType
parseAccountType Bool
allowlongform Text
s =
case Text -> Text
T.toLower Text
s of
Text
"a" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Asset
Text
"l" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Liability
Text
"e" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Equity
Text
"r" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Revenue
Text
"x" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Expense
Text
"c" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Cash
Text
"v" -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Conversion
Text
"asset" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Asset
Text
"liability" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Liability
Text
"equity" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Equity
Text
"revenue" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Revenue
Text
"expense" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Expense
Text
"cash" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Cash
Text
"conversion" | Bool
allowlongform -> AccountType -> Either [Char] AccountType
forall a b. b -> Either a b
Right AccountType
Conversion
Text
_ -> [Char] -> Either [Char] AccountType
forall a b. a -> Either a b
Left ([Char] -> Either [Char] AccountType)
-> [Char] -> Either [Char] AccountType
forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
s
parseStatus :: T.Text -> Either String Status
parseStatus :: Text -> Either [Char] Status
parseStatus Text
s | Text
s Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"*",Text
"1"] = Status -> Either [Char] Status
forall a b. b -> Either a b
Right Status
Cleared
| Text
s Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"",Text
"0"] = Status -> Either [Char] Status
forall a b. b -> Either a b
Right Status
Unmarked
| Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"!" = Status -> Either [Char] Status
forall a b. b -> Either a b
Right Status
Pending
| Bool
otherwise = [Char] -> Either [Char] Status
forall a b. a -> Either a b
Left ([Char] -> Either [Char] Status) -> [Char] -> Either [Char] Status
forall a b. (a -> b) -> a -> b
$ [Char]
"could not parse "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Text -> [Char]
forall a. Show a => a -> [Char]
show Text
s[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
" as a status (should be *, ! or empty)"
parseBool :: T.Text -> Bool
parseBool :: Text -> Bool
parseBool Text
s = Text
s Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
truestrings
truestrings :: [T.Text]
truestrings :: [Text]
truestrings = [Text
"1"]
simplifyQuery :: Query -> Query
simplifyQuery :: Query -> Query
simplifyQuery Query
q0 =
let q1 :: Query
q1 = Query -> Query
simplify Query
q0
in if Query
q1 Query -> Query -> Bool
forall a. Eq a => a -> a -> Bool
== Query
q0 then Query
q0 else Query -> Query
simplifyQuery Query
q1
where
simplify :: Query -> Query
simplify (And []) = Query
Any
simplify (And [Query
q]) = Query -> Query
simplify Query
q
simplify (And [Query]
qs) | [Query] -> Bool
forall {a}. Eq a => [a] -> Bool
same [Query]
qs = Query -> Query
simplify (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
forall a. HasCallStack => [a] -> a
headErr [Query]
qs
| Query
None Query -> [Query] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Query]
qs = Query
None
| (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Query -> Bool
queryIsDate [Query]
qs = DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ [DateSpan] -> DateSpan
spansIntersect ([DateSpan] -> DateSpan) -> [DateSpan] -> DateSpan
forall a b. (a -> b) -> a -> b
$ (Query -> Maybe DateSpan) -> [Query] -> [DateSpan]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Query -> Maybe DateSpan
queryTermDateSpan [Query]
qs
| Bool
otherwise = [Query] -> Query
And ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map Query -> Query
simplify [Query]
dateqs [Query] -> [Query] -> [Query]
forall a. [a] -> [a] -> [a]
++ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map Query -> Query
simplify [Query]
otherqs
where ([Query]
dateqs, [Query]
otherqs) = (Query -> Bool) -> [Query] -> ([Query], [Query])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Query -> Bool
queryIsDate ([Query] -> ([Query], [Query])) -> [Query] -> ([Query], [Query])
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> [Query] -> [Query]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query -> Query -> Bool
forall a. Eq a => a -> a -> Bool
/=Query
Any) [Query]
qs
simplify (Or []) = Query
Any
simplify (Or [Query
q]) = Query -> Query
simplifyQuery Query
q
simplify (Or [Query]
qs) | [Query] -> Bool
forall {a}. Eq a => [a] -> Bool
same [Query]
qs = Query -> Query
simplify (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
forall a. HasCallStack => [a] -> a
headErr [Query]
qs
| Query
Any Query -> [Query] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Query]
qs = Query
Any
| Bool
otherwise = [Query] -> Query
Or ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map Query -> Query
simplify ([Query] -> [Query]) -> [Query] -> [Query]
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> [Query] -> [Query]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query -> Query -> Bool
forall a. Eq a => a -> a -> Bool
/=Query
None) [Query]
qs
simplify (Date (DateSpan Maybe EFDay
Nothing Maybe EFDay
Nothing)) = Query
Any
simplify (Date2 (DateSpan Maybe EFDay
Nothing Maybe EFDay
Nothing)) = Query
Any
simplify Query
q = Query
q
same :: [a] -> Bool
same [] = Bool
True
same (a
a:[a]
as) = (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (a
aa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==) [a]
as
filterQuery :: (Query -> Bool) -> Query -> Query
filterQuery :: (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
p = Query -> Query
simplifyQuery (Query -> Query) -> (Query -> Query) -> Query -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Bool) -> Query -> Query
filterQuery' Query -> Bool
p
filterQuery' :: (Query -> Bool) -> Query -> Query
filterQuery' :: (Query -> Bool) -> Query -> Query
filterQuery' Query -> Bool
p (And [Query]
qs) = [Query] -> Query
And ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map ((Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
p) [Query]
qs
filterQuery' Query -> Bool
p (Or [Query]
qs) = [Query] -> Query
Or ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map ((Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
p) [Query]
qs
filterQuery' Query -> Bool
p Query
q = if Query -> Bool
p Query
q then Query
q else Query
Any
filterQueryOrNotQuery :: (Query -> Bool) -> Query -> Query
filterQueryOrNotQuery :: (Query -> Bool) -> Query -> Query
filterQueryOrNotQuery Query -> Bool
p0 = Query -> Query
simplifyQuery (Query -> Query) -> (Query -> Query) -> Query -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Bool) -> Query -> Query
filterQueryOrNotQuery' Query -> Bool
p0
where
filterQueryOrNotQuery' :: (Query -> Bool) -> Query -> Query
filterQueryOrNotQuery' :: (Query -> Bool) -> Query -> Query
filterQueryOrNotQuery' Query -> Bool
p (And [Query]
qs) = [Query] -> Query
And ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map ((Query -> Bool) -> Query -> Query
filterQueryOrNotQuery Query -> Bool
p) [Query]
qs
filterQueryOrNotQuery' Query -> Bool
p (Or [Query]
qs) = [Query] -> Query
Or ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Query) -> [Query] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map ((Query -> Bool) -> Query -> Query
filterQueryOrNotQuery Query -> Bool
p) [Query]
qs
filterQueryOrNotQuery' Query -> Bool
p (Not Query
q) | Query -> Bool
p Query
q = Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQueryOrNotQuery Query -> Bool
p Query
q
filterQueryOrNotQuery' Query -> Bool
p Query
q = if Query -> Bool
p Query
q then Query
q else Query
Any
matchesQuery :: (Query -> Bool) -> Query -> Bool
matchesQuery :: (Query -> Bool) -> Query -> Bool
matchesQuery Query -> Bool
p (And [Query]
qs) = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Query -> Bool) -> Query -> Bool
matchesQuery Query -> Bool
p) [Query]
qs
matchesQuery Query -> Bool
p (Or [Query]
qs) = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Query -> Bool) -> Query -> Bool
matchesQuery Query -> Bool
p) [Query]
qs
matchesQuery Query -> Bool
p (Not Query
q) = Query -> Bool
p Query
q
matchesQuery Query -> Bool
p Query
q = Query -> Bool
p Query
q
queryIsNull :: Query -> Bool
queryIsNull :: Query -> Bool
queryIsNull Query
Any = Bool
True
queryIsNull (And []) = Bool
True
queryIsNull (Not (Or [])) = Bool
True
queryIsNull Query
_ = Bool
False
queryIsDate :: Query -> Bool
queryIsDate :: Query -> Bool
queryIsDate (Date DateSpan
_) = Bool
True
queryIsDate Query
_ = Bool
False
queryIsDate2 :: Query -> Bool
queryIsDate2 :: Query -> Bool
queryIsDate2 (Date2 DateSpan
_) = Bool
True
queryIsDate2 Query
_ = Bool
False
queryIsDateOrDate2 :: Query -> Bool
queryIsDateOrDate2 :: Query -> Bool
queryIsDateOrDate2 (Date DateSpan
_) = Bool
True
queryIsDateOrDate2 (Date2 DateSpan
_) = Bool
True
queryIsDateOrDate2 Query
_ = Bool
False
queryIsStatus :: Query -> Bool
queryIsStatus :: Query -> Bool
queryIsStatus (StatusQ Status
_) = Bool
True
queryIsStatus Query
_ = Bool
False
queryIsCode :: Query -> Bool
queryIsCode :: Query -> Bool
queryIsCode (Code Regexp
_) = Bool
True
queryIsCode Query
_ = Bool
False
queryIsDesc :: Query -> Bool
queryIsDesc :: Query -> Bool
queryIsDesc (Desc Regexp
_) = Bool
True
queryIsDesc Query
_ = Bool
False
queryIsTag :: Query -> Bool
queryIsTag :: Query -> Bool
queryIsTag (Tag Regexp
_ Maybe Regexp
_) = Bool
True
queryIsTag Query
_ = Bool
False
queryIsAcct :: Query -> Bool
queryIsAcct :: Query -> Bool
queryIsAcct (Acct Regexp
_) = Bool
True
queryIsAcct Query
_ = Bool
False
queryIsType :: Query -> Bool
queryIsType :: Query -> Bool
queryIsType (Type [AccountType]
_) = Bool
True
queryIsType Query
_ = Bool
False
queryIsDepth :: Query -> Bool
queryIsDepth :: Query -> Bool
queryIsDepth (Depth Int
_) = Bool
True
queryIsDepth (DepthAcct Regexp
_ Int
_) = Bool
True
queryIsDepth Query
_ = Bool
False
queryIsReal :: Query -> Bool
queryIsReal :: Query -> Bool
queryIsReal (Real Bool
_) = Bool
True
queryIsReal Query
_ = Bool
False
queryIsAmt :: Query -> Bool
queryIsAmt :: Query -> Bool
queryIsAmt (Amt OrdPlus
_ Quantity
_) = Bool
True
queryIsAmt Query
_ = Bool
False
queryIsSym :: Query -> Bool
queryIsSym :: Query -> Bool
queryIsSym (Sym Regexp
_) = Bool
True
queryIsSym Query
_ = Bool
False
queryIsStartDateOnly :: Bool -> Query -> Bool
queryIsStartDateOnly :: Bool -> Query -> Bool
queryIsStartDateOnly Bool
_ Query
Any = Bool
False
queryIsStartDateOnly Bool
_ Query
None = Bool
False
queryIsStartDateOnly Bool
secondary (Or [Query]
ms) = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Query -> Bool
queryIsStartDateOnly Bool
secondary) [Query]
ms
queryIsStartDateOnly Bool
secondary (And [Query]
ms) = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Query -> Bool
queryIsStartDateOnly Bool
secondary) [Query]
ms
queryIsStartDateOnly Bool
False (Date (DateSpan (Just EFDay
_) Maybe EFDay
_)) = Bool
True
queryIsStartDateOnly Bool
True (Date2 (DateSpan (Just EFDay
_) Maybe EFDay
_)) = Bool
True
queryIsStartDateOnly Bool
_ Query
_ = Bool
False
queryIsTransactionRelated :: Query -> Bool
queryIsTransactionRelated :: Query -> Bool
queryIsTransactionRelated = (Query -> Bool) -> Query -> Bool
matchesQuery (
Query -> Bool
queryIsDate
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsDate2
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsStatus
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsCode
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsDesc
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsReal
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsAmt
(Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| Query -> Bool
queryIsSym
)
(|||) :: (a->Bool) -> (a->Bool) -> (a->Bool)
a -> Bool
p ||| :: forall a. (a -> Bool) -> (a -> Bool) -> a -> Bool
||| a -> Bool
q = \a
v -> a -> Bool
p a
v Bool -> Bool -> Bool
|| a -> Bool
q a
v
queryStartDate :: Bool -> Query -> Maybe Day
queryStartDate :: Bool -> Query -> Maybe Day
queryStartDate Bool
secondary (Or [Query]
ms) = [Maybe Day] -> Maybe Day
earliestMaybeDate ([Maybe Day] -> Maybe Day) -> [Maybe Day] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ (Query -> Maybe Day) -> [Query] -> [Maybe Day]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Query -> Maybe Day
queryStartDate Bool
secondary) [Query]
ms
queryStartDate Bool
secondary (And [Query]
ms) = [Maybe Day] -> Maybe Day
latestMaybeDate ([Maybe Day] -> Maybe Day) -> [Maybe Day] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ (Query -> Maybe Day) -> [Query] -> [Maybe Day]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Query -> Maybe Day
queryStartDate Bool
secondary) [Query]
ms
queryStartDate Bool
False (Date (DateSpan (Just EFDay
d) Maybe EFDay
_)) = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ EFDay -> Day
fromEFDay EFDay
d
queryStartDate Bool
True (Date2 (DateSpan (Just EFDay
d) Maybe EFDay
_)) = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ EFDay -> Day
fromEFDay EFDay
d
queryStartDate Bool
_ Query
_ = Maybe Day
forall a. Maybe a
Nothing
queryEndDate :: Bool -> Query -> Maybe Day
queryEndDate :: Bool -> Query -> Maybe Day
queryEndDate Bool
secondary (Or [Query]
ms) = [Maybe Day] -> Maybe Day
latestMaybeDate' ([Maybe Day] -> Maybe Day) -> [Maybe Day] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ (Query -> Maybe Day) -> [Query] -> [Maybe Day]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Query -> Maybe Day
queryEndDate Bool
secondary) [Query]
ms
queryEndDate Bool
secondary (And [Query]
ms) = [Maybe Day] -> Maybe Day
earliestMaybeDate' ([Maybe Day] -> Maybe Day) -> [Maybe Day] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ (Query -> Maybe Day) -> [Query] -> [Maybe Day]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Query -> Maybe Day
queryEndDate Bool
secondary) [Query]
ms
queryEndDate Bool
False (Date (DateSpan Maybe EFDay
_ (Just EFDay
d))) = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ EFDay -> Day
fromEFDay EFDay
d
queryEndDate Bool
True (Date2 (DateSpan Maybe EFDay
_ (Just EFDay
d))) = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ EFDay -> Day
fromEFDay EFDay
d
queryEndDate Bool
_ Query
_ = Maybe Day
forall a. Maybe a
Nothing
queryTermDateSpan :: Query -> Maybe DateSpan
queryTermDateSpan (Date DateSpan
spn) = DateSpan -> Maybe DateSpan
forall a. a -> Maybe a
Just DateSpan
spn
queryTermDateSpan Query
_ = Maybe DateSpan
forall a. Maybe a
Nothing
queryDateSpan :: Bool -> Query -> DateSpan
queryDateSpan :: Bool -> Query -> DateSpan
queryDateSpan Bool
secondary (Or [Query]
qs) = [DateSpan] -> DateSpan
spansUnion ([DateSpan] -> DateSpan) -> [DateSpan] -> DateSpan
forall a b. (a -> b) -> a -> b
$ (Query -> DateSpan) -> [Query] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Query -> DateSpan
queryDateSpan Bool
secondary) [Query]
qs
queryDateSpan Bool
secondary (And [Query]
qs) = [DateSpan] -> DateSpan
spansIntersect ([DateSpan] -> DateSpan) -> [DateSpan] -> DateSpan
forall a b. (a -> b) -> a -> b
$ (Query -> DateSpan) -> [Query] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Query -> DateSpan
queryDateSpan Bool
secondary) [Query]
qs
queryDateSpan Bool
_ (Date DateSpan
spn) = DateSpan
spn
queryDateSpan Bool
True (Date2 DateSpan
spn) = DateSpan
spn
queryDateSpan Bool
_ Query
_ = DateSpan
nulldatespan
queryDateSpan' :: Query -> DateSpan
queryDateSpan' :: Query -> DateSpan
queryDateSpan' (Or [Query]
qs) = [DateSpan] -> DateSpan
spansUnion ([DateSpan] -> DateSpan) -> [DateSpan] -> DateSpan
forall a b. (a -> b) -> a -> b
$ (Query -> DateSpan) -> [Query] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map Query -> DateSpan
queryDateSpan' [Query]
qs
queryDateSpan' (And [Query]
qs) = [DateSpan] -> DateSpan
spansIntersect ([DateSpan] -> DateSpan) -> [DateSpan] -> DateSpan
forall a b. (a -> b) -> a -> b
$ (Query -> DateSpan) -> [Query] -> [DateSpan]
forall a b. (a -> b) -> [a] -> [b]
map Query -> DateSpan
queryDateSpan' [Query]
qs
queryDateSpan' (Date DateSpan
spn) = DateSpan
spn
queryDateSpan' (Date2 DateSpan
spn) = DateSpan
spn
queryDateSpan' Query
_ = DateSpan
nulldatespan
earliestMaybeDate :: [Maybe Day] -> Maybe Day
earliestMaybeDate :: [Maybe Day] -> Maybe Day
earliestMaybeDate = Maybe Day -> Maybe (Maybe Day) -> Maybe Day
forall a. a -> Maybe a -> a
fromMaybe Maybe Day
forall a. Maybe a
Nothing (Maybe (Maybe Day) -> Maybe Day)
-> ([Maybe Day] -> Maybe (Maybe Day)) -> [Maybe Day] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Day] -> Maybe (Maybe Day)
forall a. Ord a => [a] -> Maybe a
minimumMay
latestMaybeDate :: [Maybe Day] -> Maybe Day
latestMaybeDate :: [Maybe Day] -> Maybe Day
latestMaybeDate = Maybe Day -> Maybe (Maybe Day) -> Maybe Day
forall a. a -> Maybe a -> a
fromMaybe Maybe Day
forall a. Maybe a
Nothing (Maybe (Maybe Day) -> Maybe Day)
-> ([Maybe Day] -> Maybe (Maybe Day)) -> [Maybe Day] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Day] -> Maybe (Maybe Day)
forall a. Ord a => [a] -> Maybe a
maximumMay
earliestMaybeDate' :: [Maybe Day] -> Maybe Day
earliestMaybeDate' :: [Maybe Day] -> Maybe Day
earliestMaybeDate' = Maybe Day -> Maybe (Maybe Day) -> Maybe Day
forall a. a -> Maybe a -> a
fromMaybe Maybe Day
forall a. Maybe a
Nothing (Maybe (Maybe Day) -> Maybe Day)
-> ([Maybe Day] -> Maybe (Maybe Day)) -> [Maybe Day] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Day] -> Maybe (Maybe Day)
forall a. Ord a => [a] -> Maybe a
minimumMay ([Maybe Day] -> Maybe (Maybe Day))
-> ([Maybe Day] -> [Maybe Day]) -> [Maybe Day] -> Maybe (Maybe Day)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Day -> Bool) -> [Maybe Day] -> [Maybe Day]
forall a. (a -> Bool) -> [a] -> [a]
filter Maybe Day -> Bool
forall a. Maybe a -> Bool
isJust
latestMaybeDate' :: [Maybe Day] -> Maybe Day
latestMaybeDate' :: [Maybe Day] -> Maybe Day
latestMaybeDate' = Maybe Day -> Maybe (Maybe Day) -> Maybe Day
forall a. a -> Maybe a -> a
fromMaybe Maybe Day
forall a. Maybe a
Nothing (Maybe (Maybe Day) -> Maybe Day)
-> ([Maybe Day] -> Maybe (Maybe Day)) -> [Maybe Day] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Day -> Maybe Day -> Ordering)
-> [Maybe Day] -> Maybe (Maybe Day)
forall a. (a -> a -> Ordering) -> [a] -> Maybe a
maximumByMay Maybe Day -> Maybe Day -> Ordering
forall {a}. Ord a => Maybe a -> Maybe a -> Ordering
compareNothingMax
where
compareNothingMax :: Maybe a -> Maybe a -> Ordering
compareNothingMax Maybe a
Nothing Maybe a
Nothing = Ordering
EQ
compareNothingMax (Just a
_) Maybe a
Nothing = Ordering
LT
compareNothingMax Maybe a
Nothing (Just a
_) = Ordering
GT
compareNothingMax (Just a
a) (Just a
b) = a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
a a
b
queryDepth :: Query -> DepthSpec
queryDepth :: Query -> DepthSpec
queryDepth (Or [Query]
qs) = (Query -> DepthSpec) -> [Query] -> DepthSpec
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Query -> DepthSpec
queryDepth [Query]
qs
queryDepth (And [Query]
qs) = (Query -> DepthSpec) -> [Query] -> DepthSpec
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Query -> DepthSpec
queryDepth [Query]
qs
queryDepth (Depth Int
d) = Maybe Int -> [(Regexp, Int)] -> DepthSpec
DepthSpec (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
d) []
queryDepth (DepthAcct Regexp
r Int
d) = Maybe Int -> [(Regexp, Int)] -> DepthSpec
DepthSpec Maybe Int
forall a. Maybe a
Nothing [(Regexp
r,Int
d)]
queryDepth Query
_ = DepthSpec
forall a. Monoid a => a
mempty
inAccount :: [QueryOpt] -> Maybe (AccountName,Bool)
inAccount :: [QueryOpt] -> Maybe (Text, Bool)
inAccount [] = Maybe (Text, Bool)
forall a. Maybe a
Nothing
inAccount (QueryOptInAcctOnly Text
a:[QueryOpt]
_) = (Text, Bool) -> Maybe (Text, Bool)
forall a. a -> Maybe a
Just (Text
a,Bool
False)
inAccount (QueryOptInAcct Text
a:[QueryOpt]
_) = (Text, Bool) -> Maybe (Text, Bool)
forall a. a -> Maybe a
Just (Text
a,Bool
True)
inAccountQuery :: [QueryOpt] -> Maybe Query
inAccountQuery :: [QueryOpt] -> Maybe Query
inAccountQuery [] = Maybe Query
forall a. Maybe a
Nothing
inAccountQuery (QueryOptInAcctOnly Text
a : [QueryOpt]
_) = Query -> Maybe Query
forall a. a -> Maybe a
Just (Query -> Maybe Query)
-> (Regexp -> Query) -> Regexp -> Maybe Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Acct (Regexp -> Maybe Query) -> Regexp -> Maybe Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
accountNameToAccountOnlyRegex Text
a
inAccountQuery (QueryOptInAcct Text
a : [QueryOpt]
_) = Query -> Maybe Query
forall a. a -> Maybe a
Just (Query -> Maybe Query)
-> (Regexp -> Query) -> Regexp -> Maybe Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> Query
Acct (Regexp -> Maybe Query) -> Regexp -> Maybe Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
accountNameToAccountRegex Text
a
matchesCommodity :: Query -> CommoditySymbol -> Bool
matchesCommodity :: Query -> Text -> Bool
matchesCommodity (Sym Regexp
r) = Regexp -> Text -> Bool
regexMatchText Regexp
r
matchesCommodity Query
_ = Bool -> Text -> Bool
forall a b. a -> b -> a
const Bool
True
matchesAmount :: Query -> Amount -> Bool
matchesAmount :: Query -> Amount -> Bool
matchesAmount (Not Query
q) Amount
a = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Query
q Query -> Amount -> Bool
`matchesAmount` Amount
a
matchesAmount (Query
Any) Amount
_ = Bool
True
matchesAmount (Query
None) Amount
_ = Bool
False
matchesAmount (Or [Query]
qs) Amount
a = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Amount -> Bool
`matchesAmount` Amount
a) [Query]
qs
matchesAmount (And [Query]
qs) Amount
a = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Query -> Amount -> Bool
`matchesAmount` Amount
a) [Query]
qs
matchesAmount (Amt OrdPlus
ord Quantity
n) Amount
a = OrdPlus -> Quantity -> Amount -> Bool
compareAmount OrdPlus
ord Quantity
n Amount
a
matchesAmount (Sym Regexp
r) Amount
a = Query -> Text -> Bool
matchesCommodity (Regexp -> Query
Sym Regexp
r) (Amount -> Text
acommodity Amount
a)
matchesAmount Query
_ Amount
_ = Bool
True
compareAmount :: OrdPlus -> Quantity -> Amount -> Bool
compareAmount :: OrdPlus -> Quantity -> Amount -> Bool
compareAmount OrdPlus
ord Quantity
q Amount{aquantity :: Amount -> Quantity
aquantity=Quantity
aq} = case OrdPlus
ord of OrdPlus
Lt -> Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
< Quantity
q
OrdPlus
LtEq -> Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
<= Quantity
q
OrdPlus
Gt -> Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
> Quantity
q
OrdPlus
GtEq -> Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
>= Quantity
q
OrdPlus
Eq -> Quantity
aq Quantity -> Quantity -> Bool
forall a. Eq a => a -> a -> Bool
== Quantity
q
OrdPlus
AbsLt -> Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
< Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
q
OrdPlus
AbsLtEq -> Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
<= Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
q
OrdPlus
AbsGt -> Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
> Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
q
OrdPlus
AbsGtEq -> Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
aq Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
>= Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
q
OrdPlus
AbsEq -> Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
aq Quantity -> Quantity -> Bool
forall a. Eq a => a -> a -> Bool
== Quantity -> Quantity
forall a. Num a => a -> a
abs Quantity
q
matchesMixedAmount :: Query -> MixedAmount -> Bool
matchesMixedAmount :: Query -> MixedAmount -> Bool
matchesMixedAmount Query
q MixedAmount
ma = case MixedAmount -> [Amount]
amountsRaw MixedAmount
ma of
[] -> Query
q Query -> Amount -> Bool
`matchesAmount` Amount
nullamt
[Amount]
as -> (Amount -> Bool) -> [Amount] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query
q Query -> Amount -> Bool
`matchesAmount`) [Amount]
as
matchesAccount :: Query -> AccountName -> Bool
matchesAccount :: Query -> Text -> Bool
matchesAccount (Query
None) Text
_ = Bool
False
matchesAccount (Not Query
m) Text
a = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Query -> Text -> Bool
matchesAccount Query
m Text
a
matchesAccount (Or [Query]
ms) Text
a = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Text -> Bool
`matchesAccount` Text
a) [Query]
ms
matchesAccount (And [Query]
ms) Text
a = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Query -> Text -> Bool
`matchesAccount` Text
a) [Query]
ms
matchesAccount (Acct Regexp
r) Text
a = Regexp -> Text -> Bool
regexMatchText Regexp
r Text
a
matchesAccount (Depth Int
d) Text
a = Text -> Int
accountNameLevel Text
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
d
matchesAccount (DepthAcct Regexp
r Int
d) Text
a = Text -> Int
accountNameLevel Text
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
d Bool -> Bool -> Bool
|| Bool -> Bool
not (Regexp -> Text -> Bool
regexMatchText Regexp
r Text
a)
matchesAccount (Tag Regexp
_ Maybe Regexp
_) Text
_ = Bool
False
matchesAccount Query
_ Text
_ = Bool
True
matchesAccountExtra :: (AccountName -> Maybe AccountType) -> (AccountName -> [Tag]) -> Query -> AccountName -> Bool
Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
atags (Not Query
q ) Text
a = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe AccountType)
-> (Text -> [(Text, Text)]) -> Query -> Text -> Bool
matchesAccountExtra Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
atags Query
q Text
a
matchesAccountExtra Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
atags (Or [Query]
qs ) Text
a = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Query
q -> (Text -> Maybe AccountType)
-> (Text -> [(Text, Text)]) -> Query -> Text -> Bool
matchesAccountExtra Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
atags Query
q Text
a) [Query]
qs
matchesAccountExtra Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
atags (And [Query]
qs ) Text
a = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Query
q -> (Text -> Maybe AccountType)
-> (Text -> [(Text, Text)]) -> Query -> Text -> Bool
matchesAccountExtra Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
atags Query
q Text
a) [Query]
qs
matchesAccountExtra Text -> Maybe AccountType
atypes Text -> [(Text, Text)]
_ (Type [AccountType]
ts) Text
a = Bool -> (AccountType -> Bool) -> Maybe AccountType -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (\AccountType
t -> (AccountType -> Bool) -> [AccountType] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (AccountType
t AccountType -> AccountType -> Bool
`isAccountSubtypeOf`) [AccountType]
ts) (Maybe AccountType -> Bool) -> Maybe AccountType -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Maybe AccountType
atypes Text
a
matchesAccountExtra Text -> Maybe AccountType
_ Text -> [(Text, Text)]
atags (Tag Regexp
npat Maybe Regexp
vpat) Text
a = Regexp -> Maybe Regexp -> [(Text, Text)] -> Bool
matchesTags Regexp
npat Maybe Regexp
vpat ([(Text, Text)] -> Bool) -> [(Text, Text)] -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)]
atags Text
a
matchesAccountExtra Text -> Maybe AccountType
_ Text -> [(Text, Text)]
_ Query
q Text
a = Query -> Text -> Bool
matchesAccount Query
q Text
a
matchesPosting :: Query -> Posting -> Bool
matchesPosting :: Query -> Posting -> Bool
matchesPosting (Not Query
q) Posting
p = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Query
q Query -> Posting -> Bool
`matchesPosting` Posting
p
matchesPosting (Query
Any) Posting
_ = Bool
True
matchesPosting (Query
None) Posting
_ = Bool
False
matchesPosting (Or [Query]
qs) Posting
p = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Posting -> Bool
`matchesPosting` Posting
p) [Query]
qs
matchesPosting (And [Query]
qs) Posting
p = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Query -> Posting -> Bool
`matchesPosting` Posting
p) [Query]
qs
matchesPosting (Code Regexp
r) Posting
p = Bool -> (Transaction -> Bool) -> Maybe Transaction -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Regexp -> Text -> Bool
regexMatchText Regexp
r (Text -> Bool) -> (Transaction -> Text) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
tcode) (Maybe Transaction -> Bool) -> Maybe Transaction -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Transaction
ptransaction Posting
p
matchesPosting (Desc Regexp
r) Posting
p = Bool -> (Transaction -> Bool) -> Maybe Transaction -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Regexp -> Text -> Bool
regexMatchText Regexp
r (Text -> Bool) -> (Transaction -> Text) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
tdescription) (Maybe Transaction -> Bool) -> Maybe Transaction -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Transaction
ptransaction Posting
p
matchesPosting (Acct Regexp
r) Posting
p = Posting -> Bool
matches Posting
p Bool -> Bool -> Bool
|| Bool -> (Posting -> Bool) -> Maybe Posting -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Posting -> Bool
matches (Posting -> Maybe Posting
poriginal Posting
p) where matches :: Posting -> Bool
matches = Regexp -> Text -> Bool
regexMatchText Regexp
r (Text -> Bool) -> (Posting -> Text) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> Text
paccount
matchesPosting (Date DateSpan
spn) Posting
p = DateSpan
spn DateSpan -> Day -> Bool
`spanContainsDate` Posting -> Day
postingDate Posting
p
matchesPosting (Date2 DateSpan
spn) Posting
p = DateSpan
spn DateSpan -> Day -> Bool
`spanContainsDate` Posting -> Day
postingDate2 Posting
p
matchesPosting (StatusQ Status
s) Posting
p = Posting -> Status
postingStatus Posting
p Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
s
matchesPosting (Real Bool
v) Posting
p = Bool
v Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Posting -> Bool
isReal Posting
p
matchesPosting q :: Query
q@(Depth Int
_) Posting{paccount :: Posting -> Text
paccount=Text
a} = Query
q Query -> Text -> Bool
`matchesAccount` Text
a
matchesPosting q :: Query
q@(DepthAcct Regexp
_ Int
_) Posting{paccount :: Posting -> Text
paccount=Text
a} = Query
q Query -> Text -> Bool
`matchesAccount` Text
a
matchesPosting q :: Query
q@(Amt OrdPlus
_ Quantity
_) Posting{pamount :: Posting -> MixedAmount
pamount=MixedAmount
as} = Query
q Query -> MixedAmount -> Bool
`matchesMixedAmount` MixedAmount
as
matchesPosting (Sym Regexp
r) Posting{pamount :: Posting -> MixedAmount
pamount=MixedAmount
as} = (Amount -> Bool) -> [Amount] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Text -> Bool
matchesCommodity (Regexp -> Query
Sym Regexp
r) (Text -> Bool) -> (Amount -> Text) -> Amount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Text
acommodity) ([Amount] -> Bool) -> [Amount] -> Bool
forall a b. (a -> b) -> a -> b
$ MixedAmount -> [Amount]
amountsRaw MixedAmount
as
matchesPosting (Tag Regexp
n Maybe Regexp
v) Posting
p = case (Regexp -> Text
reString Regexp
n, Maybe Regexp
v) of
(Text
"payee", Just Regexp
v') -> Bool -> (Transaction -> Bool) -> Maybe Transaction -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Regexp -> Text -> Bool
regexMatchText Regexp
v' (Text -> Bool) -> (Transaction -> Text) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
transactionPayee) (Maybe Transaction -> Bool) -> Maybe Transaction -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Transaction
ptransaction Posting
p
(Text
"note", Just Regexp
v') -> Bool -> (Transaction -> Bool) -> Maybe Transaction -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Regexp -> Text -> Bool
regexMatchText Regexp
v' (Text -> Bool) -> (Transaction -> Text) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
transactionNote) (Maybe Transaction -> Bool) -> Maybe Transaction -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Transaction
ptransaction Posting
p
(Text
_, Maybe Regexp
mv) -> Regexp -> Maybe Regexp -> [(Text, Text)] -> Bool
matchesTags Regexp
n Maybe Regexp
mv ([(Text, Text)] -> Bool) -> [(Text, Text)] -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> [(Text, Text)]
postingAllTags Posting
p
matchesPosting (Type [AccountType]
_) Posting
_ = Bool
False
matchesPostingExtra :: (AccountName -> Maybe AccountType) -> Query -> Posting -> Bool
Text -> Maybe AccountType
atype (Not Query
q ) Posting
p = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe AccountType) -> Query -> Posting -> Bool
matchesPostingExtra Text -> Maybe AccountType
atype Query
q Posting
p
matchesPostingExtra Text -> Maybe AccountType
atype (Or [Query]
qs) Posting
p = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Query
q -> (Text -> Maybe AccountType) -> Query -> Posting -> Bool
matchesPostingExtra Text -> Maybe AccountType
atype Query
q Posting
p) [Query]
qs
matchesPostingExtra Text -> Maybe AccountType
atype (And [Query]
qs) Posting
p = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Query
q -> (Text -> Maybe AccountType) -> Query -> Posting -> Bool
matchesPostingExtra Text -> Maybe AccountType
atype Query
q Posting
p) [Query]
qs
matchesPostingExtra Text -> Maybe AccountType
atype (Type [AccountType]
ts) Posting
p =
(Bool -> (AccountType -> Bool) -> Maybe AccountType -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (\AccountType
t -> (AccountType -> Bool) -> [AccountType] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (AccountType
t AccountType -> AccountType -> Bool
`isAccountSubtypeOf`) [AccountType]
ts) (Maybe AccountType -> Bool)
-> (Text -> Maybe AccountType) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe AccountType
atype (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> Text
paccount Posting
p)
Bool -> Bool -> Bool
|| (Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ do
Posting
porig <- Posting -> Maybe Posting
poriginal Posting
p
let a :: Text
a = Posting -> Text
paccount Posting
porig
AccountType
t <- Text -> Maybe AccountType
atype Text
a
Bool -> Maybe Bool
forall a. a -> Maybe a
Just (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ (AccountType -> Bool) -> [AccountType] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (AccountType
t AccountType -> AccountType -> Bool
`isAccountSubtypeOf`) [AccountType]
ts
)
matchesPostingExtra Text -> Maybe AccountType
_ Query
q Posting
p = Query -> Posting -> Bool
matchesPosting Query
q Posting
p
matchesTransaction :: Query -> Transaction -> Bool
matchesTransaction :: Query -> Transaction -> Bool
matchesTransaction (Not Query
q) Transaction
t = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Query
q Query -> Transaction -> Bool
`matchesTransaction` Transaction
t
matchesTransaction (Query
Any) Transaction
_ = Bool
True
matchesTransaction (Query
None) Transaction
_ = Bool
False
matchesTransaction (Or [Query]
qs) Transaction
t = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Transaction -> Bool
`matchesTransaction` Transaction
t) [Query]
qs
matchesTransaction (And [Query]
qs) Transaction
t = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Query -> Transaction -> Bool
`matchesTransaction` Transaction
t) [Query]
qs
matchesTransaction (Code Regexp
r) Transaction
t = Regexp -> Text -> Bool
regexMatchText Regexp
r (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
tcode Transaction
t
matchesTransaction (Desc Regexp
r) Transaction
t = Regexp -> Text -> Bool
regexMatchText Regexp
r (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
tdescription Transaction
t
matchesTransaction q :: Query
q@(Acct Regexp
_) Transaction
t = (Posting -> Bool) -> [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query
q Query -> Posting -> Bool
`matchesPosting`) ([Posting] -> Bool) -> [Posting] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
matchesTransaction (Date DateSpan
spn) Transaction
t = DateSpan -> Day -> Bool
spanContainsDate DateSpan
spn (Day -> Bool) -> Day -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> Day
tdate Transaction
t
matchesTransaction (Date2 DateSpan
spn) Transaction
t = DateSpan -> Day -> Bool
spanContainsDate DateSpan
spn (Day -> Bool) -> Day -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> Day
transactionDate2 Transaction
t
matchesTransaction (StatusQ Status
s) Transaction
t = Transaction -> Status
tstatus Transaction
t Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
s
matchesTransaction (Real Bool
v) Transaction
t = Bool
v Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Transaction -> Bool
hasRealPostings Transaction
t
matchesTransaction q :: Query
q@(Amt OrdPlus
_ Quantity
_) Transaction
t = (Posting -> Bool) -> [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query
q Query -> Posting -> Bool
`matchesPosting`) ([Posting] -> Bool) -> [Posting] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
matchesTransaction q :: Query
q@(Depth Int
_) Transaction
t = (Posting -> Bool) -> [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query
q Query -> Posting -> Bool
`matchesPosting`) ([Posting] -> Bool) -> [Posting] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
matchesTransaction q :: Query
q@(DepthAcct Regexp
_ Int
_) Transaction
t = (Posting -> Bool) -> [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query
q Query -> Posting -> Bool
`matchesPosting`) ([Posting] -> Bool) -> [Posting] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
matchesTransaction q :: Query
q@(Sym Regexp
_) Transaction
t = (Posting -> Bool) -> [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query
q Query -> Posting -> Bool
`matchesPosting`) ([Posting] -> Bool) -> [Posting] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
matchesTransaction (Tag Regexp
n Maybe Regexp
v) Transaction
t = case (Regexp -> Text
reString Regexp
n, Maybe Regexp
v) of
(Text
"payee", Just Regexp
v') -> Regexp -> Text -> Bool
regexMatchText Regexp
v' (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
transactionPayee Transaction
t
(Text
"note", Just Regexp
v') -> Regexp -> Text -> Bool
regexMatchText Regexp
v' (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
transactionNote Transaction
t
(Text
_, Maybe Regexp
v') -> Regexp -> Maybe Regexp -> [(Text, Text)] -> Bool
matchesTags Regexp
n Maybe Regexp
v' ([(Text, Text)] -> Bool) -> [(Text, Text)] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [(Text, Text)]
transactionAllTags Transaction
t
matchesTransaction (Type [AccountType]
_) Transaction
_ = Bool
False
matchesTransactionExtra :: (AccountName -> Maybe AccountType) -> Query -> Transaction -> Bool
Text -> Maybe AccountType
atype (Not Query
q) Transaction
t = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe AccountType) -> Query -> Transaction -> Bool
matchesTransactionExtra Text -> Maybe AccountType
atype Query
q Transaction
t
matchesTransactionExtra Text -> Maybe AccountType
atype (Or [Query]
qs) Transaction
t = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Query
q -> (Text -> Maybe AccountType) -> Query -> Transaction -> Bool
matchesTransactionExtra Text -> Maybe AccountType
atype Query
q Transaction
t) [Query]
qs
matchesTransactionExtra Text -> Maybe AccountType
atype (And [Query]
qs) Transaction
t = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Query
q -> (Text -> Maybe AccountType) -> Query -> Transaction -> Bool
matchesTransactionExtra Text -> Maybe AccountType
atype Query
q Transaction
t) [Query]
qs
matchesTransactionExtra Text -> Maybe AccountType
atype q :: Query
q@(Type [AccountType]
_) Transaction
t = (Posting -> Bool) -> [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Text -> Maybe AccountType) -> Query -> Posting -> Bool
matchesPostingExtra Text -> Maybe AccountType
atype Query
q) ([Posting] -> Bool) -> [Posting] -> Bool
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
matchesTransactionExtra Text -> Maybe AccountType
_ Query
q Transaction
t = Query -> Transaction -> Bool
matchesTransaction Query
q Transaction
t
matchesDescription :: Query -> Text -> Bool
matchesDescription :: Query -> Text -> Bool
matchesDescription (Not Query
q) Text
d = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Query
q Query -> Text -> Bool
`matchesDescription` Text
d
matchesDescription (Query
Any) Text
_ = Bool
True
matchesDescription (Query
None) Text
_ = Bool
False
matchesDescription (Or [Query]
qs) Text
d = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> Text -> Bool
`matchesDescription` Text
d) ([Query] -> Bool) -> [Query] -> Bool
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> [Query] -> [Query]
forall a. (a -> Bool) -> [a] -> [a]
filter Query -> Bool
queryIsDesc [Query]
qs
matchesDescription (And [Query]
qs) Text
d = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Query -> Text -> Bool
`matchesDescription` Text
d) ([Query] -> Bool) -> [Query] -> Bool
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> [Query] -> [Query]
forall a. (a -> Bool) -> [a] -> [a]
filter Query -> Bool
queryIsDesc [Query]
qs
matchesDescription (Code Regexp
_) Text
_ = Bool
False
matchesDescription (Desc Regexp
r) Text
d = Regexp -> Text -> Bool
regexMatchText Regexp
r Text
d
matchesDescription Query
_ Text
_ = Bool
False
matchesPayeeWIP :: Query -> Payee -> Bool
matchesPayeeWIP :: Query -> Text -> Bool
matchesPayeeWIP = Query -> Text -> Bool
matchesDescription
matchesTags :: Regexp -> Maybe Regexp -> [Tag] -> Bool
matchesTags :: Regexp -> Maybe Regexp -> [(Text, Text)] -> Bool
matchesTags Regexp
namepat Maybe Regexp
valuepat = ((Text, Text) -> Bool) -> [(Text, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Regexp -> Maybe Regexp -> (Text, Text) -> Bool
matches Regexp
namepat Maybe Regexp
valuepat)
where
matches :: Regexp -> Maybe Regexp -> (Text, Text) -> Bool
matches Regexp
npat Maybe Regexp
vpat (Text
n,Text
v) = Regexp -> Text -> Bool
regexMatchText Regexp
npat Text
n Bool -> Bool -> Bool
&& (Text -> Bool)
-> (Regexp -> Text -> Bool) -> Maybe Regexp -> Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> Text -> Bool
forall a b. a -> b -> a
const Bool
True) Regexp -> Text -> Bool
regexMatchText Maybe Regexp
vpat Text
v
matchesPriceDirective :: Query -> PriceDirective -> Bool
matchesPriceDirective :: Query -> PriceDirective -> Bool
matchesPriceDirective (Query
None) PriceDirective
_ = Bool
False
matchesPriceDirective (Not Query
q) PriceDirective
p = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Query -> PriceDirective -> Bool
matchesPriceDirective Query
q PriceDirective
p
matchesPriceDirective (Or [Query]
qs) PriceDirective
p = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Query -> PriceDirective -> Bool
`matchesPriceDirective` PriceDirective
p) [Query]
qs
matchesPriceDirective (And [Query]
qs) PriceDirective
p = (Query -> Bool) -> [Query] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Query -> PriceDirective -> Bool
`matchesPriceDirective` PriceDirective
p) [Query]
qs
matchesPriceDirective q :: Query
q@(Amt OrdPlus
_ Quantity
_) PriceDirective
p = Query -> Amount -> Bool
matchesAmount Query
q (PriceDirective -> Amount
pdamount PriceDirective
p)
matchesPriceDirective q :: Query
q@(Sym Regexp
_) PriceDirective
p = Query -> Text -> Bool
matchesCommodity Query
q (PriceDirective -> Text
pdcommodity PriceDirective
p)
matchesPriceDirective (Date DateSpan
spn) PriceDirective
p = DateSpan -> Day -> Bool
spanContainsDate DateSpan
spn (PriceDirective -> Day
pddate PriceDirective
p)
matchesPriceDirective Query
_ PriceDirective
_ = Bool
True
tests_Query :: TestTree
tests_Query = [Char] -> [TestTree] -> TestTree
testGroup [Char]
"Query" [
[Char] -> Assertion -> TestTree
testCase [Char]
"simplifyQuery" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
Or [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"a"]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"a")
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
Or [Query
Any,Query
None]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query
Any)
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
Any,Query
None]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query
None)
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
Any,Query
Any]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query
Any)
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"b",Query
Any]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"b")
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
Any,[Query] -> Query
And [DateSpan -> Query
Date (Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing Maybe EFDay
forall a. Maybe a
Nothing)]]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query
Any)
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [DateSpan -> Query
Date (Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Exact (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2013 Int
01 Int
01)), DateSpan -> Query
Date (Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Exact (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2012 Int
01 Int
01) Maybe EFDay
forall a. Maybe a
Nothing)])
Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (DateSpan -> Query
Date (Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Exact (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2012 Int
01 Int
01) (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Exact (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2013 Int
01 Int
01)))
(Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [[Query] -> Query
Or [],[Query] -> Query
Or [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"b b"]]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"b b")
,[Char] -> Assertion -> TestTree
testCase [Char]
"parseQuery" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
(Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
nulldate Text
"acct:'expenses:autres d\233penses' desc:b") Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
And [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:autres d\233penses", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
nulldate Text
"inacct:a desc:\"b b\"" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b b", [Text -> QueryOpt
QueryOptInAcct Text
"a"])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
nulldate Text
"inacct:a inacct:b" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query
Any, [Text -> QueryOpt
QueryOptInAcct Text
"a", Text -> QueryOpt
QueryOptInAcct Text
"b"])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
nulldate Text
"desc:'x x'" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"x x", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
nulldate Text
"'a a' 'b" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
Or [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a a",Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"'b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQuery Day
nulldate Text
"\"" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"\"", [])
,[Char] -> Assertion -> TestTree
testCase [Char]
"parseBooleanQuery" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"(tag:'atag=a')" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"atag") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a"), [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"( tag:\"atag=a\" )" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"atag") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a"), [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"(acct:'expenses:food')" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:food", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"(((acct:'expenses:food')))" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:food", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"acct:'expenses:food' AND desc:'b'" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
And [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:food", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"((desc:'a') AND (desc:'b') OR (desc:'c'))" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
Or [[Query] -> Query
And [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"c"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"((desc:'a') OR (desc:'b') AND (desc:'c'))" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
Or [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", [Query] -> Query
And [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"c"]], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"((desc:'a') AND desc:'b' AND (desc:'c'))" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
And [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"c"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"(NOT (desc:'a') AND (desc:'b'))" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
And [Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"((desc:'a') AND (NOT desc:'b'))" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
And [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"(desc:'a' AND desc:'b')" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
And [Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"(acct:'a' acct:'b')" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
Or [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
" acct:'a' acct:'b'" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
Or [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"b"], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"not:a" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"expenses:food OR (tag:A expenses:drink)" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right ([Query] -> Query
Or [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:food", [Query] -> Query
And [Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:drink", Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"A") Maybe Regexp
forall a. Maybe a
Nothing]], [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"not a" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"nota" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"nota", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseBooleanQuery Day
nulldate Text
"not (acct:a)" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", [])
,[Char] -> Assertion -> TestTree
testCase [Char]
"words''" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
([Text] -> Text -> [Text]
words'' [] Text
"a b") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"a",Text
"b"]
([Text] -> Text -> [Text]
words'' [] Text
"'a b'") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"a b"]
([Text] -> Text -> [Text]
words'' [] Text
"not:a b") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"not:a",Text
"b"]
([Text] -> Text -> [Text]
words'' [] Text
"not:'a b'") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"not:a b"]
([Text] -> Text -> [Text]
words'' [] Text
"'not:a b'") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"not:a b"]
([Text] -> Text -> [Text]
words'' [Text
"desc:"] Text
"not:desc:'a b'") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"not:desc:a b"]
([Text] -> Text -> [Text]
words'' [Text]
queryprefixes Text
"\"acct:expenses:autres d\233penses\"") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"acct:expenses:autres d\233penses"]
([Text] -> Text -> [Text]
words'' [Text]
queryprefixes Text
"\"") [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
"\""]
,[Char] -> Assertion -> TestTree
testCase [Char]
"filterQuery" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
(Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDepth Query
Any Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Query
Any
(Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDepth (Int -> Query
Depth Int
1) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Int -> Query
Depth Int
1
(Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not(Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Query -> Bool
queryIsDepth) ([Query] -> Query
And [[Query] -> Query
And [Status -> Query
StatusQ Status
Cleared,Int -> Query
Depth Int
1]]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Status -> Query
StatusQ Status
Cleared
(Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsDepth ([Query] -> Query
And [DateSpan -> Query
Date DateSpan
nulldatespan, Query -> Query
Not ([Query] -> Query
Or [Query
Any, Int -> Query
Depth Int
1])]) Query -> Query -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Query
Any
,[Char] -> Assertion -> TestTree
testCase [Char]
"parseQueryTerm" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"a" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"acct:expenses:autres d\233penses" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"expenses:autres d\233penses", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"not:desc:a b" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"a b", [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"status:1" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Status -> Query
StatusQ Status
Cleared, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"status:*" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Status -> Query
StatusQ Status
Cleared, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"status:!" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Status -> Query
StatusQ Status
Pending, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"status:0" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Status -> Query
StatusQ Status
Unmarked, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"status:" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Status -> Query
StatusQ Status
Unmarked, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"payee:x" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text -> Either [Char] Query
payeeTag (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"x")
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"note:x" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (,[]) (Query -> (Query, [QueryOpt]))
-> Either [Char] Query -> Either [Char] (Query, [QueryOpt])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text -> Either [Char] Query
noteTag (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"x")
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"real:1" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Bool -> Query
Real Bool
True, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"date:2008" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Flex (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2008 Int
01 Int
01) (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Flex (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01), [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"date:from 2012/5/17" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Exact (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2012 Int
05 Int
17) Maybe EFDay
forall a. Maybe a
Nothing, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"date:20180101-201804" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Exact (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2018 Int
01 Int
01) (EFDay -> Maybe EFDay
forall a. a -> Maybe a
Just (EFDay -> Maybe EFDay) -> EFDay -> Maybe EFDay
forall a b. (a -> b) -> a -> b
$ Day -> EFDay
Flex (Day -> EFDay) -> Day -> EFDay
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2018 Int
04 Int
01), [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"inacct:a" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Query
Any, [Text -> QueryOpt
QueryOptInAcct Text
"a"])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"tag:a" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"a") Maybe Regexp
forall a. Maybe a
Nothing, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"tag:a=some value" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"a") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegexCI' Text
"some value"), [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"amt:<0" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (OrdPlus -> Quantity -> Query
Amt OrdPlus
Lt Quantity
0, [])
Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm Day
nulldate Text
"amt:>10000.10" Either [Char] (Query, [QueryOpt])
-> Either [Char] (Query, [QueryOpt]) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (Query, [QueryOpt]) -> Either [Char] (Query, [QueryOpt])
forall a b. b -> Either a b
Right (OrdPlus -> Quantity -> Query
Amt OrdPlus
AbsGt Quantity
10000.1, [])
,[Char] -> Assertion -> TestTree
testCase [Char]
"parseAmountQueryTerm" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"<0" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Lt,Quantity
0)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
">0" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Gt,Quantity
0)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
" > - 0 " Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Gt,Quantity
0)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
">10000.10" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsGt,Quantity
10000.1)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"=0.23" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsEq,Quantity
0.23)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"0.23" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
AbsEq,Quantity
0.23)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"<=+0.23" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
LtEq,Quantity
0.23)
Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"-0.23" Either [Char] (OrdPlus, Quantity)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (OrdPlus, Quantity) -> Either [Char] (OrdPlus, Quantity)
forall a b. b -> Either a b
Right (OrdPlus
Eq,(-Quantity
0.23))
Either [Char] (OrdPlus, Quantity) -> Assertion
forall b a. (HasCallStack, Eq b, Show b) => Either a b -> Assertion
assertLeft (Either [Char] (OrdPlus, Quantity) -> Assertion)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a b. (a -> b) -> a -> b
$ Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"-0,23"
Either [Char] (OrdPlus, Quantity) -> Assertion
forall b a. (HasCallStack, Eq b, Show b) => Either a b -> Assertion
assertLeft (Either [Char] (OrdPlus, Quantity) -> Assertion)
-> Either [Char] (OrdPlus, Quantity) -> Assertion
forall a b. (a -> b) -> a -> b
$ Text -> Either [Char] (OrdPlus, Quantity)
parseAmountQueryTerm Text
"=.23"
,[Char] -> Assertion -> TestTree
testCase [Char]
"queryStartDate" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
let small :: Maybe Day
small = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
01
big :: Maybe Day
big = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
02
Bool -> Query -> Maybe Day
queryStartDate Bool
False ([Query] -> Query
And [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small) Maybe EFDay
forall a. Maybe a
Nothing, DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
big) Maybe EFDay
forall a. Maybe a
Nothing]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
big
Bool -> Query -> Maybe Day
queryStartDate Bool
False ([Query] -> Query
And [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small) Maybe EFDay
forall a. Maybe a
Nothing, DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing Maybe EFDay
forall a. Maybe a
Nothing]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
small
Bool -> Query -> Maybe Day
queryStartDate Bool
False ([Query] -> Query
Or [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small) Maybe EFDay
forall a. Maybe a
Nothing, DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
big) Maybe EFDay
forall a. Maybe a
Nothing]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
small
Bool -> Query -> Maybe Day
queryStartDate Bool
False ([Query] -> Query
Or [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small) Maybe EFDay
forall a. Maybe a
Nothing, DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing Maybe EFDay
forall a. Maybe a
Nothing]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
forall a. Maybe a
Nothing
,[Char] -> Assertion -> TestTree
testCase [Char]
"queryEndDate" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
let small :: Maybe Day
small = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
01
big :: Maybe Day
big = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
02
Bool -> Query -> Maybe Day
queryEndDate Bool
False ([Query] -> Query
And [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small), DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
big)]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
small
Bool -> Query -> Maybe Day
queryEndDate Bool
False ([Query] -> Query
And [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small), DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing Maybe EFDay
forall a. Maybe a
Nothing]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
small
Bool -> Query -> Maybe Day
queryEndDate Bool
False ([Query] -> Query
Or [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small), DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
big)]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
big
Bool -> Query -> Maybe Day
queryEndDate Bool
False ([Query] -> Query
Or [DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Day
small), DateSpan -> Query
Date (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Maybe EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing Maybe EFDay
forall a. Maybe a
Nothing]) Maybe Day -> Maybe Day -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe Day
forall a. Maybe a
Nothing
,[Char] -> Assertion -> TestTree
testCase [Char]
"matchesAccount" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"b:c") Query -> Text -> Bool
`matchesAccount` Text
"a:bb:c:d"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"^a:b") Query -> Text -> Bool
`matchesAccount` Text
"c:a:b"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Int -> Query
Depth Int
2 Query -> Text -> Bool
`matchesAccount` Text
"a"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Int -> Query
Depth Int
2 Query -> Text -> Bool
`matchesAccount` Text
"a:b"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Int -> Query
Depth Int
2 Query -> Text -> Bool
`matchesAccount` Text
"a:b:c"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ DateSpan -> Query
Date DateSpan
nulldatespan Query -> Text -> Bool
`matchesAccount` Text
"a"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ DateSpan -> Query
Date2 DateSpan
nulldatespan Query -> Text -> Bool
`matchesAccount` Text
"a"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"a") Maybe Regexp
forall a. Maybe a
Nothing Query -> Text -> Bool
`matchesAccount` Text
"a"
,[Char] -> Assertion -> TestTree
testCase [Char]
"matchesAccountExtra" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
let tagq :: Query
tagq = Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegexCI' Text
"type") Maybe Regexp
forall a. Maybe a
Nothing
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe AccountType)
-> (Text -> [(Text, Text)]) -> Query -> Text -> Bool
matchesAccountExtra (Maybe AccountType -> Text -> Maybe AccountType
forall a b. a -> b -> a
const Maybe AccountType
forall a. Maybe a
Nothing) ([(Text, Text)] -> Text -> [(Text, Text)]
forall a b. a -> b -> a
const []) Query
tagq Text
"a"
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe AccountType)
-> (Text -> [(Text, Text)]) -> Query -> Text -> Bool
matchesAccountExtra (Maybe AccountType -> Text -> Maybe AccountType
forall a b. a -> b -> a
const Maybe AccountType
forall a. Maybe a
Nothing) ([(Text, Text)] -> Text -> [(Text, Text)]
forall a b. a -> b -> a
const [(Text
"type",Text
"")]) Query
tagq Text
"a"
,[Char] -> [TestTree] -> TestTree
testGroup [Char]
"matchesPosting" [
[Char] -> Assertion -> TestTree
testCase [Char]
"positive match on cleared posting status" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Status -> Query
StatusQ Status
Cleared) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pstatus=Cleared}
,[Char] -> Assertion -> TestTree
testCase [Char]
"negative match on cleared posting status" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Status -> Query
StatusQ Status
Cleared) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pstatus=Cleared}
,[Char] -> Assertion -> TestTree
testCase [Char]
"positive match on unmarked posting status" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Status -> Query
StatusQ Status
Unmarked) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pstatus=Unmarked}
,[Char] -> Assertion -> TestTree
testCase [Char]
"negative match on unmarked posting status" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Query -> Query
Not (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ Status -> Query
StatusQ Status
Unmarked) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pstatus=Unmarked}
,[Char] -> Assertion -> TestTree
testCase [Char]
"positive match on true posting status acquired from transaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Status -> Query
StatusQ Status
Cleared) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pstatus=Unmarked,ptransaction=Just nulltransaction{tstatus=Cleared}}
,[Char] -> Assertion -> TestTree
testCase [Char]
"real:1 on real posting" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Bool -> Query
Real Bool
True) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptype=RegularPosting}
,[Char] -> Assertion -> TestTree
testCase [Char]
"real:1 on virtual posting fails" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Bool -> Query
Real Bool
True) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptype=VirtualPosting}
,[Char] -> Assertion -> TestTree
testCase [Char]
"real:1 on balanced virtual posting fails" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Bool -> Query
Real Bool
True) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptype=BalancedVirtualPosting}
,[Char] -> Assertion -> TestTree
testCase [Char]
"acct:" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Query
Acct (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"'b") Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{paccount="'b"}
,[Char] -> Assertion -> TestTree
testCase [Char]
"tag:" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"a") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"r$")) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"foo") Maybe Regexp
forall a. Maybe a
Nothing) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptags=[("foo","")]}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"foo") Maybe Regexp
forall a. Maybe a
Nothing) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptags=[("foo","baz")]}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"foo") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"a")) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptags=[("foo","bar")]}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"foo") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"a$")) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptags=[("foo","bar")]}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
" foo ") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"a")) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptags=[("foo","bar")]}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"foo foo") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
" ar ba ")) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptags=[("foo foo","bar bar")]}
,[Char] -> Assertion -> TestTree
testCase [Char]
"a tag match on a posting also sees inherited tags" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"txntag") Maybe Regexp
forall a. Maybe a
Nothing) Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{ptransaction=Just nulltransaction{ttags=[("txntag","")]}}
,[Char] -> Assertion -> TestTree
testCase [Char]
"cur:" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
let toSym :: Text -> Query
toSym = (Query, [QueryOpt]) -> Query
forall a b. (a, b) -> a
fst ((Query, [QueryOpt]) -> Query)
-> (Text -> (Query, [QueryOpt])) -> Text -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> (Query, [QueryOpt]))
-> ((Query, [QueryOpt]) -> (Query, [QueryOpt]))
-> Either [Char] (Query, [QueryOpt])
-> (Query, [QueryOpt])
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either [Char] -> (Query, [QueryOpt])
forall a. [Char] -> a
error' (Query, [QueryOpt]) -> (Query, [QueryOpt])
forall a. a -> a
id (Either [Char] (Query, [QueryOpt]) -> (Query, [QueryOpt]))
-> (Text -> Either [Char] (Query, [QueryOpt]))
-> Text
-> (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Text -> Either [Char] (Query, [QueryOpt])
parseQueryTerm (Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
01) (Text -> Either [Char] (Query, [QueryOpt]))
-> (Text -> Text) -> Text -> Either [Char] (Query, [QueryOpt])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"cur:"Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Query
toSym Text
"$" Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pamount=mixedAmount $ usd 1}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Text -> Query
toSym Text
"\\$") Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pamount=mixedAmount $ usd 1}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Text -> Query
toSym Text
"shekels") Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pamount=mixedAmount nullamt{acommodity="shekels"}}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Text -> Query
toSym Text
"shek") Query -> Posting -> Bool
`matchesPosting` Posting
nullposting{pamount=mixedAmount nullamt{acommodity="shekels"}}
]
,[Char] -> Assertion -> TestTree
testCase [Char]
"matchesTransaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Query
Any Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"x x") Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction{tdescription="x"}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Query
Desc (Regexp -> Query) -> Regexp -> Query
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"x x") Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction{tdescription="x x"}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"foo") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"a")) Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction{ttags=[("foo","bar")]}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"payee") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"payee")) Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction{tdescription="payee|note"}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"note") (Regexp -> Maybe Regexp
forall a. a -> Maybe a
Just (Regexp -> Maybe Regexp) -> Regexp -> Maybe Regexp
forall a b. (a -> b) -> a -> b
$ Text -> Regexp
toRegex' Text
"note")) Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction{tdescription="payee|note"}
HasCallStack => [Char] -> Bool -> Assertion
[Char] -> Bool -> Assertion
assertBool [Char]
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$ (Regexp -> Maybe Regexp -> Query
Tag (Text -> Regexp
toRegex' Text
"postingtag") Maybe Regexp
forall a. Maybe a
Nothing) Query -> Transaction -> Bool
`matchesTransaction` Transaction
nulltransaction{tpostings=[nullposting{ptags=[("postingtag","")]}]}
]