persistent-2.7.0: Type-safe, multi-backend data serialization.

Safe HaskellNone
LanguageHaskell98

Database.Persist

Contents

Synopsis

Documentation

Reference Schema & Dataset

All the combinators present here will be explained based on this schema:

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
User
    name String
    age Int
    deriving Show
|]

and this dataset. The examples below will refer to this as dataset-1.

+-----+-----+-----+
|id   |name |age  |
+-----+-----+-----+
|1    |SPJ  |40   |
+-----+-----+-----+
|2    |Simon|41   |
+-----+-----+-----+

Query update combinators

(=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 Source #

Assign a field a value.

Example usage

updateAge :: MonadIO m => ReaderT SqlBackend m ()
updateAge = updateWhere [UserName ==. "SPJ" ] [UserAge =. 45]

Similar to updateWhere which is shown in the above example you can use other functions present in the module Database.Persist.Class. Note that the first parameter of updateWhere is [Filter val] and second parameter is [Update val]. By comparing this with the type of ==. and =., you can see that they match up in the above usage.

The above query when applied on dataset-1, will produce this:

+-----+-----+--------+
|id   |name |age     |
+-----+-----+--------+
|1    |SPJ  |40 -> 45|
+-----+-----+--------+
|2    |Simon|41      |
+-----+-----+--------+

(+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 Source #

Assign a field by addition (+=).

Example usage

addAge :: MonadIO m => ReaderT SqlBackend m ()
addAge = updateWhere [UserName ==. "SPJ" ] [UserAge +=. 1]

The above query when applied on dataset-1, will produce this:

+-----+-----+---------+
|id   |name |age      |
+-----+-----+---------+
|1    |SPJ  |40 -> 41 |
+-----+-----+---------+
|2    |Simon|41       |
+-----+-----+---------+

(-=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 Source #

Assign a field by subtraction (-=).

Example usage

subtractAge :: MonadIO m => ReaderT SqlBackend m ()
subtractAge = updateWhere [UserName ==. "SPJ" ] [UserAge -=. 1]

The above query when applied on dataset-1, will produce this:

+-----+-----+---------+
|id   |name |age      |
+-----+-----+---------+
|1    |SPJ  |40 -> 39 |
+-----+-----+---------+
|2    |Simon|41       |
+-----+-----+---------+

(*=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 Source #

Assign a field by multiplication (*=).

Example usage

multiplyAge :: MonadIO m => ReaderT SqlBackend m ()
multiplyAge = updateWhere [UserName ==. "SPJ" ] [UserAge *=. 2]

The above query when applied on dataset-1, will produce this:

+-----+-----+--------+
|id   |name |age     |
+-----+-----+--------+
|1    |SPJ  |40 -> 80|
+-----+-----+--------+
|2    |Simon|41      |
+-----+-----+--------+

(/=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 Source #

Assign a field by division (/=).

Example usage

divideAge :: MonadIO m => ReaderT SqlBackend m ()
divideAge = updateWhere [UserName ==. "SPJ" ] [UserAge /=. 2]

The above query when applied on dataset-1, will produce this:

+-----+-----+---------+
|id   |name |age      |
+-----+-----+---------+
|1    |SPJ  |40 -> 20 |
+-----+-----+---------+
|2    |Simon|41       |
+-----+-----+---------+

Query filter combinators

(==.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 Source #

Check for equality.

Example usage

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 Source #

Non-equality check.

Example usage

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   |
+-----+-----+-----+

(<.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 Source #

Less-than check.

Example usage

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 Source #

Greater-than check.

Example usage

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 Source #

Less-than or equal check.

Example usage

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 Source #

Greater-than or equal check.

Example usage

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   |
+-----+-----+-----+

(<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v infix 4 Source #

Check if value is in given list.

Example usage

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 Source #

Check if value is not in given list.

Example usage

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   |
+-----+-----+-----+

(||.) :: forall v. [Filter v] -> [Filter v] -> [Filter v] infixl 3 Source #

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).

JSON Utilities

listToJSON :: [PersistValue] -> Text Source #

Convert list of PersistValues into textual representation of JSON object. This is a type-constrained synonym for toJsonText.

mapToJSON :: [(Text, PersistValue)] -> Text Source #

Convert map (list of tuples) into textual representation of JSON object. This is a type-constrained synonym for toJsonText.

toJsonText :: ToJSON j => j -> Text Source #

A more general way to convert instances of ToJSON type class to strict text Text.

getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)] Source #

FIXME Add documentation to that.

Other utilities

limitOffsetOrder :: PersistEntity val => [SelectOpt val] -> (Int, Int, [SelectOpt val]) Source #

FIXME What's this exactly?