esqueleto-3.2.2: Type-safe EDSL for SQL queries on persistent backends.

Safe HaskellNone
LanguageHaskell2010

Database.Esqueleto

Contents

Description

The esqueleto EDSL (embedded domain specific language). This module replaces Database.Persist, so instead of importing that module you should just import this one:

-- For a module using just esqueleto.
import Database.Esqueleto

If you need to use persistent's default support for queries as well, either import it qualified:

-- For a module that mostly uses esqueleto.
import Database.Esqueleto
import qualified Database.Persist as P

or import esqueleto itself qualified:

-- For a module that uses esqueleto just on some queries.
import Database.Persist
import qualified Database.Esqueleto as E

Other than identifier name clashes, esqueleto does not conflict with persistent in any way.

Synopsis

Setup

If you're already using persistent, then you're ready to use esqueleto, no further setup is needed. If you're just starting a new project and would like to use esqueleto, take a look at persistent's book first (http://www.yesodweb.com/book/persistent) to learn how to define your schema.

Introduction

The main goals of esqueleto are to:

  • Be easily translatable to SQL. When you take a look at a esqueleto query, you should be able to know exactly how the SQL query will end up. (As opposed to being a relational algebra EDSL such as HaskellDB, which is non-trivial to translate into SQL.)
  • Support the most widely used SQL features. We'd like you to be able to use esqueleto for all of your queries, no exceptions. Send a pull request or open an issue on our project page (https://github.com/prowdsponsor/esqueleto) if there's anything missing that you'd like to see.
  • Be as type-safe as possible. We strive to provide as many type checks as possible. If you get bitten by some invalid code that type-checks, please open an issue on our project page so we can take a look.

However, it is not a goal to be able to write portable SQL. We do not try to hide the differences between DBMSs from you, and esqueleto code that works for one database may not work on another. This is a compromise we have to make in order to give you as much control over the raw SQL as possible without losing too much convenience. This also means that you may type-check a query that doesn't work on your DBMS.

Getting started

We like clean, easy-to-read EDSLs. However, in order to achieve this goal we've used a lot of type hackery, leading to some hard-to-read type signatures. On this section, we'll try to build some intuition about the syntax.

For the following examples, we'll use this example schema:

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persist|
  Person
    name String
    age Int Maybe
    deriving Eq Show
  BlogPost
    title String
    authorId PersonId
    deriving Eq Show
  Follow
    follower PersonId
    followed PersonId
    deriving Eq Show
|]

Most of esqueleto was created with SELECT statements in mind, not only because they're the most common but also because they're the most complex kind of statement. The most simple kind of SELECT would be:

SELECT *
FROM Person

In esqueleto, we may write the same query above as:

do people <- select $
             from $ \person -> do
             return person
   liftIO $ mapM_ (putStrLn . personName . entityVal) people

The expression above has type SqlPersist m (), while people has type [Entity Person]. The query above will be translated into exactly the same query we wrote manually, but instead of SELECT * it will list all entity fields (using * is not robust). Note that esqueleto knows that we want an Entity Person just because of the personName that we're printing later.

However, most of the time we need to filter our queries using WHERE. For example:

SELECT *
FROM Person
WHERE Person.name = "John"

In esqueleto, we may write the same query above as:

select $
from $ \p -> do
where_ (p ^. PersonName ==. val "John")
return p

Although esqueleto's code is a bit more noisy, it's has almost the same structure (save from the return). The (^.) operator is used to project a field from an entity. The field name is the same one generated by persistent's Template Haskell functions. We use val to lift a constant Haskell value into the SQL query.

Another example would be:

SELECT *
FROM Person
WHERE Person.age >= 18

In esqueleto, we may write the same query above as:

select $
from $ \p -> do
where_ (p ^. PersonAge >=. just (val 18))
return p

Since age is an optional Person field, we use just to lift val 18 :: SqlExpr (Value Int) into just (val 18) :: SqlExpr (Value (Maybe Int)).

Implicit joins are represented by tuples. For example, to get the list of all blog posts and their authors, we could write:

SELECT BlogPost.*, Person.*
FROM BlogPost, Person
WHERE BlogPost.authorId = Person.id
ORDER BY BlogPost.title ASC

In esqueleto, we may write the same query above as:

select $
from $ \(b, p) -> do
where_ (b ^. BlogPostAuthorId ==. p ^. PersonId)
orderBy [asc (b ^. BlogPostTitle)]
return (b, p)

However, you may want your results to include people who don't have any blog posts as well using a LEFT OUTER JOIN:

SELECT Person.*, BlogPost.*
FROM Person LEFT OUTER JOIN BlogPost
ON Person.id = BlogPost.authorId
ORDER BY Person.name ASC, BlogPost.title ASC

In esqueleto, we may write the same query above as:

select $
from $ \(p `LeftOuterJoin` mb) -> do
on (just (p ^. PersonId) ==. mb ?. BlogPostAuthorId)
orderBy [asc (p ^. PersonName), asc (mb ?. BlogPostTitle)]
return (p, mb)

On a LEFT OUTER JOIN the entity on the right hand side may not exist (i.e. there may be a Person without any BlogPosts), so while p :: SqlExpr (Entity Person), we have mb :: SqlExpr (Maybe (Entity BlogPost)). The whole expression above has type SqlPersist m [(Entity Person, Maybe (Entity BlogPost))]. Instead of using (^.), we used (?.) to project a field from a Maybe (Entity a).

We are by no means limited to joins of two tables, nor by joins of different tables. For example, we may want a list of the Follow entity:

SELECT P1.*, Follow.*, P2.*
FROM Person AS P1
INNER JOIN Follow ON P1.id = Follow.follower
INNER JOIN Person AS P2 ON P2.id = Follow.followed

In esqueleto, we may write the same query above as:

select $
from $ \(p1 `InnerJoin` f `InnerJoin` p2) -> do
on (p1 ^. PersonId ==. f ^. FollowFollower)
on (p2 ^. PersonId ==. f ^. FollowFollowed)
return (p1, f, p2)

We also currently support UPDATE and DELETE statements. For example:

do update $ \p -> do
     set p [ PersonName =. val "João" ]
     where_ (p ^. PersonName ==. val "Joao")
   delete $
     from $ \p -> do
     where_ (p ^. PersonAge <. just (val 14))

The results of queries can also be used for insertions. In SQL, we might write the following, inserting a new blog post for every user:

INSERT INTO BlogPost
SELECT ('Group Blog Post', id)
FROM Person

In esqueleto, we may write the same query above as:

 insertSelect $ from $ \p->
 return $ BlogPost <# "Group Blog Post" <&> (p ^. PersonId)

Individual insertions can be performed through Persistent's insert function, reexported for convenience.

esqueleto's Language

where_ :: SqlExpr (Value Bool) -> SqlQuery () Source #

WHERE clause: restrict the query's result.

on :: SqlExpr (Value Bool) -> SqlQuery () Source #

An ON clause, useful to describe how two tables are related. Cross joins and tuple-joins do not need an on clause, but InnerJoin and the various outer joins do.

If you don't include an on clause (or include too many!) then a runtime exception will be thrown.

As an example, consider this simple join:

select $
from $ \(foo `InnerJoin` bar) -> do
  on (foo ^. FooId ==. bar ^. BarFooId)
  ...

We need to specify the clause for joining the two columns together. If we had this:

select $
from $ \(foo `CrossJoin` bar) -> do
  ...

Then we can safely omit the on clause, because the cross join will make pairs of all records possible.

You can do multiple on clauses in a query. This query joins three tables, and has two on clauses:

select $
from $ \(foo `InnerJoin` bar `InnerJoin` baz) -> do
  on (baz ^. BazId ==. bar ^. BarBazId)
  on (foo ^. FooId ==. bar ^. BarFooId)
  ...

Old versions of esqueleto required that you provide the on clauses in reverse order. This restriction has been lifted - you can now provide on clauses in any order, and the SQL should work itself out. The above query is now totally equivalent to this:

select $
from $ \(foo `InnerJoin` bar `InnerJoin` baz) -> do
  on (foo ^. FooId ==. bar ^. BarFooId)
  on (baz ^. BazId ==. bar ^. BarBazId)
  ...

groupBy :: ToSomeValues a => a -> SqlQuery () Source #

GROUP BY clause. You can enclose multiple columns in a tuple.

select $ from \(foo `InnerJoin` bar) -> do
  on (foo ^. FooBarId ==. bar ^. BarId)
  groupBy (bar ^. BarId, bar ^. BarName)
  return (bar ^. BarId, bar ^. BarName, countRows)

With groupBy you can sort by aggregate functions, like so (we used let to restrict the more general countRows to SqlSqlExpr (Value Int) to avoid ambiguity---the second use of countRows has its type restricted by the :: Int below):

r <- select $ from \(foo `InnerJoin` bar) -> do
  on (foo ^. FooBarId ==. bar ^. BarId)
  groupBy $ bar ^. BarName
  let countRows' = countRows
  orderBy [asc countRows']
  return (bar ^. BarName, countRows')
forM_ r $ \(Value name, Value count) -> do
  print name
  print (count :: Int)

orderBy :: [SqlExpr OrderBy] -> SqlQuery () Source #

ORDER BY clause. See also asc and desc.

Multiple calls to orderBy get concatenated on the final query, including distinctOnOrderBy.

rand :: SqlExpr OrderBy Source #

Deprecated: Since 2.6.0: rand ordering function is not uniform across all databases! To avoid accidental partiality it will be removed in the next major version.

ORDER BY random() clause.

Since: 1.3.10

asc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #

Ascending order of this field or SqlExpression.

desc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #

Descending order of this field or SqlExpression.

limit :: Int64 -> SqlQuery () Source #

LIMIT. Limit the number of returned rows.

offset :: Int64 -> SqlQuery () Source #

OFFSET. Usually used with limit.

distinct :: SqlQuery a -> SqlQuery a Source #

DISTINCT. Change the current SELECT into SELECT DISTINCT. For example:

select $ distinct $
  from \foo -> do
  ...

Note that this also has the same effect:

select $
  from \foo -> do
  distinct (return ())
  ...

Since: 2.2.4

distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a Source #

DISTINCT ON. Change the current SELECT into SELECT DISTINCT ON (SqlExpressions). For example:

select $
  from \foo ->
  distinctOn [don (foo ^. FooName), don (foo ^. FooState)] $ do
  ...

You can also chain different calls to distinctOn. The above is equivalent to:

select $
  from \foo ->
  distinctOn [don (foo ^. FooName)] $
  distinctOn [don (foo ^. FooState)] $ do
  ...

Each call to distinctOn adds more SqlExpressions. Calls to distinctOn override any calls to distinct.

Note that PostgreSQL requires the SqlExpressions on DISTINCT ON to be the first ones to appear on a ORDER BY. This is not managed automatically by esqueleto, keeping its spirit of trying to be close to raw SQL.

Supported by PostgreSQL only.

Since: 2.2.4

don :: SqlExpr (Value a) -> SqlExpr DistinctOn Source #

Erase an SqlExpression's type so that it's suitable to be used by distinctOn.

Since: 2.2.4

distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a Source #

A convenience function that calls both distinctOn and orderBy. In other words,

distinctOnOrderBy [asc foo, desc bar, desc quux] $ do
  ...

is the same as:

distinctOn [don foo, don  bar, don  quux] $ do
  orderBy  [asc foo, desc bar, desc quux]
  ...

Since: 2.2.4

having :: SqlExpr (Value Bool) -> SqlQuery () Source #

HAVING.

Since: 1.2.2

locking :: LockingKind -> SqlQuery () Source #

Add a locking clause to the query. Please read LockingKind documentation and your RDBMS manual.

If multiple calls to locking are made on the same query, the last one is used.

Since: 2.2.7

sub_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) Source #

Deprecated: sub_select sub_select is an unsafe function to use. If used with a SqlQuery that returns 0 results, then it may return NULL despite not mentioning Maybe in the return type. If it returns more than 1 result, then it will throw a SQL error. Instead, consider using one of the following alternatives: - subSelect: attaches a LIMIT 1 and the Maybe return type, totally safe. - subSelectMaybe: Attaches a LIMIT 1, useful for a query that already has a Maybe in the return type. - subSelectCount: Performs a count of the query - this is always safe. - subSelectUnsafe: Performs no checks or guarantees. Safe to use with countRows and friends.

Execute a subquery SELECT in an SqlExpression. Returns a simple value so should be used only when the SELECT query is guaranteed to return just one row.

Deprecated in 3.2.0.

(^.) :: forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) infixl 9 Source #

Project a field of an entity.

(?.) :: (PersistEntity val, PersistField typ) => SqlExpr (Maybe (Entity val)) -> EntityField val typ -> SqlExpr (Value (Maybe typ)) Source #

Project a field of an entity that may be null.

val :: PersistField typ => typ -> SqlExpr (Value typ) Source #

Lift a constant value from Haskell-land to the query.

isNothing :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool) Source #

IS NULL comparison.

just :: SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ)) Source #

Analogous to Just, promotes a value of type typ into one of type Maybe typ. It should hold that val . Just === just . val.

nothing :: SqlExpr (Value (Maybe typ)) Source #

NULL value.

joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (Value (Maybe typ)) Source #

Join nested Maybes in a Value into one. This is useful when calling aggregate functions on nullable fields.

withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a Source #

Project an SqlExpression that may be null, guarding against null cases.

countRows :: Num a => SqlExpr (Value a) Source #

COUNT(*) value.

count :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a) Source #

COUNT.

countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a) Source #

COUNT(DISTINCT x).

Since: 2.4.1

(==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(>=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(>.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(<=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(<.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(!=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

between :: PersistField a => SqlExpr (Value a) -> (SqlExpr (Value a), SqlExpr (Value a)) -> SqlExpr (Value Bool) Source #

BETWEEN.

@since: 3.1.0

(+.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 6 Source #

(-.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 6 Source #

(/.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 7 Source #

(*.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 7 Source #

random_ :: (PersistField a, Num a) => SqlExpr (Value a) Source #

Deprecated: Since 2.6.0: random_ is not uniform across all databases! Please use a specific one such as random_, random_, or random_

castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) Source #

Allow a number of one type to be used as one of another type via an implicit cast. An explicit cast is not made, this function changes only the types on the Haskell side.

Caveat: Trying to use castNum from Double to Int will not result in an integer, the original fractional number will still be used! Use round_, ceiling_ or floor_ instead.

Safety: This operation is mostly safe due to the Num constraint between the types and the fact that RDBMSs usually allow numbers of different types to be used interchangeably. However, there may still be issues with the query not being accepted by the RDBMS or persistent not being able to parse it.

Since: 2.2.9

castNumM :: (Num a, Num b) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b)) Source #

Same as castNum, but for nullable values.

Since: 2.2.9

coalesce :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value (Maybe a)) Source #

COALESCE function. Evaluates the arguments in order and returns the value of the first non-NULL SqlExpression, or NULL (Nothing) otherwise. Some RDBMSs (such as SQLite) require at least two arguments; please refer to the appropriate documentation.

Since: 1.4.3

coalesceDefault :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

Like coalesce, but takes a non-nullable SqlExpression placed at the end of the SqlExpression list, which guarantees a non-NULL result.

Since: 1.4.3

lower_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) Source #

LOWER function.

like :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) infixr 2 Source #

LIKE operator.

ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) infixr 2 Source #

ILIKE operator (case-insensitive LIKE).

Supported by PostgreSQL only.

Since: 2.2.3

(%) :: SqlString s => SqlExpr (Value s) Source #

The string %. May be useful while using like and concatenation (concat_ or ++., depending on your database). Note that you always have to type the parenthesis, for example:

name `like` (%) ++. val "John" ++. (%)

concat_ :: SqlString s => [SqlExpr (Value s)] -> SqlExpr (Value s) Source #

The CONCAT function with a variable number of parameters. Supported by MySQL and PostgreSQL.

(++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value s) infixr 5 Source #

The || string concatenation operator (named after Haskell's ++ in order to avoid naming clash with ||.). Supported by SQLite and PostgreSQL.

castString :: (SqlString s, SqlString r) => SqlExpr (Value s) -> SqlExpr (Value r) Source #

Cast a string type into Text. This function is very useful if you want to use newtypes, or if you want to apply functions such as like to strings of different types.

Safety: This is a slightly unsafe function, especially if you have defined your own instances of SqlString. Also, since Maybe is an instance of SqlString, it's possible to turn a nullable value into a non-nullable one. Avoid using this function if possible.

subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) Source #

Execute a subquery SELECT in an SqlExpression. Returns a list of values.

valList :: PersistField typ => [typ] -> SqlExpr (ValueList typ) Source #

Lift a list of constant value from Haskell-land to the query.

justList :: SqlExpr (ValueList typ) -> SqlExpr (ValueList (Maybe typ)) Source #

Same as just but for ValueList. Most of the time you won't need it, though, because you can use just from inside subList_select or Just from inside valList.

Since: 2.2.12

in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #

IN operator. For example if you want to select all Persons by a list of IDs:

SELECT *
FROM Person
WHERE Person.id IN (?)

In esqueleto, we may write the same query above as:

select $
from $ \person -> do
where_ $ person ^. PersonId `in_` valList personIds
return person

Where personIds is of type [Key Person].

notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #

NOT IN operator.

exists :: SqlQuery () -> SqlExpr (Value Bool) Source #

EXISTS operator. For example:

select $
from $ \person -> do
where_ $ exists $
         from $ \post -> do
         where_ (post ^. BlogPostAuthorId ==. person ^. PersonId)
return person

notExists :: SqlQuery () -> SqlExpr (Value Bool) Source #

NOT EXISTS operator.

set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Update val)] -> SqlQuery () Source #

SET clause used on UPDATEs. Note that while it's not a type error to use this function on a SELECT, it will most certainly result in a runtime error.

(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Update val) infixr 3 Source #

(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) infixr 3 Source #

(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) infixr 3 Source #

(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) infixr 3 Source #

(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) infixr 3 Source #

case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

CASE statement. For example:

select $
return $
case_
   [ when_
       (exists $
       from $ \p -> do
       where_ (p ^. PersonName ==. val "Mike"))
     then_
       (sub_select $
       from $ \v -> do
       let sub =
               from $ \c -> do
               where_ (c ^. PersonName ==. val "Mike")
               return (c ^. PersonFavNum)
       where_ (v ^. PersonFavNum >. sub_select sub)
       return $ count (v ^. PersonName) +. val (1 :: Int)) ]
   (else_ $ val (-1))

This query is a bit complicated, but basically it checks if a person named "Mike" exists, and if that person does, run the subquery to find out how many people have a ranking (by Fav Num) higher than "Mike".

NOTE: There are a few things to be aware about this statement.

  • This only implements the full CASE statement, it does not implement the "simple" CASE statement.
  • At least one when_ and then_ is mandatory otherwise it will emit an error.
  • The else_ is also mandatory, unlike the SQL statement in which if the ELSE is omitted it will return a NULL. You can reproduce this via nothing.

Since: 2.1.2

toBaseId :: ToBaseId ent => SqlExpr (Value (Key ent)) -> SqlExpr (Value (Key (BaseEnt ent))) Source #

Convert an entity's key into another entity's.

This function is to be used when you change an entity's Id to be that of another entity. For example:

Bar
  barNum Int
Foo
  bar BarId
  fooNum Int
  Primary bar

For this example, declare:

instance ToBaseId Foo where
  type BaseEnt Foo = Bar
  toBaseIdWitness = FooKey

Now you're able to write queries such as:

select $
from $ (bar `InnerJoin` foo) -> do
on (toBaseId (foo ^. FooId) ==. bar ^. BarId)
return (bar, foo)

Note: this function may be unsafe to use in conditions not like the one of the example above.

Since: 2.4.3

subSelect :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value (Maybe a)) Source #

Execute a subquery SELECT in a SqlExpr. The query passed to this function will only return a single result - it has a LIMIT 1 passed in to the query to make it safe, and the return type is Maybe to indicate that the subquery might result in 0 rows.

If you find yourself writing joinV . subSelect, then consider using subSelectMaybe.

If you're performing a countRows, then you can use subSelectCount which is safe.

If you know that the subquery will always return exactly one row (eg a foreign key constraint guarantees that you'll get exactly one row), then consider subSelectUnsafe, along with a comment explaining why it is safe.

Since: 3.2.0

subSelectMaybe :: PersistField a => SqlQuery (SqlExpr (Value (Maybe a))) -> SqlExpr (Value (Maybe a)) Source #

Execute a subquery SELECT in a SqlExpr. This function is a shorthand for the common joinV . subSelect idiom, where you are calling subSelect on an expression that would be Maybe already.

As an example, you would use this function when calling sum_ or max_, which have Maybe in the result type (for a 0 row query).

Since: 3.2.0

subSelectCount :: (Num a, PersistField a) => SqlQuery ignored -> SqlExpr (Value a) Source #

Performs a COUNT of the given query in a subSelect manner. This is always guaranteed to return a result value, and is completely safe.

Since: 3.2.0

subSelectForeign Source #

Arguments

:: (BackendCompatible SqlBackend (PersistEntityBackend val1), PersistEntity val1, PersistEntity val2, PersistField a) 
=> SqlExpr (Entity val2)

An expression representing the table you have access to now.

-> EntityField val2 (Key val1)

The foreign key field on the table.

-> (SqlExpr (Entity val1) -> SqlExpr (Value a))

A function to extract a value from the foreign reference table.

-> SqlExpr (Value a) 

Performs a sub-select using the given foreign key on the entity. This is useful to extract values that are known to be present by the database schema.

As an example, consider the following persistent definition:

User
  profile ProfileId

Profile
  name    Text

The following query will return the name of the user.

getUserWithName =
    select $
    from $ user ->
    pure (user, subSelectForeign user UserProfile (^. ProfileName)

Since: 3.2.0

subSelectList :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) Source #

Execute a subquery SELECT in a SqlExpr that returns a list. This is an alias for subList_select and is provided for symmetry with the other safe subselect functions.

Since: 3.2.0

subSelectUnsafe :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) Source #

Execute a subquery SELECT in a SqlExpr. This function is unsafe, because it can throw runtime exceptions in two cases:

  1. If the query passed has 0 result rows, then it will return a NULL value. The persistent parsing operations will fail on an unexpected NULL.
  2. If the query passed returns more than one row, then the SQL engine will fail with an error like "More than one row returned by a subquery used as an expression".

This function is safe if you guarantee that exactly one row will be returned, or if the result already has a Maybe type for some reason.

For variants with the safety encoded already, see subSelect and subSelectMaybe. For the most common safe use of this, see subSelectCount.

Since: 3.2.0

class ToBaseId ent where Source #

Class that enables one to use toBaseId to convert an entity's key on a query into another (cf. toBaseId).

Associated Types

type BaseEnt ent :: * Source #

Methods

toBaseIdWitness :: Key (BaseEnt ent) -> Key ent Source #

when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a) Source #

Syntax sugar for case_.

Since: 2.1.2

then_ :: () Source #

Syntax sugar for case_.

Since: 2.1.2

else_ :: expr a -> expr a Source #

Syntax sugar for case_.

Since: 2.1.2

from :: From a => (a -> SqlQuery b) -> SqlQuery b Source #

FROM clause: bring entities into scope.

This function internally uses two type classes in order to provide some flexibility of how you may call it. Internally we refer to these type classes as the two different magics.

The innermost magic allows you to use from with the following types:

  • expr (Entity val), which brings a single entity into scope.
  • expr (Maybe (Entity val)), which brings a single entity that may be NULL into scope. Used for OUTER JOINs.
  • A JOIN of any other two types allowed by the innermost magic, where a JOIN may be an InnerJoin, a CrossJoin, a LeftOuterJoin, a RightOuterJoin, or a FullOuterJoin. The JOINs have left fixity.

The outermost magic allows you to use from on any tuples of types supported by innermost magic (and also tuples of tuples, and so on), up to 8-tuples.

Note that using from for the same entity twice does work and corresponds to a self-join. You don't even need to use two different calls to from, you may use a JOIN or a tuple.

The following are valid examples of uses of from (the types of the arguments of the lambda are inside square brackets):

from $ \person -> ...
from $ \(person, blogPost) -> ...
from $ \(p `LeftOuterJoin` mb) -> ...
from $ \(p1 `InnerJoin` f `InnerJoin` p2) -> ...
from $ \((p1 `InnerJoin` f) `InnerJoin` p2) -> ...

The types of the arguments to the lambdas above are, respectively:

person
  :: ( Esqueleto query expr backend
     , PersistEntity Person
     , PersistEntityBackend Person ~ backend
     ) => expr (Entity Person)
(person, blogPost)
  :: (...) => (expr (Entity Person), expr (Entity BlogPost))
(p `LeftOuterJoin` mb)
  :: (...) => InnerJoin (expr (Entity Person)) (expr (Maybe (Entity BlogPost)))
(p1 `InnerJoin` f `InnerJoin` p2)
  :: (...) => InnerJoin
                (InnerJoin (expr (Entity Person))
                           (expr (Entity Follow)))
                (expr (Entity Person))
(p1 `InnerJoin` (f `InnerJoin` p2)) ::
  :: (...) => InnerJoin
                (expr (Entity Person))
                (InnerJoin (expr (Entity Follow))
                           (expr (Entity Person)))

Note that some backends may not support all kinds of JOINs.

newtype Value a Source #

A single value (as opposed to a whole entity). You may use (^.) or (?.) to get a Value from an Entity.

Constructors

Value 

Fields

Instances
Monad Value Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(>>=) :: Value a -> (a -> Value b) -> Value b #

(>>) :: Value a -> Value b -> Value b #

return :: a -> Value a #

fail :: String -> Value a #

Functor Value Source #

Since: 1.4.4

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Applicative Value Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

pure :: a -> Value a #

(<*>) :: Value (a -> b) -> Value a -> Value b #

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

(*>) :: Value a -> Value b -> Value b #

(<*) :: Value a -> Value b -> Value a #

Eq a => Eq (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

Ord a => Ord (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

compare :: Value a -> Value a -> Ordering #

(<) :: Value a -> Value a -> Bool #

(<=) :: Value a -> Value a -> Bool #

(>) :: Value a -> Value a -> Bool #

(>=) :: Value a -> Value a -> Bool #

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

Show a => Show (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

ToSomeValues (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) Source #

You may return any single value (i.e. a single column) from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

newtype ValueList a Source #

A list of single values. There's a limited set of functions able to work with this data type (such as subList_select, valList, in_ and exists).

Constructors

ValueList a 
Instances
Eq a => Eq (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(==) :: ValueList a -> ValueList a -> Bool #

(/=) :: ValueList a -> ValueList a -> Bool #

Ord a => Ord (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show a => Show (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OrderBy Source #

Phantom type used by orderBy, asc and desc.

data DistinctOn Source #

Phantom type used by distinctOn and don.

data LockingKind Source #

Different kinds of locking clauses supported by locking.

Note that each RDBMS has different locking support. The constructors of this datatype specify only the syntax of the locking mechanism, not its semantics. For example, even though both MySQL and PostgreSQL support ForUpdate, there are no guarantees that they will behave the same.

Since: 2.2.7

Constructors

ForUpdate

FOR UPDATE syntax. Supported by MySQL, Oracle and PostgreSQL.

Since: 2.2.7

ForUpdateSkipLocked

FOR UPDATE SKIP LOCKED syntax. Supported by MySQL, Oracle and PostgreSQL.

Since: 2.2.7

ForShare

FOR SHARE syntax. Supported by PostgreSQL.

Since: 2.2.7

LockInShareMode

LOCK IN SHARE MODE syntax. Supported by MySQL.

Since: 2.2.7

class PersistField a => SqlString a Source #

Phantom class of data types that are treated as strings by the RDBMS. It has no methods because it's only used to avoid type errors such as trying to concatenate integers.

If you have a custom data type or newtype, feel free to make it an instance of this class.

Since: 2.4.0

Instances
SqlString ByteString Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Html Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

a ~ Char => SqlString [a] Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString a => SqlString (Maybe a) Source #

Since: 2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Joins

data InnerJoin a b infixl 2 Source #

Data type that represents an INNER JOIN (see LeftOuterJoin for an example).

Constructors

a `InnerJoin` b infixl 2 
Instances
IsJoinKind InnerJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (InnerJoin a b) => From (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) Source #

data CrossJoin a b infixl 2 Source #

Data type that represents a CROSS JOIN (see LeftOuterJoin for an example).

Constructors

a `CrossJoin` b infixl 2 
Instances
IsJoinKind CrossJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (CrossJoin a b) => From (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) Source #

data LeftOuterJoin a b infixl 2 Source #

Data type that represents a LEFT OUTER JOIN. For example,

select $
from $ \(person `LeftOuterJoin` pet) ->
  ...

is translated into

SELECT ...
FROM Person LEFT OUTER JOIN Pet
...

See also: from.

Constructors

a `LeftOuterJoin` b infixl 2 

data RightOuterJoin a b infixl 2 Source #

Data type that represents a RIGHT OUTER JOIN (see LeftOuterJoin for an example).

Constructors

a `RightOuterJoin` b infixl 2 

data FullOuterJoin a b infixl 2 Source #

Data type that represents a FULL OUTER JOIN (see LeftOuterJoin for an example).

Constructors

a `FullOuterJoin` b infixl 2 

data OnClauseWithoutMatchingJoinException Source #

Exception thrown whenever on is used to create an ON clause but no matching JOIN is found.

Instances
Eq OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Ord OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Exception OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

SQL backend

data SqlQuery a Source #

SQL backend for esqueleto using SqlPersistT.

Instances
Monad SqlQuery Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(>>=) :: SqlQuery a -> (a -> SqlQuery b) -> SqlQuery b #

(>>) :: SqlQuery a -> SqlQuery b -> SqlQuery b #

return :: a -> SqlQuery a #

fail :: String -> SqlQuery a #

Functor SqlQuery Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

fmap :: (a -> b) -> SqlQuery a -> SqlQuery b #

(<$) :: a -> SqlQuery b -> SqlQuery a #

Applicative SqlQuery Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

pure :: a -> SqlQuery a #

(<*>) :: SqlQuery (a -> b) -> SqlQuery a -> SqlQuery b #

liftA2 :: (a -> b -> c) -> SqlQuery a -> SqlQuery b -> SqlQuery c #

(*>) :: SqlQuery a -> SqlQuery b -> SqlQuery b #

(<*) :: SqlQuery a -> SqlQuery b -> SqlQuery a #

data SqlExpr a Source #

An expression on the SQL backend.

There are many comments describing the constructors of this data type. However, Haddock doesn't like GADTs, so you'll have to read them by hitting "Source".

Instances
a ~ Value b => UnsafeSqlFunctionArgument (SqlExpr a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: SqlExpr a -> [SqlExpr (Value ())] Source #

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Maybe (Entity val))) Source #

FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Entity val)) Source #

ToSomeValues (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlSelect (SqlExpr InsertFinal) InsertFinal Source #

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) Source #

You may return a possibly-NULL Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) Source #

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) Source #

You may return any single value (i.e. a single column) from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend) Source #

Constraint synonym for persistent entities whose backend is SqlPersistT.

select :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Source #

Execute an esqueleto SELECT query inside persistent's SqlPersistT monad and return a list of rows.

We've seen that from has some magic about which kinds of things you may bring into scope. This select function also has some magic for which kinds of things you may bring back to Haskell-land by using SqlQuery's return:

  • You may return a SqlExpr (Entity v) for an entity v (i.e., like the * in SQL), which is then returned to Haskell-land as just Entity v.
  • You may return a SqlExpr (Maybe (Entity v)) for an entity v that may be NULL, which is then returned to Haskell-land as Maybe (Entity v). Used for OUTER JOINs.
  • You may return a SqlExpr (Value t) for a value t (i.e., a single column), where t is any instance of PersistField, which is then returned to Haskell-land as Value t. You may use Value to return projections of an Entity (see (^.) and (?.)) or to return any other value calculated on the query (e.g., countRows or subSelect).

The SqlSelect a r class has functional dependencies that allow type information to flow both from a to r and vice-versa. This means that you'll almost never have to give any type signatures for esqueleto queries. For example, the query select $ from $ \p -> return p alone is ambiguous, but in the context of

do ps <- select $
         from $ \p ->
         return p
   liftIO $ mapM_ (putStrLn . personName . entityVal) ps

we are able to infer from that single personName . entityVal function composition that the p inside the query is of type SqlExpr (Entity Person).

selectSource :: (SqlSelect a r, BackendCompatible SqlBackend backend, IsPersistBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend, MonadResource m) => SqlQuery a -> ConduitT () r (ReaderT backend m) () Source #

Execute an esqueleto SELECT query inside persistent's SqlPersistT monad and return a Source of rows.

delete :: MonadIO m => SqlQuery () -> SqlWriteT m () Source #

Execute an esqueleto DELETE query inside persistent's SqlPersistT monad. Note that currently there are no type checks for statements that should not appear on a DELETE query.

Example of usage:

delete $
from $ \appointment ->
where_ (appointment ^. AppointmentDate <. val now)

Unlike select, there is a useful way of using delete that will lead to type ambiguities. If you want to delete all rows (i.e., no where_ clause), you'll have to use a type signature:

delete $
from $ \(appointment :: SqlExpr (Entity Appointment)) ->
return ()

deleteCount :: MonadIO m => SqlQuery () -> SqlWriteT m Int64 Source #

Same as delete, but returns the number of rows affected.

update :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m () Source #

Execute an esqueleto UPDATE query inside persistent's SqlPersistT monad. Note that currently there are no type checks for statements that should not appear on a UPDATE query.

Example of usage:

update $ \p -> do
set p [ PersonAge =. just (val thisYear) -. p ^. PersonBorn ]
where_ $ isNothing (p ^. PersonAge)

updateCount :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m Int64 Source #

Same as update, but returns the number of rows affected.

insertSelect :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m () Source #

Insert a PersistField for every selected value.

Since: 2.4.2

insertSelectCount :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m Int64 Source #

Insert a PersistField for every selected value, return the count afterward

(<#) :: (a -> b) -> SqlExpr (Value a) -> SqlExpr (Insertion b) Source #

Apply a PersistField constructor to SqlExpr Value arguments.

(<&>) :: SqlExpr (Insertion (a -> b)) -> SqlExpr (Value a) -> SqlExpr (Insertion b) Source #

Apply extra SqlExpr Value arguments to a PersistField constructor

Rendering Queries

renderQueryToText Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> Mode

Whether to render as an SELECT, DELETE, etc.

-> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQuerySelect Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQueryUpdate Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQueryDelete Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQueryInsertInto Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

Internal.Language

class From a Source #

(Internal) Class that implements the tuple from magic (see fromStart).

Minimal complete definition

from_

Instances
FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Maybe (Entity val))) Source #

FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Entity val)) Source #

(From a, From b) => From (a, b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b) Source #

FromPreprocess (FullOuterJoin a b) => From (FullOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (RightOuterJoin a b) => From (RightOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (LeftOuterJoin a b) => From (LeftOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (CrossJoin a b) => From (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) Source #

FromPreprocess (InnerJoin a b) => From (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) Source #

(From a, From b, From c) => From (a, b, c) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c) Source #

(From a, From b, From c, From d) => From (a, b, c, d) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d) Source #

(From a, From b, From c, From d, From e) => From (a, b, c, d, e) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e) Source #

(From a, From b, From c, From d, From e, From f) => From (a, b, c, d, e, f) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e, f) Source #

(From a, From b, From c, From d, From e, From f, From g) => From (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e, f, g) Source #

(From a, From b, From c, From d, From e, From f, From g, From h) => From (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e, f, g, h) Source #

RDBMS-specific modules

There are many differences between SQL syntax and functions supported by different RDBMSs. Since version 2.2.8, esqueleto includes modules containing functions that are specific to a given RDBMS.

In order to use these functions, you need to explicitly import their corresponding modules, they're not re-exported here.

Helpers

valJ :: PersistField (Key entity) => Value (Key entity) -> SqlExpr (Value (Key entity)) Source #

valJ is like val but for something that is already a Value. The use case it was written for was, given a Value lift the Key for that Value into the query expression in a type safe way. However, the implementation is more generic than that so we call it valJ.

Its important to note that the input entity and the output entity are constrained to be the same by the type signature on the function (https://github.com/prowdsponsor/esqueleto/pull/69).

Since: 1.4.2

associateJoin :: forall e1 e0. Ord (Key e0) => [(Entity e0, e1)] -> Map (Key e0) (e0, [e1]) Source #

Avoid N+1 queries and join entities into a map structure getFoosAndNestedBarsFromParent :: ParentId -> (Map (Key Foo) (Foo, [Maybe (Entity Bar)])) getFoosAndNestedBarsFromParent parentId = fmap associateJoin $ select $ from $ \(foo `LeftOuterJoin` bar) -> do on (bar ?. BarFooId ==. foo ^. FooId) where_ (foo ^. FooParentId ==. val parentId) pure (foo, bar) Since: 3.1.2

Re-exports

We re-export many symbols from persistent for convenince:

deleteKey :: (PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, MonadIO m, PersistEntity val) => Key val -> ReaderT backend m () Source #

Synonym for delete that does not clash with esqueleto's delete.

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

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

entityIdFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record) #

Predefined parseJSON. The input JSON looks like {"id": 1, "name": ...}.

The typical usage is:

instance FromJSON (Entity User) where
    parseJSON = entityIdFromJSON

entityIdToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value #

Predefined toJSON. The resulting JSON looks like {"id": 1, "name": ...}.

The typical usage is:

instance ToJSON (Entity User) where
    toJSON = entityIdToJSON

entityValues :: PersistEntity record => Entity record -> [PersistValue] #

Get list of values corresponding to given entity.

fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a #

Convenience function for getting a free PersistField instance from a type with JSON instances. The JSON parser used will accept JSON values other that object and arrays. So, if your instance serializes the data to a JSON string, this will still work.

Example usage in combination with toPersistValueJSON:

instance PersistField MyData where
  fromPersistValue = fromPersistValueJSON
  toPersistValue = toPersistValueJSON

keyValueEntityFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record) #

Predefined parseJSON. The input JSON looks like {"key": 1, "value": {"name": ...}}.

The typical usage is:

instance FromJSON (Entity User) where
    parseJSON = keyValueEntityFromJSON

keyValueEntityToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value #

Predefined toJSON. The resulting JSON looks like {"key": 1, "value": {"name": ...}}.

The typical usage is:

instance ToJSON (Entity User) where
    toJSON = keyValueEntityToJSON

toPersistValueJSON :: ToJSON a => a -> PersistValue #

Convenience function for getting a free PersistField instance from a type with JSON instances.

Example usage in combination with fromPersistValueJSON:

instance PersistField MyData where
  fromPersistValue = fromPersistValueJSON
  toPersistValue = toPersistValueJSON

selectKeys :: (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Key record) m () #

Get the Keys of all records matching the given criterion.

belongsTo :: (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2) #

Curry this to make a convenience function that loads an associated model.

foreign = belongsTo foreignId

belongsToJust :: (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2 #

Same as belongsTo, but uses getJust and therefore is similarly unsafe.

getEntity :: (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e)) #

Like get, but returns the complete Entity.

Example usage

Expand

With schema-1 and dataset-1,

getSpjEntity :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User))
getSpjEntity = getEntity spjId
mSpjEnt <- getSpjEntity

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

+----+------+-----+
| id | name | age |
+----+------+-----+
|  1 | SPJ  |  40 |
+----+------+-----+

getJust :: (PersistStoreRead backend, PersistRecordBackend record backend, MonadIO m) => Key record -> ReaderT backend m record #

Same as get, but for a non-null (not Maybe) foreign key. Unsafe unless your database is enforcing that the foreign key is valid.

Example usage

Expand

With schema-1 and dataset-1,

getJustSpj :: MonadIO m => ReaderT SqlBackend m User
getJustSpj = getJust spjId
spj <- getJust spjId

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

+----+------+-----+
| id | name | age |
+----+------+-----+
|  1 | SPJ  |  40 |
+----+------+-----+
getJustUnknown :: MonadIO m => ReaderT SqlBackend m User
getJustUnknown = getJust unknownId

mrx <- getJustUnknown

This just throws an error.

getJustEntity :: (PersistEntityBackend record ~ BaseBackend backend, MonadIO m, PersistEntity record, PersistStoreRead backend) => Key record -> ReaderT backend m (Entity record) #

Same as getJust, but returns an Entity instead of just the record.

Example usage

Expand

With schema-1 and dataset-1,

getJustEntitySpj :: MonadIO m => ReaderT SqlBackend m (Entity User)
getJustEntitySpj = getJustEntity spjId
spjEnt <- getJustEntitySpj

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

+----+------+-----+
| id | name | age |
+----+------+-----+
|  1 | SPJ  |  40 |
+----+------+-----+

Since: persistent-2.6.1

insertEntity :: (PersistStoreWrite backend, PersistRecordBackend e backend, MonadIO m) => e -> ReaderT backend m (Entity e) #

Like insert, but returns the complete Entity.

Example usage

Expand

With schema-1 and dataset-1,

insertHaskellEntity :: MonadIO m => ReaderT SqlBackend m (Entity User)
insertHaskellEntity = insertEntity $ User "Haskell" 81
haskellEnt <- insertHaskellEntity

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

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

insertRecord :: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend) => record -> ReaderT backend m record #

Like insertEntity but just returns the record instead of Entity.

Example usage

Expand

With schema-1 and dataset-1,

insertDaveRecord :: MonadIO m => ReaderT SqlBackend m User
insertDaveRecord = insertRecord $ User "Dave" 50
dave <- insertDaveRecord

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

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

Since: persistent-2.6.1

liftPersist :: (MonadIO m, MonadReader backend m) => ReaderT backend IO b -> m b #

checkUnique :: (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => record -> ReaderT backend m (Maybe (Unique record)) #

Check whether there are any conflicts for unique keys with this entity and existing entities in the database.

Returns Nothing if the entity would be unique, and could thus safely be inserted. on a conflict returns the conflicting key

Example usage

Expand

We use schema-1 and dataset-1 here.

This would be Nothing:

mAlanConst <- checkUnique $ User "Alan" 70

While this would be Just because SPJ already exists:

mSpjConst <- checkUnique $ User "SPJ" 60

getByValue :: (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Maybe (Entity record)) #

A modification of getBy, which takes the PersistEntity itself instead of a Unique record. Returns a record matching one of the unique keys. This function makes the most sense on entities with a single Unique constructor.

Example usage

Expand

With schema-1 and dataset-1,

getBySpjValue :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User)) getBySpjValue = getByValue $ User SPJ 999

mSpjEnt <- getBySpjValue

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

+----+------+-----+
| id | name | age |
+----+------+-----+
|  1 | SPJ  |  40 |
+----+------+-----+

insertBy :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Either (Entity record) (Key record)) #

Insert a value, checking for conflicts with any unique constraints. If a duplicate exists in the database, it is returned as Left. Otherwise, the new 'Key is returned as Right.

Example usage

Expand

With schema-2 and dataset-1, we have following lines of code:

l1 <- insertBy $ User "SPJ" 20
l2 <- insertBy $ User "XXX" 41
l3 <- insertBy $ User "SPJ" 40
r1 <- insertBy $ User "XXX" 100

First three lines return Left because there're duplicates in given record's uniqueness constraints. While the last line returns a new key as Right.

insertUniqueEntity :: (MonadIO m, PersistRecordBackend record backend, PersistUniqueWrite backend) => record -> ReaderT backend m (Maybe (Entity record)) #

Like insertEntity, but returns Nothing when the record couldn't be inserted because of a uniqueness constraint.

Example usage

Expand

We use schema-2 and dataset-1 here.

insertUniqueSpjEntity :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User))
insertUniqueSpjEntity = insertUniqueEntity $ User "SPJ" 50
mSpjEnt <- insertUniqueSpjEntity

The above query results Nothing as SPJ already exists.

insertUniqueAlexaEntity :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User))
insertUniqueAlexaEntity = insertUniqueEntity $ User "Alexa" 3
mAlexaEnt <- insertUniqueSpjEntity

Because there's no such unique keywords of the given record, the above query when applied on dataset-1, will produce this:

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

Since: persistent-2.7.1

onlyUnique :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, OnlyOneUniqueKey record) => record -> ReaderT backend m (Unique record) #

Return the single unique key for a record.

Example usage

Expand

We use shcema-1 and dataset-1 here.

onlySimonConst :: MonadIO m => ReaderT SqlBackend m (Unique User)
onlySimonConst = onlyUnique $ User "Simon" 999
mSimonConst <- onlySimonConst

mSimonConst would be Simon's uniqueness constraint. Note that onlyUnique doesn't work if there're more than two constraints. It will fail with a type error instead.

replaceUnique :: (MonadIO m, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record)) #

Attempt to replace the record of the given key with the given new record. First query the unique fields to make sure the replacement maintains uniqueness constraints.

Return Nothing if the replacement was made. If uniqueness is violated, return a Just with the Unique violation

Since: persistent-1.2.2.0

transactionSave :: MonadIO m => ReaderT SqlBackend m () #

Commit the current transaction and begin a new one. This is used when a transaction commit is required within the context of runSqlConn (which brackets its provided action with a transaction begin/commit pair).

Since: persistent-1.2.0

transactionUndo :: MonadIO m => ReaderT SqlBackend m () #

Roll back the current transaction and begin a new one. This rolls back to the state of the last call to transactionSave or the enclosing runSqlConn call.

Since: persistent-1.2.0

mkColumns :: [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef]) #

Create the list of columns for the given entity.

getMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Sql] #

Return all of the Sql values associated with the given migration. Calls error if there's a parse error on any migration.

migrate :: [EntityDef] -> EntityDef -> Migration #

Given a list of old entity definitions and a new EntityDef in val, this creates a Migration to update the old list of definitions with the new one.

parseMigration :: MonadIO m => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration) #

Given a Migration, this parses it and returns either a list of errors associated with the migration or a list of migrations to do.

parseMigration' :: MonadIO m => Migration -> ReaderT SqlBackend m CautiousMigration #

Like parseMigration, but instead of returning the value in an Either value, it calls error on the error values.

printMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () #

Prints a migration.

runMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () #

Runs a migration. If the migration fails to parse or if any of the migrations are unsafe, then this calls error to halt the program.

runMigrationSilent :: MonadUnliftIO m => Migration -> ReaderT SqlBackend m [Text] #

Same as runMigration, but returns a list of the SQL commands executed instead of printing them to stderr.

This function silences the migration by remapping stderr. As a result, it is not thread-safe and can clobber output from other parts of the program. This implementation method was chosen to also silence postgresql migration output on stderr, but is not recommended!

runMigrationUnsafe :: MonadIO m => Migration -> ReaderT SqlBackend m () #

Like runMigration, but this will perform the unsafe database migrations instead of erroring out.

showMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Text] #

Convert a Migration to a list of Text values corresponding to their Sql statements.

decorateSQLWithLimitOffset :: Text -> (Int, Int) -> Bool -> Text -> Text #

Generates sql for limit and offset for postgres, sqlite and mysql.

fieldDBName :: PersistEntity record => EntityField record typ -> DBName #

useful for a backend to implement fieldName by adding escaping

fromSqlKey :: ToBackendKey SqlBackend record => Key record -> Int64 #

getFieldName :: (PersistEntity record, PersistEntityBackend record ~ SqlBackend, BackendCompatible SqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text #

get the SQL string for the field that an EntityField represents Useful for raw SQL queries

Your backend may provide a more convenient fieldName function which does not operate in a Monad

getTableName :: (PersistEntity record, BackendCompatible SqlBackend backend, Monad m) => record -> ReaderT backend m Text #

get the SQL string for the table that a PeristEntity represents Useful for raw SQL queries

Your backend may provide a more convenient tableName function which does not operate in a Monad

tableDBName :: PersistEntity record => record -> DBName #

useful for a backend to implement tableName by adding escaping

toSqlKey :: ToBackendKey SqlBackend record => Int64 -> Key record #

rawExecute #

Arguments

:: (MonadIO m, BackendCompatible SqlBackend backend) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m () 

Execute a raw SQL statement

rawExecuteCount #

Arguments

:: (MonadIO m, BackendCompatible SqlBackend backend) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m Int64 

Execute a raw SQL statement and return the number of rows it has modified.

rawSql #

Arguments

:: (RawSql a, MonadIO m, BackendCompatible SqlBackend backend) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m [a] 

Execute a raw SQL statement and return its results as a list. If you do not expect a return value, use of rawExecute is recommended.

If you're using Entitys (which is quite likely), then you must use entity selection placeholders (double question mark, ??). These ?? placeholders are then replaced for the names of the columns that we need for your entities. You'll receive an error if you don't use the placeholders. Please see the Entitys documentation for more details.

You may put value placeholders (question marks, ?) in your SQL query. These placeholders are then replaced by the values you pass on the second parameter, already correctly escaped. You may want to use toPersistValue to help you constructing the placeholder values.

Since you're giving a raw SQL statement, you don't get any guarantees regarding safety. If rawSql is not able to parse the results of your query back, then an exception is raised. However, most common problems are mitigated by using the entity selection placeholder ??, and you shouldn't see any error at all if you're not using Single.

Some example of rawSql based on this schema:

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
    name String
    age Int Maybe
    deriving Show
BlogPost
    title String
    authorId PersonId
    deriving Show
|]

Examples based on the above schema:

getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person]
getPerson = rawSql "select ?? from person where name=?" [PersistText "john"]

getAge :: MonadIO m => ReaderT SqlBackend m [Single Int]
getAge = rawSql "select person.age from person where name=?" [PersistText "john"]

getAgeName :: MonadIO m => ReaderT SqlBackend m [(Single Int, Single Text)]
getAgeName = rawSql "select person.age, person.name from person where name=?" [PersistText "john"]

getPersonBlog :: MonadIO m => ReaderT SqlBackend m [(Entity Person, Entity BlogPost)]
getPersonBlog = rawSql "select ??,?? from person,blog_post where person.id = blog_post.author_id" []

Minimal working program for PostgreSQL backend based on the above concepts:

{-# LANGUAGE EmptyDataDecls             #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeFamilies               #-}

import           Control.Monad.IO.Class  (liftIO)
import           Control.Monad.Logger    (runStderrLoggingT)
import           Database.Persist
import           Control.Monad.Reader
import           Data.Text
import           Database.Persist.Sql
import           Database.Persist.Postgresql
import           Database.Persist.TH

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

conn = "host=localhost dbname=new_db user=postgres password=postgres port=5432"

getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person]
getPerson = rawSql "select ?? from person where name=?" [PersistText "sibi"]

liftSqlPersistMPool y x = liftIO (runSqlPersistMPool y x)

main :: IO ()
main = runStderrLoggingT $ withPostgresqlPool conn 10 $ liftSqlPersistMPool $ do
         runMigration migrateAll
         xs <- getPerson
         liftIO (print xs)

close' :: BackendCompatible SqlBackend backend => backend -> IO () #

createSqlPool :: (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend) #

liftSqlPersistMPool :: (MonadIO m, BackendCompatible SqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a #

runSqlConn :: (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> m a #

runSqlPersistM :: BackendCompatible SqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a #

runSqlPool :: (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> m a #

Get a connection from the pool, run the given action, and then return the connection to the pool.

Note: This function previously timed out after 2 seconds, but this behavior was buggy and caused more problems than it solved. Since version 2.1.2, it performs no timeout checks.

withSqlConn :: (MonadUnliftIO m, MonadLogger m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a #

Create a connection and run sql queries within it. This function automatically closes the connection on it's completion.

Example usage

Expand
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies#-}
{-# LANGUAGE TemplateHaskell#-}
{-# LANGUAGE QuasiQuotes#-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.IO.Class  (liftIO)
import Control.Monad.Logger
import Conduit
import Database.Persist
import Database.Sqlite
import Database.Persist.Sqlite
import Database.Persist.TH

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

openConnection :: LogFunc -> IO SqlBackend
openConnection logfn = do
 conn <- open "/home/sibi/test.db"
 wrapConnection conn logfn

main :: IO ()
main = do
  runNoLoggingT $ runResourceT $ withSqlConn openConnection (\backend ->
                                      flip runSqlConn backend $ do
                                        runMigration migrateAll
                                        insert_ $ Person "John doe" $ Just 35
                                        insert_ $ Person "Divya" $ Just 36
                                        (pers :: [Entity Person]) <- selectList [] []
                                        liftIO $ print pers
                                        return ()
                                     )

On executing it, you get this output:

Migrating: CREATE TABLE "person"("id" INTEGER PRIMARY KEY,"name" VARCHAR NOT NULL,"age" INTEGER NULL)
[Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 1}}, entityVal = Person {personName = "John doe", personAge = Just 35}},Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 2}}, entityVal = Person {personName = "Hema", personAge = Just 36}}]

withSqlPool #

Arguments

:: (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

create a new connection

-> Int

connection count

-> (Pool backend -> m a) 
-> m a 

readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a #

Useful for running a read query against a backend with unknown capabilities.

readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a #

Useful for running a read query against a backend with read and write capabilities.

writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a #

Useful for running a write query against an untagged backend with unknown capabilities.

type PersistStore a = PersistStoreWrite a #

A backwards-compatible alias for those that don't care about distinguishing between read and write queries. It signifies the assumption that, by default, a backend can write as well as read.

type PersistUnique a = PersistUniqueWrite a #

A backwards-compatible alias for those that don't care about distinguishing between read and write queries. It signifies the assumption that, by default, a backend can write as well as read.

class (PersistStoreWrite backend, PersistEntity record, BaseBackend backend ~ PersistEntityBackend record) => DeleteCascade record backend where #

For combinations of backends and entities that support cascade-deletion. “Cascade-deletion” means that entries that depend on other entries to be deleted will be deleted as well.

Methods

deleteCascade :: MonadIO m => Key record -> ReaderT backend m () #

Perform cascade-deletion of single database entry.

class PersistConfig c where #

Represents a value containing all the configuration options for a specific backend. This abstraction makes it easier to write code that can easily swap backends.

Minimal complete definition

loadConfig, createPoolConfig, runPool

Associated Types

type PersistConfigBackend c :: (Type -> Type) -> Type -> Type #

type PersistConfigPool c :: Type #

Methods

loadConfig :: Value -> Parser c #

Load the config settings from a Value, most likely taken from a YAML config file.

applyEnv :: c -> IO c #

Modify the config settings based on environment variables.

createPoolConfig :: c -> IO (PersistConfigPool c) #

Create a new connection pool based on the given config settings.

runPool :: MonadUnliftIO m => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a #

Run a database action by taking a connection from the pool.

Instances
(PersistConfig c1, PersistConfig c2, PersistConfigPool c1 ~ PersistConfigPool c2, PersistConfigBackend c1 ~ PersistConfigBackend c2) => PersistConfig (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

Associated Types

type PersistConfigBackend (Either c1 c2) :: (Type -> Type) -> Type -> Type #

type PersistConfigPool (Either c1 c2) :: Type #

Methods

loadConfig :: Value -> Parser (Either c1 c2) #

applyEnv :: Either c1 c2 -> IO (Either c1 c2) #

createPoolConfig :: Either c1 c2 -> IO (PersistConfigPool (Either c1 c2)) #

runPool :: MonadUnliftIO m => Either c1 c2 -> PersistConfigBackend (Either c1 c2) m a -> PersistConfigPool (Either c1 c2) -> m a #

type family BackendSpecificUpdate backend record :: Type #

data Entity record #

Datatype that represents an entity, with both its Key and its Haskell record representation.

When using a SQL-based backend (such as SQLite or PostgreSQL), an Entity may take any number of columns depending on how many fields it has. In order to reconstruct your entity on the Haskell side, persistent needs all of your entity columns and in the right order. Note that you don't need to worry about this when using persistent's API since everything is handled correctly behind the scenes.

However, if you want to issue a raw SQL command that returns an Entity, then you have to be careful with the column order. While you could use SELECT Entity.* WHERE ... and that would work most of the time, there are times when the order of the columns on your database is different from the order that persistent expects (for example, if you add a new field in the middle of you entity definition and then use the migration code -- persistent will expect the column to be in the middle, but your DBMS will put it as the last column). So, instead of using a query like the one above, you may use rawSql (from the Database.Persist.GenericSql module) with its /entity selection placeholder/ (a double question mark ??). Using rawSql the query above must be written as SELECT ?? WHERE ... Then rawSql will replace ?? with the list of all columns that we need from your entity in the right order. If your query returns two entities (i.e. (Entity backend a, Entity backend b)), then you must you use SELECT ??, ?? WHERE ..., and so on.

Constructors

Entity 

Fields

Instances
(Eq (Key record), Eq record) => Eq (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

(==) :: Entity record -> Entity record -> Bool #

(/=) :: Entity record -> Entity record -> Bool #

(Ord (Key record), Ord record) => Ord (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

compare :: Entity record -> Entity record -> Ordering #

(<) :: Entity record -> Entity record -> Bool #

(<=) :: Entity record -> Entity record -> Bool #

(>) :: Entity record -> Entity record -> Bool #

(>=) :: Entity record -> Entity record -> Bool #

max :: Entity record -> Entity record -> Entity record #

min :: Entity record -> Entity record -> Entity record #

(Read (Key record), Read record) => Read (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

readsPrec :: Int -> ReadS (Entity record) #

readList :: ReadS [Entity record] #

readPrec :: ReadPrec (Entity record) #

readListPrec :: ReadPrec [Entity record] #

(Show (Key record), Show record) => Show (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

showsPrec :: Int -> Entity record -> ShowS #

show :: Entity record -> String #

showList :: [Entity record] -> ShowS #

(Generic (Key record), Generic record) => Generic (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

Associated Types

type Rep (Entity record) :: Type -> Type #

Methods

from :: Entity record -> Rep (Entity record) x #

to :: Rep (Entity record) x -> Entity record #

(PersistEntity record, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (Entity record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> Entity record -> (Int, [Text]) #

rawSqlColCountReason :: Entity record -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (Entity record) #

(PersistField record, PersistEntity record) => PersistFieldSql (Entity record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Entity record) -> SqlType #

(PersistEntity record, PersistField record, PersistField (Key record)) => PersistField (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Maybe (Entity val))) Source #

FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Entity val)) Source #

PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) Source #

You may return a possibly-NULL Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) Source #

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

type Rep (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

type Rep (Entity record) = D1 (MetaData "Entity" "Database.Persist.Class.PersistEntity" "persistent-2.10.4-46xgHsOpj143FNGNwCZRVZ" False) (C1 (MetaCons "Entity" PrefixI True) (S1 (MetaSel (Just "entityKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Key record)) :*: S1 (MetaSel (Just "entityVal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 record)))

class (PersistField (Key record), ToJSON (Key record), FromJSON (Key record), Show (Key record), Read (Key record), Eq (Key record), Ord (Key record)) => PersistEntity record where #

Persistent serialized Haskell records to the database. A Database Entity (A row in SQL, a document in MongoDB, etc) corresponds to a Key plus a Haskell record.

For every Haskell record type stored in the database there is a corresponding PersistEntity instance. An instance of PersistEntity contains meta-data for the record. PersistEntity also helps abstract over different record types. That way the same query interface can return a PersistEntity, with each query returning different types of Haskell records.

Some advanced type system capabilities are used to make this process type-safe. Persistent users usually don't need to understand the class associated data and functions.

Associated Types

type PersistEntityBackend record :: Type #

Persistent allows multiple different backends (databases).

data Key record :: Type #

By default, a backend will automatically generate the key Instead you can specify a Primary key made up of unique values.

data EntityField record a :: Type #

An EntityField is parameterised by the Haskell record it belongs to and the additional type of that field.

data Unique record :: Type #

Unique keys besides the Key.

Methods

keyToValues :: Key record -> [PersistValue] #

A lower-level key operation.

keyFromValues :: [PersistValue] -> Either Text (Key record) #

A lower-level key operation.

persistIdField :: EntityField record (Key record) #

A meta-operation to retrieve the Key EntityField.

entityDef :: Monad m => m record -> EntityDef #

Retrieve the EntityDef meta-data for the record.

persistFieldDef :: EntityField record typ -> FieldDef #

Return meta-data for a given EntityField.

toPersistFields :: record -> [SomePersistField] #

A meta-operation to get the database fields of a record.

fromPersistValues :: [PersistValue] -> Either Text record #

A lower-level operation to convert from database values to a Haskell record.

persistUniqueKeys :: record -> [Unique record] #

A meta operation to retrieve all the Unique keys.

persistUniqueToFieldNames :: Unique record -> [(HaskellName, DBName)] #

A lower level operation.

persistUniqueToValues :: Unique record -> [PersistValue] #

A lower level operation.

fieldLens :: EntityField record field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity record -> f (Entity record) #

Use a PersistField as a lens.

class PersistField a where #

This class teaches Persistent how to take a custom type and marshal it to and from a PersistValue, allowing it to be stored in a database.

Examples

Expand
Simple Newtype

You can use newtype to add more type safety/readability to a basis type like ByteString. In these cases, just derive PersistField and PersistFieldSql:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

newtype HashedPassword = HashedPassword ByteString
  deriving (Eq, Show, PersistField, PersistFieldSql)
Smart Constructor Newtype

In this example, we create a PersistField instance for a newtype following the "Smart Constructor" pattern.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import qualified Data.Text as T
import qualified Data.Char as C

-- | An American Social Security Number
newtype SSN = SSN Text
 deriving (Eq, Show, PersistFieldSql)

mkSSN :: Text -> Either Text SSN
mkSSN t = if (T.length t == 9) && (T.all C.isDigit t)
 then Right $ SSN t
 else Left $ "Invalid SSN: " <> t

instance PersistField SSN where
  toPersistValue (SSN t) = PersistText t
  fromPersistValue (PersistText t) = mkSSN t
  -- Handle cases where the database does not give us PersistText
  fromPersistValue x = Left $ "File.hs: When trying to deserialize an SSN: expected PersistText, received: " <> T.pack (show x)

Tips:

  • This file contain dozens of PersistField instances you can look at for examples.
  • Typically custom PersistField instances will only accept a single PersistValue constructor in fromPersistValue.
  • Internal PersistField instances accept a wide variety of PersistValues to accomodate e.g. storing booleans as integers, booleans or strings.
  • If you're making a custom instance and using a SQL database, you'll also need PersistFieldSql to specify the type of the database column.
Instances
PersistField Bool 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Double 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int8 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int16 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int32 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int64 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Natural 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Rational 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word8 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word16 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word32 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word64 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField ByteString 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField UTCTime 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Html 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField SomePersistField 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Checkmark 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField PersistValue 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField TimeOfDay 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Day 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField [Char] 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField a => PersistField [a] 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField a => PersistField (Maybe a) 
Instance details

Defined in Database.Persist.Class.PersistField

HasResolution a => PersistField (Fixed a) 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField v => PersistField (IntMap v) 
Instance details

Defined in Database.Persist.Class.PersistField

(Ord a, PersistField a) => PersistField (Set a) 
Instance details

Defined in Database.Persist.Class.PersistField

(PersistEntity record, PersistField record, PersistField (Key record)) => PersistField (Entity record) 
Instance details

Defined in Database.Persist.Class.PersistEntity

PersistField a => PersistField (Vector a) 
Instance details

Defined in Database.Persist.Class.PersistField

(FromJSON a, ToJSON a) => PersistField (JSONB a) Source #

Since: 3.1.0

Instance details

Defined in Database.Esqueleto.PostgreSQL.JSON.Instances

(PersistField a, PersistField b) => PersistField (a, b) 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField v => PersistField (Map Text v) 
Instance details

Defined in Database.Persist.Class.PersistField

class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where #

Backends supporting conditional read operations.

Minimal complete definition

selectSourceRes, selectKeysRes, count

Methods

selectSourceRes :: (PersistRecordBackend record backend, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ())) #

Get all records matching the given criterion in the specified order. Returns also the identifiers.

selectFirst :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m (Maybe (Entity record)) #

Get just the first record for the criterion.

selectKeysRes :: (MonadIO m1, MonadIO m2, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ())) #

Get the Keys of all records matching the given criterion.

class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend where #

Backends supporting conditional write operations

Methods

updateWhere :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [Update record] -> ReaderT backend m () #

Update individual fields on any record matching the given criterion.

deleteWhere :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m () #

Delete all records matching the given criterion.

class BackendCompatible sup sub where #

This class witnesses that two backend are compatible, and that you can convert from the sub backend into the sup backend. This is similar to the HasPersistBackend and IsPersistBackend classes, but where you don't want to fix the type associated with the PersistEntityBackend of a record.

Generally speaking, where you might have:

foo ::
  ( PersistEntity record
  , PeristEntityBackend record ~ BaseBackend backend
  , IsSqlBackend backend
  )

this can be replaced with:

foo ::
  ( PersistEntity record,
  , PersistEntityBackend record ~ backend
  , BackendCompatible SqlBackend backend
  )

This works for SqlReadBackend because of the instance BackendCompatible SqlBackend SqlReadBackend, without needing to go through the BaseBackend type family.

Likewise, functions that are currently hardcoded to use SqlBackend can be generalized:

-- before:
asdf :: ReaderT SqlBackend m ()
asdf = pure ()

-- after:
asdf' :: BackendCompatible SqlBackend backend => ReaderT backend m ()
asdf' = withReaderT projectBackend asdf

Since: persistent-2.7.1

Methods

projectBackend :: sub -> sup #

class HasPersistBackend backend where #

Class which allows the plucking of a BaseBackend backend from some larger type. For example, instance HasPersistBackend (SqlReadBackend, Int) where type BaseBackend (SqlReadBackend, Int) = SqlBackend persistBackend = unSqlReadBackend . fst

Associated Types

type BaseBackend backend :: Type #

Methods

persistBackend :: backend -> BaseBackend backend #

class HasPersistBackend backend => IsPersistBackend backend #

Class which witnesses that backend is essentially the same as BaseBackend backend. That is, they're isomorphic and backend is just some wrapper over BaseBackend backend.

Minimal complete definition

mkPersistBackend

class PersistCore backend #

Associated Types

data BackendKey backend :: Type #

type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend) #

A convenient alias for common type signatures

class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistCore backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreRead backend where #

Minimal complete definition

get

Methods

get :: (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m (Maybe record) #

Get a record by identifier, if available.

Example usage

Expand

With schema-1 and dataset-1,

getSpj :: MonadIO m => ReaderT SqlBackend m (Maybe User)
getSpj = get spjId
mspj <- getSpj

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

+------+-----+
| name | age |
+------+-----+
| SPJ  |  40 |
+------+-----+

getMany :: (MonadIO m, PersistRecordBackend record backend) => [Key record] -> ReaderT backend m (Map (Key record) record) #

Get many records by their respective identifiers, if available.

Example usage

Expand

With schema-1 and dataset-1:

getUsers :: MonadIO m => ReaderT SqlBackend m (Map (Key User) User)
getUsers = getMany allkeys
musers <- getUsers

The above query when applied on dataset-1, will get these records:

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

Since: persistent-2.8.1

class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistStoreRead backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreWrite backend where #

Minimal complete definition

insert, insertKey, repsert, replace, delete, update

Methods

insert :: (MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m (Key record) #

Create a new record in the database, returning an automatically created key (in SQL an auto-increment id).

Example usage

Expand

Using schema-1 and dataset-1, let's insert a new user John.

insertJohn :: MonadIO m => ReaderT SqlBackend m (Key User)
insertJohn = insert $ User "John" 30
johnId <- insertJohn

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

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

insert_ :: (MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m () #

Same as insert, but doesn't return a Key.

Example usage

Expand

with schema-1 and dataset-1,

insertJohn :: MonadIO m => ReaderT SqlBackend m (Key User)
insertJohn = insert_ $ User "John" 30

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

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

insertMany :: (MonadIO m, PersistRecordBackend record backend) => [record] -> ReaderT backend m [Key record] #

Create multiple records in the database and return their Keys.

If you don't need the inserted Keys, use insertMany_.

The MongoDB and PostgreSQL backends insert all records and retrieve their keys in one database query.

The SQLite and MySQL backends use the slow, default implementation of mapM insert.

Example usage

Expand

with schema-1 and dataset-1,

insertUsers :: MonadIO m => ReaderT SqlBackend m [Key User]
insertUsers = insertMany [User "John" 30, User "Nick" 32, User "Jane" 20]
userIds <- insertUsers

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

+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|1    |SPJ   |40   |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+
|3    |John  |30   |
+-----+------+-----+
|4    |Nick  |32   |
+-----+------+-----+
|5    |Jane  |20   |
+-----+------+-----+

insertMany_ :: (MonadIO m, PersistRecordBackend record backend) => [record] -> ReaderT backend m () #

Same as insertMany, but doesn't return any Keys.

The MongoDB, PostgreSQL, SQLite and MySQL backends insert all records in one database query.

Example usage

Expand

With schema-1 and dataset-1,

insertUsers_ :: MonadIO m => ReaderT SqlBackend m ()
insertUsers_ = insertMany_ [User "John" 30, User "Nick" 32, User "Jane" 20]

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

+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|1    |SPJ   |40   |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+
|3    |John  |30   |
+-----+------+-----+
|4    |Nick  |32   |
+-----+------+-----+
|5    |Jane  |20   |
+-----+------+-----+

insertEntityMany :: (MonadIO m, PersistRecordBackend record backend) => [Entity record] -> ReaderT backend m () #

Same as insertMany_, but takes an Entity instead of just a record.

Useful when migrating data from one entity to another and want to preserve ids.

The MongoDB, PostgreSQL, SQLite and MySQL backends insert all records in one database query.

Example usage

Expand

With schema-1 and dataset-1,

insertUserEntityMany :: MonadIO m => ReaderT SqlBackend m ()
insertUserEntityMany = insertEntityMany [SnakeEntity, EvaEntity]

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

+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|1    |SPJ   |40   |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+
|3    |Snake |38   |
+-----+------+-----+
|4    |Eva   |38   |
+-----+------+-----+

insertKey :: (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () #

Create a new record in the database using the given key.

Example usage

Expand

With schema-1 and dataset-1,

insertAliceKey :: MonadIO m => Key User -> ReaderT SqlBackend m ()
insertAliceKey key = insertKey key $ User "Alice" 20
insertAliceKey $ UserKey {unUserKey = SqlBackendKey {unSqlBackendKey = 3}}

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

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

repsert :: (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () #

Put the record in the database with the given key. Unlike replace, if a record with the given key does not exist then a new record will be inserted.

Example usage

Expand

We try to explain upsertBy using schema-1 and dataset-1.

First, we insert Philip to dataset-1.

insertPhilip :: MonadIO m => ReaderT SqlBackend m (Key User)
insertPhilip = insert $ User "Philip" 42
philipId <- insertPhilip

This query will produce:

+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|1    |SPJ   |40   |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+
|3    |Philip|42   |
+-----+------+-----+
repsertHaskell :: MonadIO m => Key record -> ReaderT SqlBackend m ()
repsertHaskell id = repsert id $ User "Haskell" 81
repsertHaskell philipId

This query will replace Philip's record with Haskell's one:

+-----+-----------------+--------+
|id   |name             |age     |
+-----+-----------------+--------+
|1    |SPJ              |40      |
+-----+-----------------+--------+
|2    |Simon            |41      |
+-----+-----------------+--------+
|3    |Philip -> Haskell|42 -> 81|
+-----+-----------------+--------+

repsert inserts the given record if the key doesn't exist.

repsertXToUnknown :: MonadIO m => ReaderT SqlBackend m ()
repsertXToUnknown = repsert unknownId $ User "X" 999

For example, applying the above query to dataset-1 will produce this:

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

repsertMany :: (MonadIO m, PersistRecordBackend record backend) => [(Key record, record)] -> ReaderT backend m () #

Put many entities into the database.

Batch version of repsert for SQL backends.

Useful when migrating data from one entity to another and want to preserve ids.

Example usage

Expand

With schema-1 and dataset-1,

repsertManyUsers :: MonadIO m =>ReaderT SqlBackend m ()
repsertManyusers = repsertMany [(simonId, User "Philip" 20), (unknownId999, User "Mr. X" 999)]

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

+-----+----------------+---------+
|id   |name            |age      |
+-----+----------------+---------+
|1    |SPJ             |40       |
+-----+----------------+---------+
|2    |Simon -> Philip |41 -> 20 |
+-----+----------------+---------+
|999  |Mr. X           |999      |
+-----+----------------+---------+

Since: persistent-2.8.1

replace :: (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () #

Replace the record in the database with the given key. Note that the result is undefined if such record does not exist, so you must use insertKey or repsert in these cases.

Example usage

Expand

With schema-1 schama-1 and dataset-1,

replaceSpj :: MonadIO m => User -> ReaderT SqlBackend m ()
replaceSpj record = replace spjId record

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

+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|1    |Mike  |45   |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+

updateGet :: (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m record #

Update individual fields on a specific record, and retrieve the updated value from the database.

Note that this function will throw an exception if the given key is not found in the database.

Example usage

Expand

With schema-1 and dataset-1,

updateGetSpj :: MonadIO m => [Update User] -> ReaderT SqlBackend m User
updateGetSpj updates = updateGet spjId updates
spj <- updateGetSpj [UserAge +=. 100]

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

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

class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record where #

ToBackendKey converts a PersistEntity Key into a BackendKey This can be used by each backend to convert between a Key and a plain Haskell type. For Sql, that is done with toSqlKey and fromSqlKey.

By default, a PersistEntity uses the default BackendKey for its Key and is an instance of ToBackendKey

A Key that instead uses a custom type will not be an instance of ToBackendKey.

Methods

toBackendKey :: Key record -> BackendKey backend #

fromBackendKey :: BackendKey backend -> Key record #

class (PersistCore backend, PersistStoreRead backend) => PersistUniqueRead backend where #

Queries against Unique keys (other than the id Key).

Please read the general Persistent documentation to learn how to create Unique keys.

Using this with an Entity without a Unique key leads to undefined behavior. A few of these functions require a single Unique, so using an Entity with multiple Uniques is also undefined. In these cases persistent's goal is to throw an exception as soon as possible, but persistent is still transitioning to that.

SQL backends automatically create uniqueness constraints, but for MongoDB you must manually place a unique index on a field to have a uniqueness constraint.

Methods

getBy :: (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m (Maybe (Entity record)) #

Get a record by unique key, if available. Returns also the identifier.

Example usage

Expand

With schema-1 and dataset-1:

getBySpjName :: MonadIO m  => ReaderT SqlBackend m (Maybe (Entity User))
getBySpjName = getBy $ UniqueUserName "SPJ"
mSpjEnt <- getBySpjName

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

+----+------+-----+
| id | name | age |
+----+------+-----+
|  1 | SPJ  |  40 |
+----+------+-----+

class (PersistUniqueRead backend, PersistStoreWrite backend) => PersistUniqueWrite backend where #

Some functions in this module (insertUnique, insertBy, and replaceUnique) first query the unique indexes to check for conflicts. You could instead optimistically attempt to perform the operation (e.g. replace instead of replaceUnique). However,

  • there is some fragility to trying to catch the correct exception and determing the column of failure;
  • an exception will automatically abort the current SQL transaction.

Minimal complete definition

deleteBy

Methods

deleteBy :: (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m () #

Delete a specific record by unique key. Does nothing if no record matches.

Example usage

Expand

With schema-1 and dataset-1,

deleteBySpjName :: MonadIO m => ReaderT SqlBackend m ()
deleteBySpjName = deleteBy UniqueUserName "SPJ"

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

+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+

insertUnique :: (MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m (Maybe (Key record)) #

Like insert, but returns Nothing when the record couldn't be inserted because of a uniqueness constraint.

Example usage

Expand

With schema-1 and dataset-1, we try to insert the following two records:

linusId <- insertUnique $ User "Linus" 48
spjId   <- insertUnique $ User "SPJ" 90
+-----+------+-----+
|id   |name  |age  |
+-----+------+-----+
|1    |SPJ   |40   |
+-----+------+-----+
|2    |Simon |41   |
+-----+------+-----+
|3    |Linus |48   |
+-----+------+-----+

Linus's record was inserted to dataset-1, while SPJ wasn't because SPJ already exists in dataset-1.

upsert #

Arguments

:: (MonadIO m, PersistRecordBackend record backend, OnlyOneUniqueKey record) 
=> record

new record to insert

-> [Update record]

updates to perform if the record already exists

-> ReaderT backend m (Entity record)

the record in the database after the operation

Update based on a uniqueness constraint or insert:

  • insert the new record if it does not exist;
  • If the record exists (matched via it's uniqueness constraint), then update the existing record with the parameters which is passed on as list to the function.

Example usage

Expand

First, we try to explain upsert using schema-1 and dataset-1.

upsertSpj :: MonadIO m => [Update User] -> ReaderT SqlBackend m (Maybe (Entity User))
upsertSpj updates = upsert (User "SPJ" 999) upadtes
mSpjEnt <- upsertSpj [UserAge +=. 15]

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

+-----+-----+--------+
|id   |name |age     |
+-----+-----+--------+
|1    |SPJ  |40 -> 55|
+-----+-----+--------+
|2    |Simon|41      |
+-----+-----+--------+
upsertX :: MonadIO m => [Update User] -> ReaderT SqlBackend m (Maybe (Entity User))
upsertX updates = upsert (User "X" 999) updates
mXEnt <- upsertX [UserAge +=. 15]

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

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

Next, what if the schema has two uniqueness constraints? Let's check it out using schema-2:

mSpjEnt <- upsertSpj [UserAge +=. 15]

This fails with a compile-time type error alerting us to the fact that this record has multiple unique keys, and suggests that we look for upsertBy to select the unique key we want.

upsertBy #

Arguments

:: (MonadIO m, PersistRecordBackend record backend) 
=> Unique record

uniqueness constraint to find by

-> record

new record to insert

-> [Update record]

updates to perform if the record already exists

-> ReaderT backend m (Entity record)

the record in the database after the operation

Update based on a given uniqueness constraint or insert:

  • insert the new record if it does not exist;
  • update the existing record that matches the given uniqueness constraint.

Example usage

Expand

We try to explain upsertBy using schema-2 and dataset-1.

upsertBySpjName :: MonadIO m => User -> [Update User] -> ReaderT SqlBackend m (Entity User)
upsertBySpjName record updates = upsertBy (UniqueUserName "SPJ") record updates
mSpjEnt <- upsertBySpjName (Person "X" 999) [PersonAge += .15]

The above query will alter dataset-1 to:

+-----+-----+--------+
|id   |name |age     |
+-----+-----+--------+
|1    |SPJ  |40 -> 55|
+-----+-----+--------+
|2    |Simon|41      |
+-----+-----+--------+
upsertBySimonAge :: MonadIO m => User -> [Update User] -> ReaderT SqlBackend m (Entity User)
upsertBySimonAge record updates = upsertBy (UniqueUserName "SPJ") record updates
mPhilipEnt <- upsertBySimonAge (User "X" 999) [UserName =. "Philip"]

The above query will alter dataset-1 to:

+----+-----------------+-----+
| id |      name       | age |
+----+-----------------+-----+
|  1 | SPJ             |  40 |
+----+-----------------+-----+
|  2 | Simon -> Philip |  41 |
+----+-----------------+-----+
upsertByUnknownName :: MonadIO m => User -> [Update User] -> ReaderT SqlBackend m (Entity User)
upsertByUnknownName record updates = upsertBy (UniqueUserName "Unknown") record updates
mXEnt <- upsertByUnknownName (User "X" 999) [UserAge +=. 15]

This query will alter dataset-1 to:

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

putMany #

Arguments

:: (MonadIO m, PersistRecordBackend record backend) 
=> [record]

A list of the records you want to insert or replace.

-> ReaderT backend m () 

Put many records into db

  • insert new records that do not exist (or violate any unique constraints)
  • replace existing records (matching any unique constraint)

Since: persistent-2.8.1

class PersistField a => PersistFieldSql a where #

Tells Persistent what database column type should be used to store a Haskell type.

Examples

Expand
Simple Boolean Alternative
data Switch = On | Off
  deriving (Show, Eq)

instance PersistField Switch where
  toPersistValue s = case s of
    On -> PersistBool True
    Off -> PersistBool False
  fromPersistValue (PersistBool b) = if b then Right On else Right Off
  fromPersistValue x = Left $ "File.hs: When trying to deserialize a Switch: expected PersistBool, received: " <> T.pack (show x)

instance PersistFieldSql Switch where
  sqlType _ = SqlBool
Non-Standard Database Types

If your database supports non-standard types, such as Postgres' uuid, you can use SqlOther to use them:

import qualified Data.UUID as UUID
instance PersistField UUID where
  toPersistValue = PersistDbSpecific . toASCIIBytes
  fromPersistValue (PersistDbSpecific uuid) =
    case fromASCIIBytes uuid of
      Nothing -> Left $ "Model/CustomTypes.hs: Failed to deserialize a UUID; received: " <> T.pack (show uuid)
      Just uuid' -> Right uuid'
  fromPersistValue x = Left $ "File.hs: When trying to deserialize a UUID: expected PersistDbSpecific, received: "-- >  <> T.pack (show x)

instance PersistFieldSql UUID where
  sqlType _ = SqlOther "uuid"
User Created Database Types

Similarly, some databases support creating custom types, e.g. Postgres' DOMAIN and ENUM features. You can use SqlOther to specify a custom type:

CREATE DOMAIN ssn AS text
      CHECK ( value ~ '^[0-9]{9}$');
instance PersistFieldSQL SSN where
  sqlType _ = SqlOther "ssn"
CREATE TYPE rainbow_color AS ENUM ('red', 'orange', 'yellow', 'green', 'blue', 'indigo', 'violet');
instance PersistFieldSQL RainbowColor where
  sqlType _ = SqlOther "rainbow_color"

Methods

sqlType :: Proxy a -> SqlType #

Instances
PersistFieldSql Bool 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Bool -> SqlType #

PersistFieldSql Double 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Int 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int -> SqlType #

PersistFieldSql Int8 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int8 -> SqlType #

PersistFieldSql Int16 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int16 -> SqlType #

PersistFieldSql Int32 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int32 -> SqlType #

PersistFieldSql Int64 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Int64 -> SqlType #

PersistFieldSql Natural 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Rational 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Word 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Word -> SqlType #

PersistFieldSql Word8 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Word8 -> SqlType #

PersistFieldSql Word16 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Word32 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Word64 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql ByteString 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Text 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Text -> SqlType #

PersistFieldSql UTCTime 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Text 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Text -> SqlType #

PersistFieldSql Html 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Html -> SqlType #

PersistFieldSql Checkmark 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql PersistValue 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql TimeOfDay 
Instance details

Defined in Database.Persist.Sql.Class

PersistFieldSql Day 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy Day -> SqlType #

PersistFieldSql [Char] 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy [Char] -> SqlType #

PersistFieldSql a => PersistFieldSql [a] 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy [a] -> SqlType #

HasResolution a => PersistFieldSql (Fixed a) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Fixed a) -> SqlType #

PersistFieldSql v => PersistFieldSql (IntMap v) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (IntMap v) -> SqlType #

(Ord a, PersistFieldSql a) => PersistFieldSql (Set a) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Set a) -> SqlType #

(PersistField record, PersistEntity record) => PersistFieldSql (Entity record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Entity record) -> SqlType #

PersistFieldSql a => PersistFieldSql (Vector a) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Vector a) -> SqlType #

(FromJSON a, ToJSON a) => PersistFieldSql (JSONB a) Source #

jsonb

Since: 3.1.0

Instance details

Defined in Database.Esqueleto.PostgreSQL.JSON.Instances

Methods

sqlType :: Proxy (JSONB a) -> SqlType #

(PersistFieldSql a, PersistFieldSql b) => PersistFieldSql (a, b) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (a, b) -> SqlType #

PersistFieldSql v => PersistFieldSql (Map Text v) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Map Text v) -> SqlType #

class RawSql a where #

Class for data types that may be retrived from a rawSql query.

Methods

rawSqlCols :: (DBName -> Text) -> a -> (Int, [Text]) #

Number of columns that this data type needs and the list of substitutions for SELECT placeholders ??.

rawSqlColCountReason :: a -> String #

A string telling the user why the column count is what it is.

rawSqlProcessRow :: [PersistValue] -> Either Text a #

Transform a row of the result into the data type.

Instances
RawSql a => RawSql (Maybe a)

Since: persistent-1.0.1

Instance details

Defined in Database.Persist.Sql.Class

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

(PersistEntity a, PersistEntityBackend a ~ backend, IsPersistBackend backend) => RawSql (Key a) 
Instance details

Defined in Database.Persist.Sql.Class

(PersistEntity record, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (Entity record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> Entity record -> (Int, [Text]) #

rawSqlColCountReason :: Entity record -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (Entity record) #

(RawSql a, RawSql b) => RawSql (a, b) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b) #

(RawSql a, RawSql b, RawSql c) => RawSql (a, b, c) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c) #

(RawSql a, RawSql b, RawSql c, RawSql d) => RawSql (a, b, c, d) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e) => RawSql (a, b, c, d, e) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f) => RawSql (a, b, c, d, e, f) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g) => RawSql (a, b, c, d, e, f, g) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h) => RawSql (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i) => RawSql (a, b, c, d, e, f, g, h, i)

Since: persistent-2.10.2

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j) => RawSql (a, b, c, d, e, f, g, h, i, j)

Since: persistent-2.10.2

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k) => RawSql (a, b, c, d, e, f, g, h, i, j, k)

Since: persistent-2.10.2

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l)

Since: persistent-2.10.2

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l) #

data Column #

Instances
Eq Column 
Instance details

Defined in Database.Persist.Sql.Types

Methods

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

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

Ord Column 
Instance details

Defined in Database.Persist.Sql.Types

Show Column 
Instance details

Defined in Database.Persist.Sql.Types

type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () #

A Migration is a four level monad stack consisting of:

newtype Single a #

A single column (see rawSql). Any PersistField may be used here, including PersistValue (which does not do any processing).

Constructors

Single 

Fields

Instances
Eq a => Eq (Single a) 
Instance details

Defined in Database.Persist.Sql.Types

Methods

(==) :: Single a -> Single a -> Bool #

(/=) :: Single a -> Single a -> Bool #

Ord a => Ord (Single a) 
Instance details

Defined in Database.Persist.Sql.Types

Methods

compare :: Single a -> Single a -> Ordering #

(<) :: Single a -> Single a -> Bool #

(<=) :: Single a -> Single a -> Bool #

(>) :: Single a -> Single a -> Bool #

(>=) :: Single a -> Single a -> Bool #

max :: Single a -> Single a -> Single a #

min :: Single a -> Single a -> Single a #

Read a => Read (Single a) 
Instance details

Defined in Database.Persist.Sql.Types

Show a => Show (Single a) 
Instance details

Defined in Database.Persist.Sql.Types

Methods

showsPrec :: Int -> Single a -> ShowS #

show :: Single a -> String #

showList :: [Single a] -> ShowS #

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

type Sql = Text #

type SqlPersistT = (ReaderT SqlBackend :: (Type -> Type) -> Type -> Type) #

type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) #

A backend which is a wrapper around SqlBackend.

type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO () #

data SqlBackend #

Constructors

SqlBackend 

Fields

type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend) #

A constraint synonym which witnesses that a backend is SQL and can run read queries.

type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend) #

A constraint synonym which witnesses that a backend is SQL and can run read and write queries.

type SqlReadT (m :: Type -> Type) a = forall backend. SqlBackendCanRead backend => ReaderT backend m a #

Like SqlPersistT but compatible with any SQL backend which can handle read queries.

type SqlWriteT (m :: Type -> Type) a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a #

Like SqlPersistT but compatible with any SQL backend which can handle read and write queries.

data Statement #

Constructors

Statement 

Fields

type Attr = Text #

data Checkmark #

A Checkmark should be used as a field type whenever a uniqueness constraint should guarantee that a certain kind of record may appear at most once, but other kinds of records may appear any number of times.

NOTE: You need to mark any Checkmark fields as nullable (see the following example).

For example, suppose there's a Location entity that represents where a user has lived:

Location
    user    UserId
    name    Text
    current Checkmark nullable

    UniqueLocation user current

The UniqueLocation constraint allows any number of Inactive Locations to be current. However, there may be at most one current Location per user (i.e., either zero or one per user).

This data type works because of the way that SQL treats NULLable fields within uniqueness constraints. The SQL standard says that NULL values should be considered different, so we represent Inactive as SQL NULL, thus allowing any number of Inactive records. On the other hand, we represent Active as TRUE, so the uniqueness constraint will disallow more than one Active record.

Note: There may be DBMSs that do not respect the SQL standard's treatment of NULL values on uniqueness constraints, please check if this data type works before relying on it.

The SQL BOOLEAN type is used because it's the smallest data type available. Note that we never use FALSE, just TRUE and NULL. Provides the same behavior Maybe () would if () was a valid PersistField.

Constructors

Active

When used on a uniqueness constraint, there may be at most one Active record.

Inactive

When used on a uniqueness constraint, there may be any number of Inactive records.

Instances
Bounded Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Enum Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Eq Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Ord Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Read Checkmark 
Instance details

Defined in Database.Persist.Types.Base

Show Checkmark 
Instance details

Defined in Database.Persist.Types.Base

ToHttpApiData Checkmark 
Instance details

Defined in Database.Persist.Types.Base

FromHttpApiData Checkmark 
Instance details

Defined in Database.Persist.Types.Base

PathPiece Checkmark 
Instance details

Defined in Database.Persist.Types.Base

PersistFieldSql Checkmark 
Instance details

Defined in Database.Persist.Sql.Class

PersistField Checkmark 
Instance details

Defined in Database.Persist.Class.PersistField

newtype DBName #

Constructors

DBName 

Fields

Instances
Eq DBName 
Instance details

Defined in Database.Persist.Types.Base

Methods

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

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

Ord DBName 
Instance details

Defined in Database.Persist.Types.Base

Read DBName 
Instance details

Defined in Database.Persist.Types.Base

Show DBName 
Instance details

Defined in Database.Persist.Types.Base

data EmbedFieldDef #

An EmbedFieldDef is the same as a FieldDef But it is only used for embeddedFields so it only has data needed for embedding

Constructors

EmbedFieldDef 

Fields

data EntityDef #

An EntityDef represents the information that persistent knows about an Entity. It uses this information to generate the Haskell datatype, the SQL migrations, and other relevant conversions.

Constructors

EntityDef 

Fields

type ExtraLine = [Text] #

data FieldDef #

A FieldDef represents the inormation that persistent knows about a field of a datatype. This includes information used to parse the field out of the database and what the field corresponds to.

Constructors

FieldDef 

Fields

  • fieldHaskell :: !HaskellName

    The name of the field. Note that this does not corresponds to the record labels generated for the particular entity - record labels are generated with the type name prefixed to the field, so a FieldDef that contains a HaskellName "name" for a type User will have a record field userName.

  • fieldDB :: !DBName

    The name of the field in the database. For SQL databases, this corresponds to the column name.

  • fieldType :: !FieldType

    The type of the field in Haskell.

  • fieldSqlType :: !SqlType

    The type of the field in a SQL database.

  • fieldAttrs :: ![Attr]

    User annotations for a field. These are provided with the ! operator.

  • fieldStrict :: !Bool

    If this is True, then the Haskell datatype will have a strict record field. The default value for this is True.

  • fieldReference :: !ReferenceDef
     
  • fieldComments :: !(Maybe Text)

    Optional comments for a Field. There is not currently a way to attach comments to a field in the quasiquoter.

    Since: persistent-2.10.0

type ForeignFieldDef = (HaskellName, DBName) #

Used instead of FieldDef to generate a smaller amount of code

data IsNullable #

Instances
Eq IsNullable 
Instance details

Defined in Database.Persist.Types.Base

Show IsNullable 
Instance details

Defined in Database.Persist.Types.Base

data PersistValue #

A raw value which can be stored in any backend and can be marshalled to and from a PersistField.

Constructors

PersistText Text 
PersistByteString ByteString 
PersistInt64 Int64 
PersistDouble Double 
PersistRational Rational 
PersistBool Bool 
PersistDay Day 
PersistTimeOfDay TimeOfDay 
PersistUTCTime UTCTime 
PersistNull 
PersistList [PersistValue] 
PersistMap [(Text, PersistValue)] 
PersistObjectId ByteString

Intended especially for MongoDB backend

PersistArray [PersistValue]

Intended especially for PostgreSQL backend for text arrays

PersistDbSpecific ByteString

Using PersistDbSpecific allows you to use types specific to a particular backend For example, below is a simple example of the PostGIS geography type:

data Geo = Geo ByteString

instance PersistField Geo where
  toPersistValue (Geo t) = PersistDbSpecific t

  fromPersistValue (PersistDbSpecific t) = Right $ Geo $ Data.ByteString.concat ["'", t, "'"]
  fromPersistValue _ = Left "Geo values must be converted from PersistDbSpecific"

instance PersistFieldSql Geo where
  sqlType _ = SqlOther "GEOGRAPHY(POINT,4326)"

toPoint :: Double -> Double -> Geo
toPoint lat lon = Geo $ Data.ByteString.concat ["'POINT(", ps $ lon, " ", ps $ lat, ")'"]
  where ps = Data.Text.pack . show

If Foo has a geography field, we can then perform insertions like the following:

insert $ Foo (toPoint 44 44)
Instances
Eq PersistValue 
Instance details

Defined in Database.Persist.Types.Base

Ord PersistValue 
Instance details

Defined in Database.Persist.Types.Base

Read PersistValue 
Instance details

Defined in Database.Persist.Types.Base

Show PersistValue 
Instance details

Defined in Database.Persist.Types.Base

ToJSON PersistValue 
Instance details

Defined in Database.Persist.Types.Base

FromJSON PersistValue 
Instance details

Defined in Database.Persist.Types.Base

ToHttpApiData PersistValue 
Instance details

Defined in Database.Persist.Types.Base

FromHttpApiData PersistValue 
Instance details

Defined in Database.Persist.Types.Base

PathPiece PersistValue 
Instance details

Defined in Database.Persist.Types.Base

PersistFieldSql PersistValue 
Instance details

Defined in Database.Persist.Sql.Class

PersistField PersistValue 
Instance details

Defined in Database.Persist.Class.PersistField

data ReferenceDef #

There are 3 kinds of references 1) composite (to fields that exist in the record) 2) single field 3) embedded

Constructors

NoReference 
ForeignRef !HaskellName !FieldType

A ForeignRef has a late binding to the EntityDef it references via HaskellName and has the Haskell type of the foreign key in the form of FieldType

EmbedRef EmbedEntityDef 
CompositeRef CompositeDef 
SelfReference

A SelfReference stops an immediate cycle which causes non-termination at compile-time (issue #311).

data SqlType #

A SQL data type. Naming attempts to reflect the underlying Haskell datatypes, eg SqlString instead of SqlVarchar. Different SQL databases may have different translations for these types.

Constructors

SqlString 
SqlInt32 
SqlInt64 
SqlReal 
SqlNumeric Word32 Word32 
SqlBool 
SqlDay 
SqlTime 
SqlDayTime

Always uses UTC timezone

SqlBlob 
SqlOther Text

a backend-specific name

data WhyNullable #

The reason why a field is nullable is very important. A field that is nullable because of a Maybe tag will have its type changed from A to Maybe A. OTOH, a field that is nullable because of a nullable tag will remain with the same type.