-- ** Type 'Filter_Ord'
-data Filter_Ord o
- = Filter_Ord_Lt o
- | Filter_Ord_Le o
- | Filter_Ord_Gt o
- | Filter_Ord_Ge o
- | Filter_Ord_Eq o
- | Filter_Ord_Any
+data Order
+ = Lt -- ^ Lower than.
+ | Le -- ^ Lower or equal.
+ | Eq -- ^ Equal.
+ | Ge -- ^ Greater or equal.
+ | Gt -- ^ Greater than.
+ deriving (Data, Eq, Show, Typeable)
+
+data Filter_Ord o
+ = Filter_Ord Order o
+ | Filter_Ord_Any
deriving (Data, Eq, Show, Typeable)
instance Functor Filter_Ord where
fmap f x =
case x of
- Filter_Ord_Lt o -> Filter_Ord_Lt (f o)
- Filter_Ord_Le o -> Filter_Ord_Le (f o)
- Filter_Ord_Gt o -> Filter_Ord_Gt (f o)
- Filter_Ord_Ge o -> Filter_Ord_Ge (f o)
- Filter_Ord_Eq o -> Filter_Ord_Eq (f o)
+ Filter_Ord Lt o -> Filter_Ord Lt (f o)
+ Filter_Ord Le o -> Filter_Ord Le (f o)
+ Filter_Ord Eq o -> Filter_Ord Eq (f o)
+ Filter_Ord Ge o -> Filter_Ord Ge (f o)
+ Filter_Ord Gt o -> Filter_Ord Gt (f o)
Filter_Ord_Any -> Filter_Ord_Any
instance Ord o
- => Filter (Filter_Ord o) where
+ => Filter (Filter_Ord o) where
type Filter_Key (Filter_Ord o) = o
test f x =
case f of
- Filter_Ord_Lt o -> (<) x o
- Filter_Ord_Le o -> (<=) x o
- Filter_Ord_Gt o -> (>) x o
- Filter_Ord_Ge o -> (>=) x o
- Filter_Ord_Eq o -> (==) x o
+ Filter_Ord Lt o -> (<) x o
+ Filter_Ord Le o -> (<=) x o
+ Filter_Ord Eq o -> (==) x o
+ Filter_Ord Ge o -> (>=) x o
+ Filter_Ord Gt o -> (>) x o
Filter_Ord_Any -> True
simplify f =
Simplified $
Filter_Ord_Any -> Right True
_ -> Left f
instance Ord o
- => Filter (With_Interval (Filter_Ord o)) where
+ => Filter (With_Interval (Filter_Ord o)) where
type Filter_Key (With_Interval (Filter_Ord o)) = Interval o
test (With_Interval f) i =
let l = Interval.low i in
let h = Interval.high i in
case f of
- Filter_Ord_Lt o -> case compare (Interval.limit h) o of
+ Filter_Ord Lt o -> case compare (Interval.limit h) o of
LT -> True
EQ -> Interval.adherence h == Interval.Out
GT -> False
- Filter_Ord_Le o -> Interval.limit h <= o
- Filter_Ord_Gt o -> case compare (Interval.limit l) o of
+ Filter_Ord Le o -> Interval.limit h <= o
+ Filter_Ord Eq o -> Interval.limit l == o && Interval.limit h == o
+ Filter_Ord Ge o -> Interval.limit l >= o
+ Filter_Ord Gt o -> case compare (Interval.limit l) o of
LT -> False
EQ -> Interval.adherence l == Interval.Out
GT -> True
- Filter_Ord_Ge o -> Interval.limit l >= o
- Filter_Ord_Eq o -> Interval.limit l == o && Interval.limit h == o
Filter_Ord_Any -> True
simplify f =
Simplified $
| Not (Filter_Bool f)
| And (Filter_Bool f) (Filter_Bool f)
| Or (Filter_Bool f) (Filter_Bool f)
- deriving (Show)
-deriving instance Eq f => Eq (Filter_Bool f)
+ deriving (Eq, Show, Typeable)
instance Functor Filter_Bool where
fmap _ Any = Any
fmap f (Bool x) = Bool (f x)
traverse m (Not f) = Not <$> traverse m f
traverse m (And f0 f1) = And <$> traverse m f0 <*> traverse m f1
traverse m (Or f0 f1) = Or <$> traverse m f0 <*> traverse m f1
-instance Filter f => Filter (Filter_Bool f) where
+instance Filter f
+ => Filter (Filter_Bool f) where
type Filter_Key (Filter_Bool f) = Filter_Key f
test Any _ = True
test (Bool f) x = test f x
= Filter_Unit Filter_Text
deriving (Eq, Show, Typeable)
-instance Unit u => Filter (Filter_Unit u) where
+instance Unit u
+ => Filter (Filter_Unit u) where
type Filter_Key (Filter_Unit u) = u
test (Filter_Unit f) = test f . unit_text
simplify f =
-- ** Type 'Filter_Account'
-type Filter_Account
- = [Filter_Account_Section]
+data Filter_Account
+ = Filter_Account Order [Filter_Account_Section]
+ deriving (Eq, Show, Typeable)
data Filter_Account_Section
= Filter_Account_Section_Any
| Filter_Account_Section_Text Filter_Text
deriving (Eq, Show, Typeable)
-instance Filter Filter_Account where
- type Filter_Key Filter_Account = Account
- test f acct =
- comp f (NonEmpty.toList acct)
+instance Filter Filter_Account where
+ type Filter_Key Filter_Account = Account
+ test (Filter_Account ord flt) acct =
+ go ord (NonEmpty.toList acct) flt
where
- comp :: [Filter_Account_Section] -> [Account.Name] -> Bool
- comp [] [] = True
- comp [Filter_Account_Section_Many] _ = True
- comp [] _ = False
+ go :: Order -> [Account.Name] -> [Filter_Account_Section] -> Bool
+ go o [] [] =
+ case o of
+ Lt -> False
+ Le -> True
+ Eq -> True
+ Ge -> True
+ Gt -> False
+ go o _ [Filter_Account_Section_Many] =
+ case o of
+ Lt -> False
+ Le -> True
+ Eq -> True
+ Ge -> True
+ Gt -> False
+ go o [] _ =
+ case o of
+ Lt -> True
+ Le -> True
+ Eq -> False
+ Ge -> False
+ Gt -> False
{-
- comp (s:[]) (n:_) =
+ go o (s:[]) (n:_) =
case s of
Filter_Account_Section_Any -> True
Filter_Account_Section_Many -> True
Filter_Account_Section_Text m -> test m n
-}
- comp so@(s:ss) no@(n:ns) =
- case s of
- Filter_Account_Section_Any -> comp ss ns
- Filter_Account_Section_Many -> comp ss no || comp so ns
- Filter_Account_Section_Text m -> test m n && comp ss ns
- comp _ [] = False
+ go o no@(n:ns) fo@(f:fs) =
+ case f of
+ Filter_Account_Section_Any -> go o ns fs
+ Filter_Account_Section_Many -> go o no fs || go o ns fo
+ Filter_Account_Section_Text m -> test m n && go o ns fs
+ go o _ [] =
+ case o of
+ Lt -> False
+ Le -> False
+ Eq -> False
+ Ge -> True
+ Gt -> True
simplify flt =
case flt of
- [Filter_Account_Section_Many] -> Simplified $ Right True
- _ ->
- Simplified $
- case simplified $ go flt of
- Left [] -> Right True
- Left ff -> Left ff
- Right b -> Right b
+ Filter_Account o [Filter_Account_Section_Many] ->
+ Simplified $ Right $
+ case o of
+ Lt -> False
+ Le -> True
+ Eq -> True
+ Ge -> True
+ Gt -> False
+ Filter_Account o [] ->
+ Simplified $ Right $
+ case o of
+ Lt -> False
+ Le -> False
+ Eq -> False
+ Ge -> False
+ Gt -> True
+ Filter_Account o fa ->
+ Filter_Account o <$> go fa
where
- go :: Filter_Account -> Simplified Filter_Account
+ go :: [Filter_Account_Section] -> Simplified [Filter_Account_Section]
go f =
case f of
[] -> Simplified $ Left []
deriving instance Amount a => Show (Filter_Amount_Section a)
instance Amount a
- => Filter (Filter_Amount a) where
+ => Filter (Filter_Amount a) where
type Filter_Key (Filter_Amount a) = a
test f a =
Data.Foldable.all
| Filter_Date_Hour (Filter_Interval Int)
| Filter_Date_Minute (Filter_Interval Int)
| Filter_Date_Second (Filter_Interval Data.Fixed.Pico)
- deriving (Typeable)
-deriving instance Show (Filter_Date)
+ deriving (Eq, Show, Typeable)
-instance Filter Filter_Date where
- type Filter_Key Filter_Date = Date
+instance Filter Filter_Date where
+ type Filter_Key Filter_Date = Date
test (Filter_Date_UTC f) d = test f $ d
test (Filter_Date_Year f) d = test f $ Interval.Limited $ Date.year d
test (Filter_Date_Month f) d = test f $ Interval.Limited $ Date.month d
data Filter_Tag
= Filter_Tag_Name Filter_Text
| Filter_Tag_Value Filter_Text
- deriving (Typeable)
-deriving instance Show (Filter_Tag)
+ deriving (Eq, Show, Typeable)
-instance Filter Filter_Tag where
- type Filter_Key Filter_Tag = (Text, Text)
+instance Filter Filter_Tag where
+ type Filter_Key Filter_Tag = (Text, Text)
test (Filter_Tag_Name f) (x, _) = test f x
test (Filter_Tag_Value f) (_, x) = test f x
simplify f =
| Filter_Transaction_Date (Filter_Bool Filter_Date)
| Filter_Transaction_Tag (Filter_Bool Filter_Tag)
deriving (Typeable)
+deriving instance Transaction t => Eq (Filter_Transaction t)
deriving instance Transaction t => Show (Filter_Transaction t)
instance Transaction t
-- ** Type 'Filter_GL'
-data GL r
- => Filter_GL r
+data GL g
+ => Filter_GL g
= Filter_GL_Account Filter_Account
- | Filter_GL_Amount_Positive (Filter_Amount (GL_Amount r))
- | Filter_GL_Amount_Negative (Filter_Amount (GL_Amount r))
- | Filter_GL_Amount_Balance (Filter_Amount (GL_Amount r))
- | Filter_GL_Sum_Positive (Filter_Amount (GL_Amount r))
- | Filter_GL_Sum_Negative (Filter_Amount (GL_Amount r))
- | Filter_GL_Sum_Balance (Filter_Amount (GL_Amount r))
+ | Filter_GL_Amount_Positive (Filter_Amount (GL_Amount g))
+ | Filter_GL_Amount_Negative (Filter_Amount (GL_Amount g))
+ | Filter_GL_Amount_Balance (Filter_Amount (GL_Amount g))
+ | Filter_GL_Sum_Positive (Filter_Amount (GL_Amount g))
+ | Filter_GL_Sum_Negative (Filter_Amount (GL_Amount g))
+ | Filter_GL_Sum_Balance (Filter_Amount (GL_Amount g))
deriving (Typeable)
-deriving instance GL r => Eq (Filter_GL r)
-deriving instance GL r => Show (Filter_GL r)
+deriving instance GL g => Eq (Filter_GL g)
+deriving instance GL g => Show (Filter_GL g)
-instance GL g
- => Filter (Filter_GL g) where
+instance GL g
+ => Filter (Filter_GL g) where
type Filter_Key (Filter_GL g) = g
test (Filter_GL_Account f) g =
test f $ gl_account g
=> ParsecT s u m (o -> Filter_Ord o)
filter_ord =
R.choice_try
- [ R.string "=" >> return Filter_Ord_Eq
- , R.string "<=" >> return Filter_Ord_Le
- , R.string ">=" >> return Filter_Ord_Ge
- , R.string "<" >> return Filter_Ord_Lt
- , R.string ">" >> return Filter_Ord_Gt
+ [ R.string "=" >> return (Filter_Ord Eq)
+ , R.string "<=" >> return (Filter_Ord Le) -- NOTE: before "<"
+ , R.string ">=" >> return (Filter_Ord Ge) -- NOTE: before ">"
+ , R.string "<" >> return (Filter_Ord Lt)
+ , R.string ">" >> return (Filter_Ord Gt)
]
filter_ord_operator
=> ParsecT s u m Filter_Account
filter_account = do
R.notFollowedBy $ R.space_horizontal
- R.many1_separated filter_account_section $
- R.char account_section_sep
+ Filter_Ord o () <-
+ R.option (Filter_Ord Eq ()) $ R.try $
+ (\f -> f ()) <$> filter_ord
+ fmap (Filter_Account o) $
+ R.many1_separated filter_account_section $
+ R.char account_section_sep
filter_account_operator
:: Stream s m Char
, jump [ "C" ] filter_amount_operator
( Filter.Filter_Balance_Negative
<$> filter_amount )
- , jump [ "B", "" ] filter_amount_operator
+ , jump [ "B" ] filter_amount_operator
( Filter.Filter_Balance_Amount
<$> filter_amount )
, return
Interval.Sieve.intersection s $
Interval.Sieve.singleton $
case to of
- Filter_Ord_Lt o -> fromJust $ Interval.interval (Interval.low bounds) (Interval.Limit Interval.Out o)
- Filter_Ord_Le o -> fromJust $ Interval.interval (Interval.low bounds) (Interval.Limit Interval.In o)
- Filter_Ord_Eq o -> Interval.point o
- Filter_Ord_Ge o -> fromJust $ Interval.interval (Interval.Limit Interval.In o) (Interval.high bounds)
- Filter_Ord_Gt o -> fromJust $ Interval.interval (Interval.Limit Interval.Out o) (Interval.high bounds)
+ Filter_Ord Lt o -> fromJust $ Interval.interval (Interval.low bounds) (Interval.Limit Interval.Out o)
+ Filter_Ord Le o -> fromJust $ Interval.interval (Interval.low bounds) (Interval.Limit Interval.In o)
+ Filter_Ord Eq o -> Interval.point o
+ Filter_Ord Ge o -> fromJust $ Interval.interval (Interval.Limit Interval.In o) (Interval.high bounds)
+ Filter_Ord Gt o -> fromJust $ Interval.interval (Interval.Limit Interval.Out o) (Interval.high bounds)
Filter_Ord_Any -> bounds
Filter_Date_Year (Filter_Interval_In i) ->
Interval.Sieve.intersection s $
[ "test" ~: TestList
[ "Filter_Account" ~: TestList
[ "A A" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "A")
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ ])
(("A":|[]::Account))
, "* A" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Any
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Any
+ ])
(("A":|[]::Account))
, ": A" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Many
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Many
+ ])
(("A":|[]::Account))
, ":A A" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Many
- , Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "A")
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Many
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ ])
(("A":|[]::Account))
, "A: A" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "A")
- , Filter.Filter_Account_Section_Many
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Many
+ ])
(("A":|[]::Account))
, "A: A:B" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "A")
- , Filter.Filter_Account_Section_Many
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Many
+ ])
(("A":|"B":[]::Account))
, "A:B A:B" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "A")
- , Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "B")
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "B")
+ ])
(("A":|"B":[]::Account))
, "A::B A:B" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "A")
- , Filter.Filter_Account_Section_Many
- , Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "B")
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Many
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "B")
+ ])
(("A":|"B":[]::Account))
, ":B: A:B:C" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Many
- , Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "B")
- , Filter.Filter_Account_Section_Many
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Many
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "B")
+ , Filter.Filter_Account_Section_Many
+ ])
(("A":|"B":"C":[]::Account))
, ":C A:B:C" ~?
- Filter.test
- [ Filter.Filter_Account_Section_Many
- , Filter.Filter_Account_Section_Text
- (Filter.Filter_Text_Exact "C")
- ]
+ Filter.test
+ (Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Many
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "C")
+ ])
(("A":|"B":"C":[]::Account))
+ , "<A:B:C::D A:B" ~?
+ Filter.test
+ (Filter.Filter_Account Filter.Lt
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "B")
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "C")
+ , Filter.Filter_Account_Section_Many
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "D")
+ ])
+ (("A":|"B":[]::Account))
+ , ">A:B:C::D A:B:C:CC:CCC:D:E" ~?
+ Filter.test
+ (Filter.Filter_Account Filter.Gt
+ [ Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "B")
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "C")
+ , Filter.Filter_Account_Section_Many
+ , Filter.Filter_Account_Section_Text
+ (Filter.Filter_Text_Exact "D")
+ ])
+ (("A":|"B":"C":"CC":"CCC":"D":"E":[]::Account))
]
, "Filter_Bool" ~: TestList
[ "Any A" ~?
, "Filter_Ord" ~: TestList
[ "0 < (1, 2)" ~?
Filter.test
- (Filter.With_Interval $ Filter.Filter_Ord_Gt (0::Integer))
+ (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (0::Integer))
(fromJust $ (Lib.Interval.<=..<=) 1 2)
, "(-2, -1) < 0" ~?
Filter.test
- (Filter.With_Interval $ Filter.Filter_Ord_Lt (0::Integer))
+ (Filter.With_Interval $ Filter.Filter_Ord Filter.Lt (0::Integer))
(fromJust $ (Lib.Interval.<=..<=) (-2) (-1))
, "not (1 < (0, 2))" ~?
(not $ Filter.test
- (Filter.With_Interval $ Filter.Filter_Ord_Gt (1::Integer))
+ (Filter.With_Interval $ Filter.Filter_Ord Filter.Gt (1::Integer))
(fromJust $ (Lib.Interval.<=..<=) 0 2))
]
]
(Filter.Read.filter_account <* P.eof)
() "" ("*"::Text)])
~?=
- [ [Filter.Filter_Account_Section_Any]
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Any ]
]
, "A" ~:
(Data.Either.rights $
(Filter.Read.filter_account <* P.eof)
() "" ("A"::Text)])
~?=
- [ [Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")]
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A") ]
]
, "AA" ~:
(Data.Either.rights $
(Filter.Read.filter_account <* P.eof)
() "" ("AA"::Text)])
~?=
- [ [Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "AA")]
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "AA") ]
]
, "::A" ~:
(Data.Either.rights $
(Filter.Read.filter_account <* P.eof)
() "" ("::A"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Many
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Many
, Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
]
]
(Filter.Read.filter_account <* P.eof)
() "" (":A"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Many
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Many
, Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
]
]
(Filter.Read.filter_account <* P.eof)
() "" ("A:"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
, Filter.Filter_Account_Section_Many
]
]
(Filter.Read.filter_account <* P.eof)
() "" ("A::"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
, Filter.Filter_Account_Section_Many
]
]
(Filter.Read.filter_account <* P.eof)
() "" ("A:B"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
- , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B") ]
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
+ ]
]
, "A::B" ~:
(Data.Either.rights $
(Filter.Read.filter_account <* P.eof)
() "" ("A::B"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
, Filter.Filter_Account_Section_Many
, Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
]
(Filter.Read.filter_account <* P.eof)
() "" ("A:::B"::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
, Filter.Filter_Account_Section_Many
, Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
]
(Filter.Read.filter_account <* P.char ' ' <* P.eof)
() "" ("A: "::Text)])
~?=
- [ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ [ Filter.Filter_Account Filter.Eq
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
, Filter.Filter_Account_Section_Many
]
]
+ , "<=A:B" ~:
+ (Data.Either.rights $
+ [P.runParser
+ (Filter.Read.filter_account <* P.eof)
+ () "" ("<=A:B"::Text)])
+ ~?=
+ [ Filter.Filter_Account Filter.Le
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
+ ]
+ ]
+ , ">=A:B" ~:
+ (Data.Either.rights $
+ [P.runParser
+ (Filter.Read.filter_account <* P.eof)
+ () "" (">=A:B"::Text)])
+ ~?=
+ [ Filter.Filter_Account Filter.Ge
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
+ ]
+ ]
+ , "<A:B" ~:
+ (Data.Either.rights $
+ [P.runParser
+ (Filter.Read.filter_account <* P.eof)
+ () "" ("<A:B"::Text)])
+ ~?=
+ [ Filter.Filter_Account Filter.Lt
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
+ ]
+ ]
+ , ">A:B" ~:
+ (Data.Either.rights $
+ [P.runParser
+ (Filter.Read.filter_account <* P.eof)
+ () "" (">A:B"::Text)])
+ ~?=
+ [ Filter.Filter_Account Filter.Gt
+ [ Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "A")
+ , Filter.Filter_Account_Section_Text (Filter.Filter_Text_Exact "B")
+ ]
+ ]
]
, "filter_bool" ~: TestList
[ "( E )" ~: