Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Database.Persist.Sql.Lifted.Filter
Synopsis
- data Filter record
- (==.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (<.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (>.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (<=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (>=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v
- (/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v
- (||.) :: [Filter v] -> [Filter v] -> [Filter v]
Type
Filters which are available for select
, updateWhere
and
deleteWhere
. Each filter constructor specifies the field being
filtered on, the type of comparison applied (equals, not equals, etc)
and the argument for the comparison.
Persistent users use combinators to create these.
Note that it's important to be careful about the PersistFilter
that
you are using, if you use this directly. For example, using the In
PersistFilter
requires that you have an array- or list-shaped
EntityField
. It is possible to construct values using this that will
create malformed runtime values.
Equality
(==.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 #
Check for equality.
Examples
selectSPJ :: MonadIO m => ReaderT SqlBackend m [Entity User] selectSPJ = selectList [UserName ==. "SPJ" ] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+
(!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 #
Non-equality check.
Examples
selectSimon :: MonadIO m => ReaderT SqlBackend m [Entity User] selectSimon = selectList [UserName !=. "SPJ" ] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+
Less & greater
(<.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 #
Less-than check.
Examples
selectLessAge :: MonadIO m => ReaderT SqlBackend m [Entity User] selectLessAge = selectList [UserAge <. 41 ] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+
(>.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 #
Greater-than check.
Examples
selectGreaterAge :: MonadIO m => ReaderT SqlBackend m [Entity User] selectGreaterAge = selectList [UserAge >. 40 ] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+
(<=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 #
Less-than or equal check.
Examples
selectLessEqualAge :: MonadIO m => ReaderT SqlBackend m [Entity User] selectLessEqualAge = selectList [UserAge <=. 40 ] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+
(>=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 #
Greater-than or equal check.
Examples
selectGreaterEqualAge :: MonadIO m => ReaderT SqlBackend m [Entity User] selectGreaterEqualAge = selectList [UserAge >=. 41 ] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+
Lists
(<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v infix 4 #
Check if value is in given list.
Examples
selectUsers :: MonadIO m => ReaderT SqlBackend m [Entity User] selectUsers = selectList [UserAge <-. [40, 41]] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+
selectSPJ :: MonadIO m => ReaderT SqlBackend m [Entity User] selectSPJ = selectList [UserAge <-. [40]] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+
(/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v infix 4 #
Check if value is not in given list.
Examples
selectSimon :: MonadIO m => ReaderT SqlBackend m [Entity User] selectSimon = selectList [UserAge /<-. [40]] []
The above query when applied on dataset-1, will produce this:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+
Disjunction
(||.) :: [Filter v] -> [Filter v] -> [Filter v] infixl 3 #
The OR of two lists of filters. For example:
selectList ([ PersonAge >. 25 , PersonAge <. 30 ] ||. [ PersonIncome >. 15000 , PersonIncome <. 25000 ]) []
will filter records where a person's age is between 25 and 30 or a person's income is between (15000 and 25000).
If you are looking for an (&&.)
operator to do (A AND B AND (C OR D))
you can use the (++)
operator instead as there is no (&&.)
. For
example:
selectList ([ PersonAge >. 25 , PersonAge <. 30 ] ++ ([PersonCategory ==. 1] ||. [PersonCategory ==. 5])) []
will filter records where a person's age is between 25 and 30 and (person's category is either 1 or 5).